OSDN Git Service

2011-09-27 Pascal Obry <obry@adacore.com>
[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-2011, 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 (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
264         (Get_Pragma_Arg (Arg1), Standard_Boolean);
265
266       --  For a class-wide condition, a reference to a controlling formal must
267       --  be interpreted as having the class-wide type (or an access to such)
268       --  so that the inherited condition can be properly applied to any
269       --  overriding operation (see ARM12 6.6.1 (7)).
270
271       if Class_Present (N) then
272          declare
273             T   : constant Entity_Id := Find_Dispatching_Type (S);
274
275             ACW : Entity_Id := Empty;
276             --  Access to T'class, created if there is a controlling formal
277             --  that is an access parameter.
278
279             function Get_ACW return Entity_Id;
280             --  If the expression has a reference to an controlling access
281             --  parameter, create an access to T'class for the necessary
282             --  conversions if one does not exist.
283
284             function Process (N : Node_Id) return Traverse_Result;
285             --  ARM 6.1.1: Within the expression for a Pre'Class or Post'Class
286             --  aspect for a primitive subprogram of a tagged type T, a name
287             --  that denotes a formal parameter of type T is interpreted as
288             --  having type T'Class. Similarly, a name that denotes a formal
289             --  accessparameter of type access-to-T is interpreted as having
290             --  type access-to-T'Class. This ensures the expression is well-
291             --  defined for a primitive subprogram of a type descended from T.
292
293             -------------
294             -- Get_ACW --
295             -------------
296
297             function Get_ACW return Entity_Id is
298                Loc  : constant Source_Ptr := Sloc (N);
299                Decl : Node_Id;
300
301             begin
302                if No (ACW) then
303                   Decl := Make_Full_Type_Declaration (Loc,
304                     Defining_Identifier => Make_Temporary (Loc, 'T'),
305                     Type_Definition =>
306                        Make_Access_To_Object_Definition (Loc,
307                        Subtype_Indication =>
308                          New_Occurrence_Of (Class_Wide_Type (T), Loc),
309                        All_Present => True));
310
311                   Insert_Before (Unit_Declaration_Node (S), Decl);
312                   Analyze (Decl);
313                   ACW := Defining_Identifier (Decl);
314                   Freeze_Before (Unit_Declaration_Node (S), ACW);
315                end if;
316
317                return ACW;
318             end Get_ACW;
319
320             -------------
321             -- Process --
322             -------------
323
324             function Process (N : Node_Id) return Traverse_Result is
325                Loc : constant Source_Ptr := Sloc (N);
326                Typ : Entity_Id;
327
328             begin
329                if Is_Entity_Name (N)
330                  and then Is_Formal (Entity (N))
331                  and then Nkind (Parent (N)) /= N_Type_Conversion
332                then
333                   if Etype (Entity (N)) = T then
334                      Typ := Class_Wide_Type (T);
335
336                   elsif Is_Access_Type (Etype (Entity (N)))
337                     and then Designated_Type (Etype (Entity (N))) = T
338                   then
339                      Typ := Get_ACW;
340                   else
341                      Typ := Empty;
342                   end if;
343
344                   if Present (Typ) then
345                      Rewrite (N,
346                        Make_Type_Conversion (Loc,
347                          Subtype_Mark =>
348                            New_Occurrence_Of (Typ, Loc),
349                          Expression  => New_Occurrence_Of (Entity (N), Loc)));
350                      Set_Etype (N, Typ);
351                   end if;
352                end if;
353
354                return OK;
355             end Process;
356
357             procedure Replace_Type is new Traverse_Proc (Process);
358
359          begin
360             Replace_Type (Get_Pragma_Arg (Arg1));
361          end;
362       end if;
363
364       --  Remove the subprogram from the scope stack now that the pre-analysis
365       --  of the precondition/postcondition is done.
366
367       End_Scope;
368    end Analyze_PPC_In_Decl_Part;
369
370    --------------------
371    -- Analyze_Pragma --
372    --------------------
373
374    procedure Analyze_Pragma (N : Node_Id) is
375       Loc     : constant Source_Ptr := Sloc (N);
376       Prag_Id : Pragma_Id;
377
378       Pname : Name_Id;
379       --  Name of the source pragma, or name of the corresponding aspect for
380       --  pragmas which originate in a source aspect. In the latter case, the
381       --  name may be different from the pragma name.
382
383       Pragma_Exit : exception;
384       --  This exception is used to exit pragma processing completely. It is
385       --  used when an error is detected, and no further processing is
386       --  required. It is also used if an earlier error has left the tree in
387       --  a state where the pragma should not be processed.
388
389       Arg_Count : Nat;
390       --  Number of pragma argument associations
391
392       Arg1 : Node_Id;
393       Arg2 : Node_Id;
394       Arg3 : Node_Id;
395       Arg4 : Node_Id;
396       --  First four pragma arguments (pragma argument association nodes, or
397       --  Empty if the corresponding argument does not exist).
398
399       type Name_List is array (Natural range <>) of Name_Id;
400       type Args_List is array (Natural range <>) of Node_Id;
401       --  Types used for arguments to Check_Arg_Order and Gather_Associations
402
403       procedure Ada_2005_Pragma;
404       --  Called for pragmas defined in Ada 2005, that are not in Ada 95. In
405       --  Ada 95 mode, these are implementation defined pragmas, so should be
406       --  caught by the No_Implementation_Pragmas restriction.
407
408       procedure Ada_2012_Pragma;
409       --  Called for pragmas defined in Ada 2012, that are not in Ada 95 or 05.
410       --  In Ada 95 or 05 mode, these are implementation defined pragmas, so
411       --  should be caught by the No_Implementation_Pragmas restriction.
412
413       procedure Check_Ada_83_Warning;
414       --  Issues a warning message for the current pragma if operating in Ada
415       --  83 mode (used for language pragmas that are not a standard part of
416       --  Ada 83). This procedure does not raise Error_Pragma. Also notes use
417       --  of 95 pragma.
418
419       procedure Check_Arg_Count (Required : Nat);
420       --  Check argument count for pragma is equal to given parameter. If not,
421       --  then issue an error message and raise Pragma_Exit.
422
423       --  Note: all routines whose name is Check_Arg_Is_xxx take an argument
424       --  Arg which can either be a pragma argument association, in which case
425       --  the check is applied to the expression of the association or an
426       --  expression directly.
427
428       procedure Check_Arg_Is_External_Name (Arg : Node_Id);
429       --  Check that an argument has the right form for an EXTERNAL_NAME
430       --  parameter of an extended import/export pragma. The rule is that the
431       --  name must be an identifier or string literal (in Ada 83 mode) or a
432       --  static string expression (in Ada 95 mode).
433
434       procedure Check_Arg_Is_Identifier (Arg : Node_Id);
435       --  Check the specified argument Arg to make sure that it is an
436       --  identifier. If not give error and raise Pragma_Exit.
437
438       procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id);
439       --  Check the specified argument Arg to make sure that it is an integer
440       --  literal. If not give error and raise Pragma_Exit.
441
442       procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id);
443       --  Check the specified argument Arg to make sure that it has the proper
444       --  syntactic form for a local name and meets the semantic requirements
445       --  for a local name. The local name is analyzed as part of the
446       --  processing for this call. In addition, the local name is required
447       --  to represent an entity at the library level.
448
449       procedure Check_Arg_Is_Local_Name (Arg : Node_Id);
450       --  Check the specified argument Arg to make sure that it has the proper
451       --  syntactic form for a local name and meets the semantic requirements
452       --  for a local name. The local name is analyzed as part of the
453       --  processing for this call.
454
455       procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id);
456       --  Check the specified argument Arg to make sure that it is a valid
457       --  locking policy name. If not give error and raise Pragma_Exit.
458
459       procedure Check_Arg_Is_One_Of
460         (Arg                : Node_Id;
461          N1, N2             : Name_Id);
462       procedure Check_Arg_Is_One_Of
463         (Arg                : Node_Id;
464          N1, N2, N3         : Name_Id);
465       procedure Check_Arg_Is_One_Of
466         (Arg                : Node_Id;
467          N1, N2, N3, N4, N5 : Name_Id);
468       --  Check the specified argument Arg to make sure that it is an
469       --  identifier whose name matches either N1 or N2 (or N3, N4, N5 if
470       --  present). If not then give error and raise Pragma_Exit.
471
472       procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id);
473       --  Check the specified argument Arg to make sure that it is a valid
474       --  queuing policy name. If not give error and raise Pragma_Exit.
475
476       procedure Check_Arg_Is_Static_Expression
477         (Arg : Node_Id;
478          Typ : Entity_Id := Empty);
479       --  Check the specified argument Arg to make sure that it is a static
480       --  expression of the given type (i.e. it will be analyzed and resolved
481       --  using this type, which can be any valid argument to Resolve, e.g.
482       --  Any_Integer is OK). If not, given error and raise Pragma_Exit. If
483       --  Typ is left Empty, then any static expression is allowed.
484
485       procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id);
486       --  Check the specified argument Arg to make sure that it is a valid task
487       --  dispatching policy name. If not give error and raise Pragma_Exit.
488
489       procedure Check_Arg_Order (Names : Name_List);
490       --  Checks for an instance of two arguments with identifiers for the
491       --  current pragma which are not in the sequence indicated by Names,
492       --  and if so, generates a fatal message about bad order of arguments.
493
494       procedure Check_At_Least_N_Arguments (N : Nat);
495       --  Check there are at least N arguments present
496
497       procedure Check_At_Most_N_Arguments (N : Nat);
498       --  Check there are no more than N arguments present
499
500       procedure Check_Component
501         (Comp            : Node_Id;
502          UU_Typ          : Entity_Id;
503          In_Variant_Part : Boolean := False);
504       --  Examine an Unchecked_Union component for correct use of per-object
505       --  constrained subtypes, and for restrictions on finalizable components.
506       --  UU_Typ is the related Unchecked_Union type. Flag In_Variant_Part
507       --  should be set when Comp comes from a record variant.
508
509       procedure Check_Duplicate_Pragma (E : Entity_Id);
510       --  Check if a pragma of the same name as the current pragma is already
511       --  chained as a rep pragma to the given entity. If so give a message
512       --  about the duplicate, and then raise Pragma_Exit so does not return.
513       --  Also checks for delayed aspect specification node in the chain.
514
515       procedure Check_Duplicated_Export_Name (Nam : Node_Id);
516       --  Nam is an N_String_Literal node containing the external name set by
517       --  an Import or Export pragma (or extended Import or Export pragma).
518       --  This procedure checks for possible duplications if this is the export
519       --  case, and if found, issues an appropriate error message.
520
521       procedure Check_First_Subtype (Arg : Node_Id);
522       --  Checks that Arg, whose expression is an entity name, references a
523       --  first subtype.
524
525       procedure Check_Identifier (Arg : Node_Id; Id : Name_Id);
526       --  Checks that the given argument has an identifier, and if so, requires
527       --  it to match the given identifier name. If there is no identifier, or
528       --  a non-matching identifier, then an error message is given and
529       --  Pragma_Exit is raised.
530
531       procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id);
532       --  Checks that the given argument has an identifier, and if so, requires
533       --  it to match one of the given identifier names. If there is no
534       --  identifier, or a non-matching identifier, then an error message is
535       --  given and Pragma_Exit is raised.
536
537       procedure Check_In_Main_Program;
538       --  Common checks for pragmas that appear within a main program
539       --  (Priority, Main_Storage, Time_Slice, Relative_Deadline, CPU).
540
541       procedure Check_Interrupt_Or_Attach_Handler;
542       --  Common processing for first argument of pragma Interrupt_Handler or
543       --  pragma Attach_Handler.
544
545       procedure Check_Is_In_Decl_Part_Or_Package_Spec;
546       --  Check that pragma appears in a declarative part, or in a package
547       --  specification, i.e. that it does not occur in a statement sequence
548       --  in a body.
549
550       procedure Check_No_Identifier (Arg : Node_Id);
551       --  Checks that the given argument does not have an identifier. If
552       --  an identifier is present, then an error message is issued, and
553       --  Pragma_Exit is raised.
554
555       procedure Check_No_Identifiers;
556       --  Checks that none of the arguments to the pragma has an identifier.
557       --  If any argument has an identifier, then an error message is issued,
558       --  and Pragma_Exit is raised.
559
560       procedure Check_No_Link_Name;
561       --  Checks that no link name is specified
562
563       procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id);
564       --  Checks if the given argument has an identifier, and if so, requires
565       --  it to match the given identifier name. If there is a non-matching
566       --  identifier, then an error message is given and Pragma_Exit is raised.
567
568       procedure Check_Optional_Identifier (Arg : Node_Id; Id : String);
569       --  Checks if the given argument has an identifier, and if so, requires
570       --  it to match the given identifier name. If there is a non-matching
571       --  identifier, then an error message is given and Pragma_Exit is raised.
572       --  In this version of the procedure, the identifier name is given as
573       --  a string with lower case letters.
574
575       procedure Check_Precondition_Postcondition (In_Body : out Boolean);
576       --  Called to process a precondition or postcondition pragma. There are
577       --  three cases:
578       --
579       --    The pragma appears after a subprogram spec
580       --
581       --      If the corresponding check is not enabled, the pragma is analyzed
582       --      but otherwise ignored and control returns with In_Body set False.
583       --
584       --      If the check is enabled, then the first step is to analyze the
585       --      pragma, but this is skipped if the subprogram spec appears within
586       --      a package specification (because this is the case where we delay
587       --      analysis till the end of the spec). Then (whether or not it was
588       --      analyzed), the pragma is chained to the subprogram in question
589       --      (using Spec_PPC_List and Next_Pragma) and control returns to the
590       --      caller with In_Body set False.
591       --
592       --    The pragma appears at the start of subprogram body declarations
593       --
594       --      In this case an immediate return to the caller is made with
595       --      In_Body set True, and the pragma is NOT analyzed.
596       --
597       --    In all other cases, an error message for bad placement is given
598
599       procedure Check_Static_Constraint (Constr : Node_Id);
600       --  Constr is a constraint from an N_Subtype_Indication node from a
601       --  component constraint in an Unchecked_Union type. This routine checks
602       --  that the constraint is static as required by the restrictions for
603       --  Unchecked_Union.
604
605       procedure Check_Test_Case;
606       --  Called to process a test-case pragma. The treatment is similar to the
607       --  one for pre- and postcondition in Check_Precondition_Postcondition,
608       --  except the placement rules for the test-case pragma are stricter.
609       --  This pragma may only occur after a subprogram spec declared directly
610       --  in a package spec unit. In this case, the pragma is chained to the
611       --  subprogram in question (using Spec_TC_List and Next_Pragma) and
612       --  analysis of the pragma is delayed till the end of the spec. In
613       --  all other cases, an error message for bad placement is given.
614
615       procedure Check_Valid_Configuration_Pragma;
616       --  Legality checks for placement of a configuration pragma
617
618       procedure Check_Valid_Library_Unit_Pragma;
619       --  Legality checks for library unit pragmas. A special case arises for
620       --  pragmas in generic instances that come from copies of the original
621       --  library unit pragmas in the generic templates. In the case of other
622       --  than library level instantiations these can appear in contexts which
623       --  would normally be invalid (they only apply to the original template
624       --  and to library level instantiations), and they are simply ignored,
625       --  which is implemented by rewriting them as null statements.
626
627       procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id);
628       --  Check an Unchecked_Union variant for lack of nested variants and
629       --  presence of at least one component. UU_Typ is the related Unchecked_
630       --  Union type.
631
632       procedure Error_Pragma (Msg : String);
633       pragma No_Return (Error_Pragma);
634       --  Outputs error message for current pragma. The message contains a %
635       --  that will be replaced with the pragma name, and the flag is placed
636       --  on the pragma itself. Pragma_Exit is then raised.
637
638       procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id);
639       pragma No_Return (Error_Pragma_Arg);
640       --  Outputs error message for current pragma. The message may contain
641       --  a % that will be replaced with the pragma name. The parameter Arg
642       --  may either be a pragma argument association, in which case the flag
643       --  is placed on the expression of this association, or an expression,
644       --  in which case the flag is placed directly on the expression. The
645       --  message is placed using Error_Msg_N, so the message may also contain
646       --  an & insertion character which will reference the given Arg value.
647       --  After placing the message, Pragma_Exit is raised.
648
649       procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id);
650       pragma No_Return (Error_Pragma_Arg);
651       --  Similar to above form of Error_Pragma_Arg except that two messages
652       --  are provided, the second is a continuation comment starting with \.
653
654       procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id);
655       pragma No_Return (Error_Pragma_Arg_Ident);
656       --  Outputs error message for current pragma. The message may contain
657       --  a % that will be replaced with the pragma name. The parameter Arg
658       --  must be a pragma argument association with a non-empty identifier
659       --  (i.e. its Chars field must be set), and the error message is placed
660       --  on the identifier. The message is placed using Error_Msg_N so
661       --  the message may also contain an & insertion character which will
662       --  reference the identifier. After placing the message, Pragma_Exit
663       --  is raised.
664
665       procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id);
666       pragma No_Return (Error_Pragma_Ref);
667       --  Outputs error message for current pragma. The message may contain
668       --  a % that will be replaced with the pragma name. The parameter Ref
669       --  must be an entity whose name can be referenced by & and sloc by #.
670       --  After placing the message, Pragma_Exit is raised.
671
672       function Find_Lib_Unit_Name return Entity_Id;
673       --  Used for a library unit pragma to find the entity to which the
674       --  library unit pragma applies, returns the entity found.
675
676       procedure Find_Program_Unit_Name (Id : Node_Id);
677       --  If the pragma is a compilation unit pragma, the id must denote the
678       --  compilation unit in the same compilation, and the pragma must appear
679       --  in the list of preceding or trailing pragmas. If it is a program
680       --  unit pragma that is not a compilation unit pragma, then the
681       --  identifier must be visible.
682
683       function Find_Unique_Parameterless_Procedure
684         (Name : Entity_Id;
685          Arg  : Node_Id) return Entity_Id;
686       --  Used for a procedure pragma to find the unique parameterless
687       --  procedure identified by Name, returns it if it exists, otherwise
688       --  errors out and uses Arg as the pragma argument for the message.
689
690       procedure Fix_Error (Msg : in out String);
691       --  This is called prior to issuing an error message. Msg is a string
692       --  which typically contains the substring pragma. If the current pragma
693       --  comes from an aspect, each such "pragma" substring is replaced with
694       --  the characters "aspect", and if Error_Msg_Name_1 is Name_Precondition
695       --  (resp Name_Postcondition) it is changed to Name_Pre (resp Name_Post).
696
697       procedure Gather_Associations
698         (Names : Name_List;
699          Args  : out Args_List);
700       --  This procedure is used to gather the arguments for a pragma that
701       --  permits arbitrary ordering of parameters using the normal rules
702       --  for named and positional parameters. The Names argument is a list
703       --  of Name_Id values that corresponds to the allowed pragma argument
704       --  association identifiers in order. The result returned in Args is
705       --  a list of corresponding expressions that are the pragma arguments.
706       --  Note that this is a list of expressions, not of pragma argument
707       --  associations (Gather_Associations has completely checked all the
708       --  optional identifiers when it returns). An entry in Args is Empty
709       --  on return if the corresponding argument is not present.
710
711       procedure GNAT_Pragma;
712       --  Called for all GNAT defined pragmas to check the relevant restriction
713       --  (No_Implementation_Pragmas).
714
715       function Is_Before_First_Decl
716         (Pragma_Node : Node_Id;
717          Decls       : List_Id) return Boolean;
718       --  Return True if Pragma_Node is before the first declarative item in
719       --  Decls where Decls is the list of declarative items.
720
721       function Is_Configuration_Pragma return Boolean;
722       --  Determines if the placement of the current pragma is appropriate
723       --  for a configuration pragma.
724
725       function Is_In_Context_Clause return Boolean;
726       --  Returns True if pragma appears within the context clause of a unit,
727       --  and False for any other placement (does not generate any messages).
728
729       function Is_Static_String_Expression (Arg : Node_Id) return Boolean;
730       --  Analyzes the argument, and determines if it is a static string
731       --  expression, returns True if so, False if non-static or not String.
732
733       procedure Pragma_Misplaced;
734       pragma No_Return (Pragma_Misplaced);
735       --  Issue fatal error message for misplaced pragma
736
737       procedure Process_Atomic_Shared_Volatile;
738       --  Common processing for pragmas Atomic, Shared, Volatile. Note that
739       --  Shared is an obsolete Ada 83 pragma, treated as being identical
740       --  in effect to pragma Atomic.
741
742       procedure Process_Compile_Time_Warning_Or_Error;
743       --  Common processing for Compile_Time_Error and Compile_Time_Warning
744
745       procedure Process_Convention
746         (C   : out Convention_Id;
747          Ent : out Entity_Id);
748       --  Common processing for Convention, Interface, Import and Export.
749       --  Checks first two arguments of pragma, and sets the appropriate
750       --  convention value in the specified entity or entities. On return
751       --  C is the convention, Ent is the referenced entity.
752
753       procedure Process_Extended_Import_Export_Exception_Pragma
754         (Arg_Internal : Node_Id;
755          Arg_External : Node_Id;
756          Arg_Form     : Node_Id;
757          Arg_Code     : Node_Id);
758       --  Common processing for the pragmas Import/Export_Exception. The three
759       --  arguments correspond to the three named parameters of the pragma. An
760       --  argument is empty if the corresponding parameter is not present in
761       --  the pragma.
762
763       procedure Process_Extended_Import_Export_Object_Pragma
764         (Arg_Internal : Node_Id;
765          Arg_External : Node_Id;
766          Arg_Size     : Node_Id);
767       --  Common processing for the pragmas Import/Export_Object. The three
768       --  arguments correspond to the three named parameters of the pragmas. An
769       --  argument is empty if the corresponding parameter is not present in
770       --  the pragma.
771
772       procedure Process_Extended_Import_Export_Internal_Arg
773         (Arg_Internal : Node_Id := Empty);
774       --  Common processing for all extended Import and Export pragmas. The
775       --  argument is the pragma parameter for the Internal argument. If
776       --  Arg_Internal is empty or inappropriate, an error message is posted.
777       --  Otherwise, on normal return, the Entity_Field of Arg_Internal is
778       --  set to identify the referenced entity.
779
780       procedure Process_Extended_Import_Export_Subprogram_Pragma
781         (Arg_Internal                 : Node_Id;
782          Arg_External                 : Node_Id;
783          Arg_Parameter_Types          : Node_Id;
784          Arg_Result_Type              : Node_Id := Empty;
785          Arg_Mechanism                : Node_Id;
786          Arg_Result_Mechanism         : Node_Id := Empty;
787          Arg_First_Optional_Parameter : Node_Id := Empty);
788       --  Common processing for all extended Import and Export pragmas applying
789       --  to subprograms. The caller omits any arguments that do not apply to
790       --  the pragma in question (for example, Arg_Result_Type can be non-Empty
791       --  only in the Import_Function and Export_Function cases). The argument
792       --  names correspond to the allowed pragma association identifiers.
793
794       procedure Process_Generic_List;
795       --  Common processing for Share_Generic and Inline_Generic
796
797       procedure Process_Import_Or_Interface;
798       --  Common processing for Import of Interface
799
800       procedure Process_Import_Predefined_Type;
801       --  Processing for completing a type with pragma Import. This is used
802       --  to declare types that match predefined C types, especially for cases
803       --  without corresponding Ada predefined type.
804
805       procedure Process_Inline (Active : Boolean);
806       --  Common processing for Inline and Inline_Always. The parameter
807       --  indicates if the inline pragma is active, i.e. if it should actually
808       --  cause inlining to occur.
809
810       procedure Process_Interface_Name
811         (Subprogram_Def : Entity_Id;
812          Ext_Arg        : Node_Id;
813          Link_Arg       : Node_Id);
814       --  Given the last two arguments of pragma Import, pragma Export, or
815       --  pragma Interface_Name, performs validity checks and sets the
816       --  Interface_Name field of the given subprogram entity to the
817       --  appropriate external or link name, depending on the arguments given.
818       --  Ext_Arg is always present, but Link_Arg may be missing. Note that
819       --  Ext_Arg may represent the Link_Name if Link_Arg is missing, and
820       --  appropriate named notation is used for Ext_Arg. If neither Ext_Arg
821       --  nor Link_Arg is present, the interface name is set to the default
822       --  from the subprogram name.
823
824       procedure Process_Interrupt_Or_Attach_Handler;
825       --  Common processing for Interrupt and Attach_Handler pragmas
826
827       procedure Process_Restrictions_Or_Restriction_Warnings (Warn : Boolean);
828       --  Common processing for Restrictions and Restriction_Warnings pragmas.
829       --  Warn is True for Restriction_Warnings, or for Restrictions if the
830       --  flag Treat_Restrictions_As_Warnings is set, and False if this flag
831       --  is not set in the Restrictions case.
832
833       procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean);
834       --  Common processing for Suppress and Unsuppress. The boolean parameter
835       --  Suppress_Case is True for the Suppress case, and False for the
836       --  Unsuppress case.
837
838       procedure Set_Exported (E : Entity_Id; Arg : Node_Id);
839       --  This procedure sets the Is_Exported flag for the given entity,
840       --  checking that the entity was not previously imported. Arg is
841       --  the argument that specified the entity. A check is also made
842       --  for exporting inappropriate entities.
843
844       procedure Set_Extended_Import_Export_External_Name
845         (Internal_Ent : Entity_Id;
846          Arg_External : Node_Id);
847       --  Common processing for all extended import export pragmas. The first
848       --  argument, Internal_Ent, is the internal entity, which has already
849       --  been checked for validity by the caller. Arg_External is from the
850       --  Import or Export pragma, and may be null if no External parameter
851       --  was present. If Arg_External is present and is a non-null string
852       --  (a null string is treated as the default), then the Interface_Name
853       --  field of Internal_Ent is set appropriately.
854
855       procedure Set_Imported (E : Entity_Id);
856       --  This procedure sets the Is_Imported flag for the given entity,
857       --  checking that it is not previously exported or imported.
858
859       procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id);
860       --  Mech is a parameter passing mechanism (see Import_Function syntax
861       --  for MECHANISM_NAME). This routine checks that the mechanism argument
862       --  has the right form, and if not issues an error message. If the
863       --  argument has the right form then the Mechanism field of Ent is
864       --  set appropriately.
865
866       procedure Set_Ravenscar_Profile (N : Node_Id);
867       --  Activate the set of configuration pragmas and restrictions that make
868       --  up the Ravenscar Profile. N is the corresponding pragma node, which
869       --  is used for error messages on any constructs that violate the
870       --  profile.
871
872       ---------------------
873       -- Ada_2005_Pragma --
874       ---------------------
875
876       procedure Ada_2005_Pragma is
877       begin
878          if Ada_Version <= Ada_95 then
879             Check_Restriction (No_Implementation_Pragmas, N);
880          end if;
881       end Ada_2005_Pragma;
882
883       ---------------------
884       -- Ada_2012_Pragma --
885       ---------------------
886
887       procedure Ada_2012_Pragma is
888       begin
889          if Ada_Version <= Ada_2005 then
890             Check_Restriction (No_Implementation_Pragmas, N);
891          end if;
892       end Ada_2012_Pragma;
893
894       --------------------------
895       -- Check_Ada_83_Warning --
896       --------------------------
897
898       procedure Check_Ada_83_Warning is
899       begin
900          if Ada_Version = Ada_83 and then Comes_From_Source (N) then
901             Error_Msg_N ("(Ada 83) pragma& is non-standard?", N);
902          end if;
903       end Check_Ada_83_Warning;
904
905       ---------------------
906       -- Check_Arg_Count --
907       ---------------------
908
909       procedure Check_Arg_Count (Required : Nat) is
910       begin
911          if Arg_Count /= Required then
912             Error_Pragma ("wrong number of arguments for pragma%");
913          end if;
914       end Check_Arg_Count;
915
916       --------------------------------
917       -- Check_Arg_Is_External_Name --
918       --------------------------------
919
920       procedure Check_Arg_Is_External_Name (Arg : Node_Id) is
921          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
922
923       begin
924          if Nkind (Argx) = N_Identifier then
925             return;
926
927          else
928             Analyze_And_Resolve (Argx, Standard_String);
929
930             if Is_OK_Static_Expression (Argx) then
931                return;
932
933             elsif Etype (Argx) = Any_Type then
934                raise Pragma_Exit;
935
936             --  An interesting special case, if we have a string literal and
937             --  we are in Ada 83 mode, then we allow it even though it will
938             --  not be flagged as static. This allows expected Ada 83 mode
939             --  use of external names which are string literals, even though
940             --  technically these are not static in Ada 83.
941
942             elsif Ada_Version = Ada_83
943               and then Nkind (Argx) = N_String_Literal
944             then
945                return;
946
947             --  Static expression that raises Constraint_Error. This has
948             --  already been flagged, so just exit from pragma processing.
949
950             elsif Is_Static_Expression (Argx) then
951                raise Pragma_Exit;
952
953             --  Here we have a real error (non-static expression)
954
955             else
956                Error_Msg_Name_1 := Pname;
957
958                declare
959                   Msg : String :=
960                           "argument for pragma% must be a identifier or "
961                           & "static string expression!";
962                begin
963                   Fix_Error (Msg);
964                   Flag_Non_Static_Expr (Msg, Argx);
965                   raise Pragma_Exit;
966                end;
967             end if;
968          end if;
969       end Check_Arg_Is_External_Name;
970
971       -----------------------------
972       -- Check_Arg_Is_Identifier --
973       -----------------------------
974
975       procedure Check_Arg_Is_Identifier (Arg : Node_Id) is
976          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
977       begin
978          if Nkind (Argx) /= N_Identifier then
979             Error_Pragma_Arg
980               ("argument for pragma% must be identifier", Argx);
981          end if;
982       end Check_Arg_Is_Identifier;
983
984       ----------------------------------
985       -- Check_Arg_Is_Integer_Literal --
986       ----------------------------------
987
988       procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id) is
989          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
990       begin
991          if Nkind (Argx) /= N_Integer_Literal then
992             Error_Pragma_Arg
993               ("argument for pragma% must be integer literal", Argx);
994          end if;
995       end Check_Arg_Is_Integer_Literal;
996
997       -------------------------------------------
998       -- Check_Arg_Is_Library_Level_Local_Name --
999       -------------------------------------------
1000
1001       --  LOCAL_NAME ::=
1002       --    DIRECT_NAME
1003       --  | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
1004       --  | library_unit_NAME
1005
1006       procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id) is
1007       begin
1008          Check_Arg_Is_Local_Name (Arg);
1009
1010          if not Is_Library_Level_Entity (Entity (Get_Pragma_Arg (Arg)))
1011            and then Comes_From_Source (N)
1012          then
1013             Error_Pragma_Arg
1014               ("argument for pragma% must be library level entity", Arg);
1015          end if;
1016       end Check_Arg_Is_Library_Level_Local_Name;
1017
1018       -----------------------------
1019       -- Check_Arg_Is_Local_Name --
1020       -----------------------------
1021
1022       --  LOCAL_NAME ::=
1023       --    DIRECT_NAME
1024       --  | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
1025       --  | library_unit_NAME
1026
1027       procedure Check_Arg_Is_Local_Name (Arg : Node_Id) is
1028          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1029
1030       begin
1031          Analyze (Argx);
1032
1033          if Nkind (Argx) not in N_Direct_Name
1034            and then (Nkind (Argx) /= N_Attribute_Reference
1035                       or else Present (Expressions (Argx))
1036                       or else Nkind (Prefix (Argx)) /= N_Identifier)
1037            and then (not Is_Entity_Name (Argx)
1038                       or else not Is_Compilation_Unit (Entity (Argx)))
1039          then
1040             Error_Pragma_Arg ("argument for pragma% must be local name", Argx);
1041          end if;
1042
1043          --  No further check required if not an entity name
1044
1045          if not Is_Entity_Name (Argx) then
1046             null;
1047
1048          else
1049             declare
1050                OK   : Boolean;
1051                Ent  : constant Entity_Id := Entity (Argx);
1052                Scop : constant Entity_Id := Scope (Ent);
1053             begin
1054                --  Case of a pragma applied to a compilation unit: pragma must
1055                --  occur immediately after the program unit in the compilation.
1056
1057                if Is_Compilation_Unit (Ent) then
1058                   declare
1059                      Decl : constant Node_Id := Unit_Declaration_Node (Ent);
1060
1061                   begin
1062                      --  Case of pragma placed immediately after spec
1063
1064                      if Parent (N) = Aux_Decls_Node (Parent (Decl)) then
1065                         OK := True;
1066
1067                      --  Case of pragma placed immediately after body
1068
1069                      elsif Nkind (Decl) = N_Subprogram_Declaration
1070                              and then Present (Corresponding_Body (Decl))
1071                      then
1072                         OK := Parent (N) =
1073                                 Aux_Decls_Node
1074                                   (Parent (Unit_Declaration_Node
1075                                              (Corresponding_Body (Decl))));
1076
1077                      --  All other cases are illegal
1078
1079                      else
1080                         OK := False;
1081                      end if;
1082                   end;
1083
1084                --  Special restricted placement rule from 10.2.1(11.8/2)
1085
1086                elsif Is_Generic_Formal (Ent)
1087                        and then Prag_Id = Pragma_Preelaborable_Initialization
1088                then
1089                   OK := List_Containing (N) =
1090                           Generic_Formal_Declarations
1091                             (Unit_Declaration_Node (Scop));
1092
1093                --  Default case, just check that the pragma occurs in the scope
1094                --  of the entity denoted by the name.
1095
1096                else
1097                   OK := Current_Scope = Scop;
1098                end if;
1099
1100                if not OK then
1101                   Error_Pragma_Arg
1102                     ("pragma% argument must be in same declarative part", Arg);
1103                end if;
1104             end;
1105          end if;
1106       end Check_Arg_Is_Local_Name;
1107
1108       ---------------------------------
1109       -- Check_Arg_Is_Locking_Policy --
1110       ---------------------------------
1111
1112       procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id) is
1113          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1114
1115       begin
1116          Check_Arg_Is_Identifier (Argx);
1117
1118          if not Is_Locking_Policy_Name (Chars (Argx)) then
1119             Error_Pragma_Arg ("& is not a valid locking policy name", Argx);
1120          end if;
1121       end Check_Arg_Is_Locking_Policy;
1122
1123       -------------------------
1124       -- Check_Arg_Is_One_Of --
1125       -------------------------
1126
1127       procedure Check_Arg_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
1128          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1129
1130       begin
1131          Check_Arg_Is_Identifier (Argx);
1132
1133          if Chars (Argx) /= N1 and then Chars (Argx) /= N2 then
1134             Error_Msg_Name_2 := N1;
1135             Error_Msg_Name_3 := N2;
1136             Error_Pragma_Arg ("argument for pragma% must be% or%", Argx);
1137          end if;
1138       end Check_Arg_Is_One_Of;
1139
1140       procedure Check_Arg_Is_One_Of
1141         (Arg        : Node_Id;
1142          N1, N2, N3 : Name_Id)
1143       is
1144          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1145
1146       begin
1147          Check_Arg_Is_Identifier (Argx);
1148
1149          if Chars (Argx) /= N1
1150            and then Chars (Argx) /= N2
1151            and then Chars (Argx) /= N3
1152          then
1153             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1154          end if;
1155       end Check_Arg_Is_One_Of;
1156
1157       procedure Check_Arg_Is_One_Of
1158         (Arg                : Node_Id;
1159          N1, N2, N3, N4, N5 : Name_Id)
1160       is
1161          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1162
1163       begin
1164          Check_Arg_Is_Identifier (Argx);
1165
1166          if Chars (Argx) /= N1
1167            and then Chars (Argx) /= N2
1168            and then Chars (Argx) /= N3
1169            and then Chars (Argx) /= N4
1170            and then Chars (Argx) /= N5
1171          then
1172             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1173          end if;
1174       end Check_Arg_Is_One_Of;
1175       ---------------------------------
1176       -- Check_Arg_Is_Queuing_Policy --
1177       ---------------------------------
1178
1179       procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id) is
1180          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1181
1182       begin
1183          Check_Arg_Is_Identifier (Argx);
1184
1185          if not Is_Queuing_Policy_Name (Chars (Argx)) then
1186             Error_Pragma_Arg ("& is not a valid queuing policy name", Argx);
1187          end if;
1188       end Check_Arg_Is_Queuing_Policy;
1189
1190       ------------------------------------
1191       -- Check_Arg_Is_Static_Expression --
1192       ------------------------------------
1193
1194       procedure Check_Arg_Is_Static_Expression
1195         (Arg : Node_Id;
1196          Typ : Entity_Id := Empty)
1197       is
1198          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1199
1200       begin
1201          if Present (Typ) then
1202             Analyze_And_Resolve (Argx, Typ);
1203          else
1204             Analyze_And_Resolve (Argx);
1205          end if;
1206
1207          if Is_OK_Static_Expression (Argx) then
1208             return;
1209
1210          elsif Etype (Argx) = Any_Type then
1211             raise Pragma_Exit;
1212
1213          --  An interesting special case, if we have a string literal and we
1214          --  are in Ada 83 mode, then we allow it even though it will not be
1215          --  flagged as static. This allows the use of Ada 95 pragmas like
1216          --  Import in Ada 83 mode. They will of course be flagged with
1217          --  warnings as usual, but will not cause errors.
1218
1219          elsif Ada_Version = Ada_83
1220            and then Nkind (Argx) = N_String_Literal
1221          then
1222             return;
1223
1224          --  Static expression that raises Constraint_Error. This has already
1225          --  been flagged, so just exit from pragma processing.
1226
1227          elsif Is_Static_Expression (Argx) then
1228             raise Pragma_Exit;
1229
1230          --  Finally, we have a real error
1231
1232          else
1233             Error_Msg_Name_1 := Pname;
1234
1235             declare
1236                Msg : String :=
1237                        "argument for pragma% must be a static expression!";
1238             begin
1239                Fix_Error (Msg);
1240                Flag_Non_Static_Expr (Msg, Argx);
1241             end;
1242
1243             raise Pragma_Exit;
1244          end if;
1245       end Check_Arg_Is_Static_Expression;
1246
1247       ------------------------------------------
1248       -- Check_Arg_Is_Task_Dispatching_Policy --
1249       ------------------------------------------
1250
1251       procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id) is
1252          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1253
1254       begin
1255          Check_Arg_Is_Identifier (Argx);
1256
1257          if not Is_Task_Dispatching_Policy_Name (Chars (Argx)) then
1258             Error_Pragma_Arg
1259               ("& is not a valid task dispatching policy name", Argx);
1260          end if;
1261       end Check_Arg_Is_Task_Dispatching_Policy;
1262
1263       ---------------------
1264       -- Check_Arg_Order --
1265       ---------------------
1266
1267       procedure Check_Arg_Order (Names : Name_List) is
1268          Arg : Node_Id;
1269
1270          Highest_So_Far : Natural := 0;
1271          --  Highest index in Names seen do far
1272
1273       begin
1274          Arg := Arg1;
1275          for J in 1 .. Arg_Count loop
1276             if Chars (Arg) /= No_Name then
1277                for K in Names'Range loop
1278                   if Chars (Arg) = Names (K) then
1279                      if K < Highest_So_Far then
1280                         Error_Msg_Name_1 := Pname;
1281                         Error_Msg_N
1282                           ("parameters out of order for pragma%", Arg);
1283                         Error_Msg_Name_1 := Names (K);
1284                         Error_Msg_Name_2 := Names (Highest_So_Far);
1285                         Error_Msg_N ("\% must appear before %", Arg);
1286                         raise Pragma_Exit;
1287
1288                      else
1289                         Highest_So_Far := K;
1290                      end if;
1291                   end if;
1292                end loop;
1293             end if;
1294
1295             Arg := Next (Arg);
1296          end loop;
1297       end Check_Arg_Order;
1298
1299       --------------------------------
1300       -- Check_At_Least_N_Arguments --
1301       --------------------------------
1302
1303       procedure Check_At_Least_N_Arguments (N : Nat) is
1304       begin
1305          if Arg_Count < N then
1306             Error_Pragma ("too few arguments for pragma%");
1307          end if;
1308       end Check_At_Least_N_Arguments;
1309
1310       -------------------------------
1311       -- Check_At_Most_N_Arguments --
1312       -------------------------------
1313
1314       procedure Check_At_Most_N_Arguments (N : Nat) is
1315          Arg : Node_Id;
1316       begin
1317          if Arg_Count > N then
1318             Arg := Arg1;
1319             for J in 1 .. N loop
1320                Next (Arg);
1321                Error_Pragma_Arg ("too many arguments for pragma%", Arg);
1322             end loop;
1323          end if;
1324       end Check_At_Most_N_Arguments;
1325
1326       ---------------------
1327       -- Check_Component --
1328       ---------------------
1329
1330       procedure Check_Component
1331         (Comp            : Node_Id;
1332          UU_Typ          : Entity_Id;
1333          In_Variant_Part : Boolean := False)
1334       is
1335          Comp_Id : constant Entity_Id := Defining_Identifier (Comp);
1336          Sindic  : constant Node_Id :=
1337                      Subtype_Indication (Component_Definition (Comp));
1338          Typ     : constant Entity_Id := Etype (Comp_Id);
1339
1340          function Inside_Generic_Body (Id : Entity_Id) return Boolean;
1341          --  Determine whether entity Id appears inside a generic body.
1342          --  Shouldn't this be in a more general place ???
1343
1344          -------------------------
1345          -- Inside_Generic_Body --
1346          -------------------------
1347
1348          function Inside_Generic_Body (Id : Entity_Id) return Boolean is
1349             S : Entity_Id;
1350
1351          begin
1352             S := Id;
1353             while Present (S) and then S /= Standard_Standard loop
1354                if Ekind (S) = E_Generic_Package
1355                  and then In_Package_Body (S)
1356                then
1357                   return True;
1358                end if;
1359
1360                S := Scope (S);
1361             end loop;
1362
1363             return False;
1364          end Inside_Generic_Body;
1365
1366       --  Start of processing for Check_Component
1367
1368       begin
1369          --  Ada 2005 (AI-216): If a component subtype is subject to a per-
1370          --  object constraint, then the component type shall be an Unchecked_
1371          --  Union.
1372
1373          if Nkind (Sindic) = N_Subtype_Indication
1374            and then Has_Per_Object_Constraint (Comp_Id)
1375            and then not Is_Unchecked_Union (Etype (Subtype_Mark (Sindic)))
1376          then
1377             Error_Msg_N
1378               ("component subtype subject to per-object constraint " &
1379                "must be an Unchecked_Union", Comp);
1380
1381          --  Ada 2012 (AI05-0026): For an unchecked union type declared within
1382          --  the body of a generic unit, or within the body of any of its
1383          --  descendant library units, no part of the type of a component
1384          --  declared in a variant_part of the unchecked union type shall be of
1385          --  a formal private type or formal private extension declared within
1386          --  the formal part of the generic unit.
1387
1388          elsif Ada_Version >= Ada_2012
1389            and then Inside_Generic_Body (UU_Typ)
1390            and then In_Variant_Part
1391            and then Is_Private_Type (Typ)
1392            and then Is_Generic_Type (Typ)
1393          then
1394             Error_Msg_N
1395               ("component of Unchecked_Union cannot be of generic type", Comp);
1396
1397          elsif Needs_Finalization (Typ) then
1398             Error_Msg_N
1399               ("component of Unchecked_Union cannot be controlled", Comp);
1400
1401          elsif Has_Task (Typ) then
1402             Error_Msg_N
1403               ("component of Unchecked_Union cannot have tasks", Comp);
1404          end if;
1405       end Check_Component;
1406
1407       ----------------------------
1408       -- Check_Duplicate_Pragma --
1409       ----------------------------
1410
1411       procedure Check_Duplicate_Pragma (E : Entity_Id) is
1412          P : Node_Id;
1413
1414       begin
1415          --  Nothing to do if this pragma comes from an aspect specification,
1416          --  since we could not be duplicating a pragma, and we dealt with the
1417          --  case of duplicated aspects in Analyze_Aspect_Specifications.
1418
1419          if From_Aspect_Specification (N) then
1420             return;
1421          end if;
1422
1423          --  Otherwise current pragma may duplicate previous pragma or a
1424          --  previously given aspect specification for the same pragma.
1425
1426          P := Get_Rep_Item_For_Entity (E, Pragma_Name (N));
1427
1428          if Present (P) then
1429             Error_Msg_Name_1 := Pragma_Name (N);
1430             Error_Msg_Sloc := Sloc (P);
1431
1432             if Nkind (P) = N_Aspect_Specification
1433               or else From_Aspect_Specification (P)
1434             then
1435                Error_Msg_NE ("aspect% for & previously given#", N, E);
1436             else
1437                Error_Msg_NE ("pragma% for & duplicates pragma#", N, E);
1438             end if;
1439
1440             raise Pragma_Exit;
1441          end if;
1442       end Check_Duplicate_Pragma;
1443
1444       ----------------------------------
1445       -- Check_Duplicated_Export_Name --
1446       ----------------------------------
1447
1448       procedure Check_Duplicated_Export_Name (Nam : Node_Id) is
1449          String_Val : constant String_Id := Strval (Nam);
1450
1451       begin
1452          --  We are only interested in the export case, and in the case of
1453          --  generics, it is the instance, not the template, that is the
1454          --  problem (the template will generate a warning in any case).
1455
1456          if not Inside_A_Generic
1457            and then (Prag_Id = Pragma_Export
1458                        or else
1459                      Prag_Id = Pragma_Export_Procedure
1460                        or else
1461                      Prag_Id = Pragma_Export_Valued_Procedure
1462                        or else
1463                      Prag_Id = Pragma_Export_Function)
1464          then
1465             for J in Externals.First .. Externals.Last loop
1466                if String_Equal (String_Val, Strval (Externals.Table (J))) then
1467                   Error_Msg_Sloc := Sloc (Externals.Table (J));
1468                   Error_Msg_N ("external name duplicates name given#", Nam);
1469                   exit;
1470                end if;
1471             end loop;
1472
1473             Externals.Append (Nam);
1474          end if;
1475       end Check_Duplicated_Export_Name;
1476
1477       -------------------------
1478       -- Check_First_Subtype --
1479       -------------------------
1480
1481       procedure Check_First_Subtype (Arg : Node_Id) is
1482          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1483          Ent  : constant Entity_Id := Entity (Argx);
1484
1485       begin
1486          if Is_First_Subtype (Ent) then
1487             null;
1488
1489          elsif Is_Type (Ent) then
1490             Error_Pragma_Arg
1491               ("pragma% cannot apply to subtype", Argx);
1492
1493          elsif Is_Object (Ent) then
1494             Error_Pragma_Arg
1495               ("pragma% cannot apply to object, requires a type", Argx);
1496
1497          else
1498             Error_Pragma_Arg
1499               ("pragma% cannot apply to&, requires a type", Argx);
1500          end if;
1501       end Check_First_Subtype;
1502
1503       ----------------------
1504       -- Check_Identifier --
1505       ----------------------
1506
1507       procedure Check_Identifier (Arg : Node_Id; Id : Name_Id) is
1508       begin
1509          if Present (Arg)
1510            and then Nkind (Arg) = N_Pragma_Argument_Association
1511          then
1512             if Chars (Arg) = No_Name or else Chars (Arg) /= Id then
1513                Error_Msg_Name_1 := Pname;
1514                Error_Msg_Name_2 := Id;
1515                Error_Msg_N ("pragma% argument expects identifier%", Arg);
1516                raise Pragma_Exit;
1517             end if;
1518          end if;
1519       end Check_Identifier;
1520
1521       --------------------------------
1522       -- Check_Identifier_Is_One_Of --
1523       --------------------------------
1524
1525       procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
1526       begin
1527          if Present (Arg)
1528            and then Nkind (Arg) = N_Pragma_Argument_Association
1529          then
1530             if Chars (Arg) = No_Name then
1531                Error_Msg_Name_1 := Pname;
1532                Error_Msg_N ("pragma% argument expects an identifier", Arg);
1533                raise Pragma_Exit;
1534
1535             elsif Chars (Arg) /= N1
1536               and then Chars (Arg) /= N2
1537             then
1538                Error_Msg_Name_1 := Pname;
1539                Error_Msg_N ("invalid identifier for pragma% argument", Arg);
1540                raise Pragma_Exit;
1541             end if;
1542          end if;
1543       end Check_Identifier_Is_One_Of;
1544
1545       ---------------------------
1546       -- Check_In_Main_Program --
1547       ---------------------------
1548
1549       procedure Check_In_Main_Program is
1550          P : constant Node_Id := Parent (N);
1551
1552       begin
1553          --  Must be at in subprogram body
1554
1555          if Nkind (P) /= N_Subprogram_Body then
1556             Error_Pragma ("% pragma allowed only in subprogram");
1557
1558          --  Otherwise warn if obviously not main program
1559
1560          elsif Present (Parameter_Specifications (Specification (P)))
1561            or else not Is_Compilation_Unit (Defining_Entity (P))
1562          then
1563             Error_Msg_Name_1 := Pname;
1564             Error_Msg_N
1565               ("?pragma% is only effective in main program", N);
1566          end if;
1567       end Check_In_Main_Program;
1568
1569       ---------------------------------------
1570       -- Check_Interrupt_Or_Attach_Handler --
1571       ---------------------------------------
1572
1573       procedure Check_Interrupt_Or_Attach_Handler is
1574          Arg1_X : constant Node_Id := Get_Pragma_Arg (Arg1);
1575          Handler_Proc, Proc_Scope : Entity_Id;
1576
1577       begin
1578          Analyze (Arg1_X);
1579
1580          if Prag_Id = Pragma_Interrupt_Handler then
1581             Check_Restriction (No_Dynamic_Attachment, N);
1582          end if;
1583
1584          Handler_Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
1585          Proc_Scope := Scope (Handler_Proc);
1586
1587          --  On AAMP only, a pragma Interrupt_Handler is supported for
1588          --  nonprotected parameterless procedures.
1589
1590          if not AAMP_On_Target
1591            or else Prag_Id = Pragma_Attach_Handler
1592          then
1593             if Ekind (Proc_Scope) /= E_Protected_Type then
1594                Error_Pragma_Arg
1595                  ("argument of pragma% must be protected procedure", Arg1);
1596             end if;
1597
1598             if Parent (N) /= Protected_Definition (Parent (Proc_Scope)) then
1599                Error_Pragma ("pragma% must be in protected definition");
1600             end if;
1601          end if;
1602
1603          if not Is_Library_Level_Entity (Proc_Scope)
1604            or else (AAMP_On_Target
1605                      and then not Is_Library_Level_Entity (Handler_Proc))
1606          then
1607             Error_Pragma_Arg
1608               ("argument for pragma% must be library level entity", Arg1);
1609          end if;
1610
1611          --  AI05-0033: A pragma cannot appear within a generic body, because
1612          --  instance can be in a nested scope. The check that protected type
1613          --  is itself a library-level declaration is done elsewhere.
1614
1615          --  Note: we omit this check in Codepeer mode to properly handle code
1616          --  prior to AI-0033 (pragmas don't matter to codepeer in any case).
1617
1618          if Inside_A_Generic then
1619             if Ekind (Scope (Current_Scope)) = E_Generic_Package
1620               and then In_Package_Body (Scope (Current_Scope))
1621               and then not CodePeer_Mode
1622             then
1623                Error_Pragma ("pragma% cannot be used inside a generic");
1624             end if;
1625          end if;
1626       end Check_Interrupt_Or_Attach_Handler;
1627
1628       -------------------------------------------
1629       -- Check_Is_In_Decl_Part_Or_Package_Spec --
1630       -------------------------------------------
1631
1632       procedure Check_Is_In_Decl_Part_Or_Package_Spec is
1633          P : Node_Id;
1634
1635       begin
1636          P := Parent (N);
1637          loop
1638             if No (P) then
1639                exit;
1640
1641             elsif Nkind (P) = N_Handled_Sequence_Of_Statements then
1642                exit;
1643
1644             elsif Nkind_In (P, N_Package_Specification,
1645                                N_Block_Statement)
1646             then
1647                return;
1648
1649             --  Note: the following tests seem a little peculiar, because
1650             --  they test for bodies, but if we were in the statement part
1651             --  of the body, we would already have hit the handled statement
1652             --  sequence, so the only way we get here is by being in the
1653             --  declarative part of the body.
1654
1655             elsif Nkind_In (P, N_Subprogram_Body,
1656                                N_Package_Body,
1657                                N_Task_Body,
1658                                N_Entry_Body)
1659             then
1660                return;
1661             end if;
1662
1663             P := Parent (P);
1664          end loop;
1665
1666          Error_Pragma ("pragma% is not in declarative part or package spec");
1667       end Check_Is_In_Decl_Part_Or_Package_Spec;
1668
1669       -------------------------
1670       -- Check_No_Identifier --
1671       -------------------------
1672
1673       procedure Check_No_Identifier (Arg : Node_Id) is
1674       begin
1675          if Nkind (Arg) = N_Pragma_Argument_Association
1676            and then Chars (Arg) /= No_Name
1677          then
1678             Error_Pragma_Arg_Ident
1679               ("pragma% does not permit identifier& here", Arg);
1680          end if;
1681       end Check_No_Identifier;
1682
1683       --------------------------
1684       -- Check_No_Identifiers --
1685       --------------------------
1686
1687       procedure Check_No_Identifiers is
1688          Arg_Node : Node_Id;
1689       begin
1690          if Arg_Count > 0 then
1691             Arg_Node := Arg1;
1692             while Present (Arg_Node) loop
1693                Check_No_Identifier (Arg_Node);
1694                Next (Arg_Node);
1695             end loop;
1696          end if;
1697       end Check_No_Identifiers;
1698
1699       ------------------------
1700       -- Check_No_Link_Name --
1701       ------------------------
1702
1703       procedure Check_No_Link_Name is
1704       begin
1705          if Present (Arg3)
1706            and then Chars (Arg3) = Name_Link_Name
1707          then
1708             Arg4 := Arg3;
1709          end if;
1710
1711          if Present (Arg4) then
1712             Error_Pragma_Arg
1713               ("Link_Name argument not allowed for Import Intrinsic", Arg4);
1714          end if;
1715       end Check_No_Link_Name;
1716
1717       -------------------------------
1718       -- Check_Optional_Identifier --
1719       -------------------------------
1720
1721       procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id) is
1722       begin
1723          if Present (Arg)
1724            and then Nkind (Arg) = N_Pragma_Argument_Association
1725            and then Chars (Arg) /= No_Name
1726          then
1727             if Chars (Arg) /= Id then
1728                Error_Msg_Name_1 := Pname;
1729                Error_Msg_Name_2 := Id;
1730                Error_Msg_N ("pragma% argument expects identifier%", Arg);
1731                raise Pragma_Exit;
1732             end if;
1733          end if;
1734       end Check_Optional_Identifier;
1735
1736       procedure Check_Optional_Identifier (Arg : Node_Id; Id : String) is
1737       begin
1738          Name_Buffer (1 .. Id'Length) := Id;
1739          Name_Len := Id'Length;
1740          Check_Optional_Identifier (Arg, Name_Find);
1741       end Check_Optional_Identifier;
1742
1743       --------------------------------------
1744       -- Check_Precondition_Postcondition --
1745       --------------------------------------
1746
1747       procedure Check_Precondition_Postcondition (In_Body : out Boolean) is
1748          P  : Node_Id;
1749          PO : Node_Id;
1750
1751          procedure Chain_PPC (PO : Node_Id);
1752          --  If PO is an entry or a [generic] subprogram declaration node, then
1753          --  the precondition/postcondition applies to this subprogram and the
1754          --  processing for the pragma is completed. Otherwise the pragma is
1755          --  misplaced.
1756
1757          ---------------
1758          -- Chain_PPC --
1759          ---------------
1760
1761          procedure Chain_PPC (PO : Node_Id) is
1762             S   : Entity_Id;
1763             P   : Node_Id;
1764
1765          begin
1766             if Nkind (PO) = N_Abstract_Subprogram_Declaration then
1767                if not From_Aspect_Specification (N) then
1768                   Error_Pragma
1769                     ("pragma% cannot be applied to abstract subprogram");
1770
1771                elsif Class_Present (N) then
1772                   null;
1773
1774                else
1775                   Error_Pragma
1776                     ("aspect % requires ''Class for abstract subprogram");
1777                end if;
1778
1779             --  AI05-0230: The same restriction applies to null procedures. For
1780             --  compatibility with earlier uses of the Ada pragma, apply this
1781             --  rule only to aspect specifications.
1782
1783             --  The above discrpency needs documentation. Robert is dubious
1784             --  about whether it is a good idea ???
1785
1786             elsif Nkind (PO) = N_Subprogram_Declaration
1787               and then Nkind (Specification (PO)) = N_Procedure_Specification
1788               and then Null_Present (Specification (PO))
1789               and then From_Aspect_Specification (N)
1790               and then not Class_Present (N)
1791             then
1792                Error_Pragma
1793                  ("aspect % requires ''Class for null procedure");
1794
1795             elsif not Nkind_In (PO, N_Subprogram_Declaration,
1796                                     N_Generic_Subprogram_Declaration,
1797                                     N_Entry_Declaration)
1798             then
1799                Pragma_Misplaced;
1800             end if;
1801
1802             --  Here if we have [generic] subprogram or entry declaration
1803
1804             if Nkind (PO) = N_Entry_Declaration then
1805                S := Defining_Entity (PO);
1806             else
1807                S := Defining_Unit_Name (Specification (PO));
1808             end if;
1809
1810             --  Make sure we do not have the case of a precondition pragma when
1811             --  the Pre'Class aspect is present.
1812
1813             --  We do this by looking at pragmas already chained to the entity
1814             --  since the aspect derived pragma will be put on this list first.
1815
1816             if Pragma_Name (N) = Name_Precondition then
1817                if not From_Aspect_Specification (N) then
1818                   P := Spec_PPC_List (Contract (S));
1819                   while Present (P) loop
1820                      if Pragma_Name (P) = Name_Precondition
1821                        and then From_Aspect_Specification (P)
1822                        and then Class_Present (P)
1823                      then
1824                         Error_Msg_Sloc := Sloc (P);
1825                         Error_Pragma
1826                           ("pragma% not allowed, `Pre''Class` aspect given#");
1827                      end if;
1828
1829                      P := Next_Pragma (P);
1830                   end loop;
1831                end if;
1832             end if;
1833
1834             --  Similarly check for Pre with inherited Pre'Class. Note that
1835             --  we cover the aspect case as well here.
1836
1837             if Pragma_Name (N) = Name_Precondition
1838               and then not Class_Present (N)
1839             then
1840                declare
1841                   Inherited : constant Subprogram_List :=
1842                                 Inherited_Subprograms (S);
1843                   P         : Node_Id;
1844
1845                begin
1846                   for J in Inherited'Range loop
1847                      P := Spec_PPC_List (Contract (Inherited (J)));
1848                      while Present (P) loop
1849                         if Pragma_Name (P) = Name_Precondition
1850                           and then Class_Present (P)
1851                         then
1852                            Error_Msg_Sloc := Sloc (P);
1853                            Error_Pragma
1854                              ("pragma% not allowed, `Pre''Class` "
1855                               & "aspect inherited from#");
1856                         end if;
1857
1858                         P := Next_Pragma (P);
1859                      end loop;
1860                   end loop;
1861                end;
1862             end if;
1863
1864             --  Note: we do not analyze the pragma at this point. Instead we
1865             --  delay this analysis until the end of the declarative part in
1866             --  which the pragma appears. This implements the required delay
1867             --  in this analysis, allowing forward references. The analysis
1868             --  happens at the end of Analyze_Declarations.
1869
1870             --  Chain spec PPC pragma to list for subprogram
1871
1872             Set_Next_Pragma (N, Spec_PPC_List (Contract (S)));
1873             Set_Spec_PPC_List (Contract (S), N);
1874
1875             --  Return indicating spec case
1876
1877             In_Body := False;
1878             return;
1879          end Chain_PPC;
1880
1881       --  Start of processing for Check_Precondition_Postcondition
1882
1883       begin
1884          if not Is_List_Member (N) then
1885             Pragma_Misplaced;
1886          end if;
1887
1888          --  Preanalyze message argument if present. Visibility in this
1889          --  argument is established at the point of pragma occurrence.
1890
1891          if Arg_Count = 2 then
1892             Check_Optional_Identifier (Arg2, Name_Message);
1893             Preanalyze_Spec_Expression
1894               (Get_Pragma_Arg (Arg2), Standard_String);
1895          end if;
1896
1897          --  Record if pragma is disabled
1898
1899          if Check_Enabled (Pname) then
1900             Set_SCO_Pragma_Enabled (Loc);
1901          end if;
1902
1903          --  If we are within an inlined body, the legality of the pragma
1904          --  has been checked already.
1905
1906          if In_Inlined_Body then
1907             In_Body := True;
1908             return;
1909          end if;
1910
1911          --  Search prior declarations
1912
1913          P := N;
1914          while Present (Prev (P)) loop
1915             P := Prev (P);
1916
1917             --  If the previous node is a generic subprogram, do not go to to
1918             --  the original node, which is the unanalyzed tree: we need to
1919             --  attach the pre/postconditions to the analyzed version at this
1920             --  point. They get propagated to the original tree when analyzing
1921             --  the corresponding body.
1922
1923             if Nkind (P) not in N_Generic_Declaration then
1924                PO := Original_Node (P);
1925             else
1926                PO := P;
1927             end if;
1928
1929             --  Skip past prior pragma
1930
1931             if Nkind (PO) = N_Pragma then
1932                null;
1933
1934             --  Skip stuff not coming from source
1935
1936             elsif not Comes_From_Source (PO) then
1937
1938                --  The condition may apply to a subprogram instantiation
1939
1940                if Nkind (PO) = N_Subprogram_Declaration
1941                  and then Present (Generic_Parent (Specification (PO)))
1942                then
1943                   Chain_PPC (PO);
1944                   return;
1945
1946                elsif Nkind (PO) = N_Subprogram_Declaration
1947                  and then In_Instance
1948                then
1949                   Chain_PPC (PO);
1950                   return;
1951
1952                --  For all other cases of non source code, do nothing
1953
1954                else
1955                   null;
1956                end if;
1957
1958             --  Only remaining possibility is subprogram declaration
1959
1960             else
1961                Chain_PPC (PO);
1962                return;
1963             end if;
1964          end loop;
1965
1966          --  If we fall through loop, pragma is at start of list, so see if it
1967          --  is at the start of declarations of a subprogram body.
1968
1969          if Nkind (Parent (N)) = N_Subprogram_Body
1970            and then List_Containing (N) = Declarations (Parent (N))
1971          then
1972             if Operating_Mode /= Generate_Code
1973               or else Inside_A_Generic
1974             then
1975                --  Analyze pragma expression for correctness and for ASIS use
1976
1977                Preanalyze_Spec_Expression
1978                  (Get_Pragma_Arg (Arg1), Standard_Boolean);
1979             end if;
1980
1981             In_Body := True;
1982             return;
1983
1984          --  See if it is in the pragmas after a library level subprogram
1985
1986          elsif Nkind (Parent (N)) = N_Compilation_Unit_Aux then
1987
1988             --  In formal verification mode, analyze pragma expression for
1989             --  correctness, as it is not expanded later.
1990
1991             if Alfa_Mode then
1992                Analyze_PPC_In_Decl_Part
1993                  (N, Defining_Entity (Unit (Parent (Parent (N)))));
1994             end if;
1995
1996             Chain_PPC (Unit (Parent (Parent (N))));
1997             return;
1998          end if;
1999
2000          --  If we fall through, pragma was misplaced
2001
2002          Pragma_Misplaced;
2003       end Check_Precondition_Postcondition;
2004
2005       -----------------------------
2006       -- Check_Static_Constraint --
2007       -----------------------------
2008
2009       --  Note: for convenience in writing this procedure, in addition to
2010       --  the officially (i.e. by spec) allowed argument which is always a
2011       --  constraint, it also allows ranges and discriminant associations.
2012       --  Above is not clear ???
2013
2014       procedure Check_Static_Constraint (Constr : Node_Id) is
2015
2016          procedure Require_Static (E : Node_Id);
2017          --  Require given expression to be static expression
2018
2019          --------------------
2020          -- Require_Static --
2021          --------------------
2022
2023          procedure Require_Static (E : Node_Id) is
2024          begin
2025             if not Is_OK_Static_Expression (E) then
2026                Flag_Non_Static_Expr
2027                  ("non-static constraint not allowed in Unchecked_Union!", E);
2028                raise Pragma_Exit;
2029             end if;
2030          end Require_Static;
2031
2032       --  Start of processing for Check_Static_Constraint
2033
2034       begin
2035          case Nkind (Constr) is
2036             when N_Discriminant_Association =>
2037                Require_Static (Expression (Constr));
2038
2039             when N_Range =>
2040                Require_Static (Low_Bound (Constr));
2041                Require_Static (High_Bound (Constr));
2042
2043             when N_Attribute_Reference =>
2044                Require_Static (Type_Low_Bound  (Etype (Prefix (Constr))));
2045                Require_Static (Type_High_Bound (Etype (Prefix (Constr))));
2046
2047             when N_Range_Constraint =>
2048                Check_Static_Constraint (Range_Expression (Constr));
2049
2050             when N_Index_Or_Discriminant_Constraint =>
2051                declare
2052                   IDC : Entity_Id;
2053                begin
2054                   IDC := First (Constraints (Constr));
2055                   while Present (IDC) loop
2056                      Check_Static_Constraint (IDC);
2057                      Next (IDC);
2058                   end loop;
2059                end;
2060
2061             when others =>
2062                null;
2063          end case;
2064       end Check_Static_Constraint;
2065
2066       ---------------------
2067       -- Check_Test_Case --
2068       ---------------------
2069
2070       procedure Check_Test_Case is
2071          P  : Node_Id;
2072          PO : Node_Id;
2073
2074          procedure Chain_TC (PO : Node_Id);
2075          --  If PO is a [generic] subprogram declaration node, then the
2076          --  test-case applies to this subprogram and the processing for the
2077          --  pragma is completed. Otherwise the pragma is misplaced.
2078
2079          --------------
2080          -- Chain_TC --
2081          --------------
2082
2083          procedure Chain_TC (PO : Node_Id) is
2084             S   : Entity_Id;
2085
2086          begin
2087             if Nkind (PO) = N_Abstract_Subprogram_Declaration then
2088                if From_Aspect_Specification (N) then
2089                   Error_Pragma
2090                     ("aspect% cannot be applied to abstract subprogram");
2091                else
2092                   Error_Pragma
2093                     ("pragma% cannot be applied to abstract subprogram");
2094                end if;
2095
2096             elsif Nkind (PO) = N_Entry_Declaration then
2097                if From_Aspect_Specification (N) then
2098                   Error_Pragma ("aspect% cannot be applied to entry");
2099                else
2100                   Error_Pragma ("pragma% cannot be applied to entry");
2101                end if;
2102
2103             elsif not Nkind_In (PO, N_Subprogram_Declaration,
2104                                     N_Generic_Subprogram_Declaration)
2105             then
2106                Pragma_Misplaced;
2107             end if;
2108
2109             --  Here if we have [generic] subprogram declaration
2110
2111             S := Defining_Unit_Name (Specification (PO));
2112
2113             --  Note: we do not analyze the pragma at this point. Instead we
2114             --  delay this analysis until the end of the declarative part in
2115             --  which the pragma appears. This implements the required delay
2116             --  in this analysis, allowing forward references. The analysis
2117             --  happens at the end of Analyze_Declarations.
2118
2119             --  There should not be another test case with the same name
2120             --  associated to this subprogram.
2121
2122             declare
2123                Name : constant String_Id := Get_Name_From_Test_Case_Pragma (N);
2124                TC   : Node_Id;
2125
2126             begin
2127                TC := Spec_TC_List (Contract (S));
2128                while Present (TC) loop
2129
2130                   if String_Equal
2131                     (Name, Get_Name_From_Test_Case_Pragma (TC))
2132                   then
2133                      Error_Msg_Sloc := Sloc (TC);
2134
2135                      if From_Aspect_Specification (N) then
2136                         Error_Pragma ("name for aspect% is already used#");
2137                      else
2138                         Error_Pragma ("name for pragma% is already used#");
2139                      end if;
2140                   end if;
2141
2142                   TC := Next_Pragma (TC);
2143                end loop;
2144             end;
2145
2146             --  Chain spec TC pragma to list for subprogram
2147
2148             Set_Next_Pragma (N, Spec_TC_List (Contract (S)));
2149             Set_Spec_TC_List (Contract (S), N);
2150          end Chain_TC;
2151
2152       --  Start of processing for Check_Test_Case
2153
2154       begin
2155          if not Is_List_Member (N) then
2156             Pragma_Misplaced;
2157          end if;
2158
2159          --  Test cases should only appear in package spec unit
2160
2161          if Get_Source_Unit (N) = No_Unit
2162            or else not Nkind_In (Sinfo.Unit (Cunit (Get_Source_Unit (N))),
2163                                  N_Package_Declaration,
2164                                  N_Generic_Package_Declaration)
2165          then
2166             Pragma_Misplaced;
2167          end if;
2168
2169          --  Search prior declarations
2170
2171          P := N;
2172          while Present (Prev (P)) loop
2173             P := Prev (P);
2174
2175             --  If the previous node is a generic subprogram, do not go to to
2176             --  the original node, which is the unanalyzed tree: we need to
2177             --  attach the test-case to the analyzed version at this point.
2178             --  They get propagated to the original tree when analyzing the
2179             --  corresponding body.
2180
2181             if Nkind (P) not in N_Generic_Declaration then
2182                PO := Original_Node (P);
2183             else
2184                PO := P;
2185             end if;
2186
2187             --  Skip past prior pragma
2188
2189             if Nkind (PO) = N_Pragma then
2190                null;
2191
2192             --  Skip stuff not coming from source
2193
2194             elsif not Comes_From_Source (PO) then
2195                null;
2196
2197             --  Only remaining possibility is subprogram declaration. First
2198             --  check that it is declared directly in a package declaration.
2199             --  This may be either the package declaration for the current unit
2200             --  being defined or a local package declaration.
2201
2202             elsif not Present (Parent (Parent (PO)))
2203               or else not Present (Parent (Parent (Parent (PO))))
2204               or else not Nkind_In (Parent (Parent (PO)),
2205                                     N_Package_Declaration,
2206                                     N_Generic_Package_Declaration)
2207             then
2208                Pragma_Misplaced;
2209
2210             else
2211                Chain_TC (PO);
2212                return;
2213             end if;
2214          end loop;
2215
2216          --  If we fall through, pragma was misplaced
2217
2218          Pragma_Misplaced;
2219       end Check_Test_Case;
2220
2221       --------------------------------------
2222       -- Check_Valid_Configuration_Pragma --
2223       --------------------------------------
2224
2225       --  A configuration pragma must appear in the context clause of a
2226       --  compilation unit, and only other pragmas may precede it. Note that
2227       --  the test also allows use in a configuration pragma file.
2228
2229       procedure Check_Valid_Configuration_Pragma is
2230       begin
2231          if not Is_Configuration_Pragma then
2232             Error_Pragma ("incorrect placement for configuration pragma%");
2233          end if;
2234       end Check_Valid_Configuration_Pragma;
2235
2236       -------------------------------------
2237       -- Check_Valid_Library_Unit_Pragma --
2238       -------------------------------------
2239
2240       procedure Check_Valid_Library_Unit_Pragma is
2241          Plist       : List_Id;
2242          Parent_Node : Node_Id;
2243          Unit_Name   : Entity_Id;
2244          Unit_Kind   : Node_Kind;
2245          Unit_Node   : Node_Id;
2246          Sindex      : Source_File_Index;
2247
2248       begin
2249          if not Is_List_Member (N) then
2250             Pragma_Misplaced;
2251
2252          else
2253             Plist := List_Containing (N);
2254             Parent_Node := Parent (Plist);
2255
2256             if Parent_Node = Empty then
2257                Pragma_Misplaced;
2258
2259             --  Case of pragma appearing after a compilation unit. In this case
2260             --  it must have an argument with the corresponding name and must
2261             --  be part of the following pragmas of its parent.
2262
2263             elsif Nkind (Parent_Node) = N_Compilation_Unit_Aux then
2264                if Plist /= Pragmas_After (Parent_Node) then
2265                   Pragma_Misplaced;
2266
2267                elsif Arg_Count = 0 then
2268                   Error_Pragma
2269                     ("argument required if outside compilation unit");
2270
2271                else
2272                   Check_No_Identifiers;
2273                   Check_Arg_Count (1);
2274                   Unit_Node := Unit (Parent (Parent_Node));
2275                   Unit_Kind := Nkind (Unit_Node);
2276
2277                   Analyze (Get_Pragma_Arg (Arg1));
2278
2279                   if Unit_Kind = N_Generic_Subprogram_Declaration
2280                     or else Unit_Kind = N_Subprogram_Declaration
2281                   then
2282                      Unit_Name := Defining_Entity (Unit_Node);
2283
2284                   elsif Unit_Kind in N_Generic_Instantiation then
2285                      Unit_Name := Defining_Entity (Unit_Node);
2286
2287                   else
2288                      Unit_Name := Cunit_Entity (Current_Sem_Unit);
2289                   end if;
2290
2291                   if Chars (Unit_Name) /=
2292                      Chars (Entity (Get_Pragma_Arg (Arg1)))
2293                   then
2294                      Error_Pragma_Arg
2295                        ("pragma% argument is not current unit name", Arg1);
2296                   end if;
2297
2298                   if Ekind (Unit_Name) = E_Package
2299                     and then Present (Renamed_Entity (Unit_Name))
2300                   then
2301                      Error_Pragma ("pragma% not allowed for renamed package");
2302                   end if;
2303                end if;
2304
2305             --  Pragma appears other than after a compilation unit
2306
2307             else
2308                --  Here we check for the generic instantiation case and also
2309                --  for the case of processing a generic formal package. We
2310                --  detect these cases by noting that the Sloc on the node
2311                --  does not belong to the current compilation unit.
2312
2313                Sindex := Source_Index (Current_Sem_Unit);
2314
2315                if Loc not in Source_First (Sindex) .. Source_Last (Sindex) then
2316                   Rewrite (N, Make_Null_Statement (Loc));
2317                   return;
2318
2319                --  If before first declaration, the pragma applies to the
2320                --  enclosing unit, and the name if present must be this name.
2321
2322                elsif Is_Before_First_Decl (N, Plist) then
2323                   Unit_Node := Unit_Declaration_Node (Current_Scope);
2324                   Unit_Kind := Nkind (Unit_Node);
2325
2326                   if Nkind (Parent (Unit_Node)) /= N_Compilation_Unit then
2327                      Pragma_Misplaced;
2328
2329                   elsif Unit_Kind = N_Subprogram_Body
2330                     and then not Acts_As_Spec (Unit_Node)
2331                   then
2332                      Pragma_Misplaced;
2333
2334                   elsif Nkind (Parent_Node) = N_Package_Body then
2335                      Pragma_Misplaced;
2336
2337                   elsif Nkind (Parent_Node) = N_Package_Specification
2338                     and then Plist = Private_Declarations (Parent_Node)
2339                   then
2340                      Pragma_Misplaced;
2341
2342                   elsif (Nkind (Parent_Node) = N_Generic_Package_Declaration
2343                            or else Nkind (Parent_Node) =
2344                                              N_Generic_Subprogram_Declaration)
2345                     and then Plist = Generic_Formal_Declarations (Parent_Node)
2346                   then
2347                      Pragma_Misplaced;
2348
2349                   elsif Arg_Count > 0 then
2350                      Analyze (Get_Pragma_Arg (Arg1));
2351
2352                      if Entity (Get_Pragma_Arg (Arg1)) /= Current_Scope then
2353                         Error_Pragma_Arg
2354                           ("name in pragma% must be enclosing unit", Arg1);
2355                      end if;
2356
2357                   --  It is legal to have no argument in this context
2358
2359                   else
2360                      return;
2361                   end if;
2362
2363                --  Error if not before first declaration. This is because a
2364                --  library unit pragma argument must be the name of a library
2365                --  unit (RM 10.1.5(7)), but the only names permitted in this
2366                --  context are (RM 10.1.5(6)) names of subprogram declarations,
2367                --  generic subprogram declarations or generic instantiations.
2368
2369                else
2370                   Error_Pragma
2371                     ("pragma% misplaced, must be before first declaration");
2372                end if;
2373             end if;
2374          end if;
2375       end Check_Valid_Library_Unit_Pragma;
2376
2377       -------------------
2378       -- Check_Variant --
2379       -------------------
2380
2381       procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id) is
2382          Clist : constant Node_Id := Component_List (Variant);
2383          Comp  : Node_Id;
2384
2385       begin
2386          if not Is_Non_Empty_List (Component_Items (Clist)) then
2387             Error_Msg_N
2388               ("Unchecked_Union may not have empty component list",
2389                Variant);
2390             return;
2391          end if;
2392
2393          Comp := First (Component_Items (Clist));
2394          while Present (Comp) loop
2395             Check_Component (Comp, UU_Typ, In_Variant_Part => True);
2396             Next (Comp);
2397          end loop;
2398       end Check_Variant;
2399
2400       ------------------
2401       -- Error_Pragma --
2402       ------------------
2403
2404       procedure Error_Pragma (Msg : String) is
2405          MsgF : String := Msg;
2406       begin
2407          Error_Msg_Name_1 := Pname;
2408          Fix_Error (MsgF);
2409          Error_Msg_N (MsgF, N);
2410          raise Pragma_Exit;
2411       end Error_Pragma;
2412
2413       ----------------------
2414       -- Error_Pragma_Arg --
2415       ----------------------
2416
2417       procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id) is
2418          MsgF : String := Msg;
2419       begin
2420          Error_Msg_Name_1 := Pname;
2421          Fix_Error (MsgF);
2422          Error_Msg_N (MsgF, Get_Pragma_Arg (Arg));
2423          raise Pragma_Exit;
2424       end Error_Pragma_Arg;
2425
2426       procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id) is
2427          MsgF : String := Msg1;
2428       begin
2429          Error_Msg_Name_1 := Pname;
2430          Fix_Error (MsgF);
2431          Error_Msg_N (MsgF, Get_Pragma_Arg (Arg));
2432          Error_Pragma_Arg (Msg2, Arg);
2433       end Error_Pragma_Arg;
2434
2435       ----------------------------
2436       -- Error_Pragma_Arg_Ident --
2437       ----------------------------
2438
2439       procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id) is
2440          MsgF : String := Msg;
2441       begin
2442          Error_Msg_Name_1 := Pname;
2443          Fix_Error (MsgF);
2444          Error_Msg_N (MsgF, Arg);
2445          raise Pragma_Exit;
2446       end Error_Pragma_Arg_Ident;
2447
2448       ----------------------
2449       -- Error_Pragma_Ref --
2450       ----------------------
2451
2452       procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id) is
2453          MsgF : String := Msg;
2454       begin
2455          Error_Msg_Name_1 := Pname;
2456          Fix_Error (MsgF);
2457          Error_Msg_Sloc   := Sloc (Ref);
2458          Error_Msg_NE (MsgF, N, Ref);
2459          raise Pragma_Exit;
2460       end Error_Pragma_Ref;
2461
2462       ------------------------
2463       -- Find_Lib_Unit_Name --
2464       ------------------------
2465
2466       function Find_Lib_Unit_Name return Entity_Id is
2467       begin
2468          --  Return inner compilation unit entity, for case of nested
2469          --  categorization pragmas. This happens in generic unit.
2470
2471          if Nkind (Parent (N)) = N_Package_Specification
2472            and then Defining_Entity (Parent (N)) /= Current_Scope
2473          then
2474             return Defining_Entity (Parent (N));
2475          else
2476             return Current_Scope;
2477          end if;
2478       end Find_Lib_Unit_Name;
2479
2480       ----------------------------
2481       -- Find_Program_Unit_Name --
2482       ----------------------------
2483
2484       procedure Find_Program_Unit_Name (Id : Node_Id) is
2485          Unit_Name : Entity_Id;
2486          Unit_Kind : Node_Kind;
2487          P         : constant Node_Id := Parent (N);
2488
2489       begin
2490          if Nkind (P) = N_Compilation_Unit then
2491             Unit_Kind := Nkind (Unit (P));
2492
2493             if Unit_Kind = N_Subprogram_Declaration
2494               or else Unit_Kind = N_Package_Declaration
2495               or else Unit_Kind in N_Generic_Declaration
2496             then
2497                Unit_Name := Defining_Entity (Unit (P));
2498
2499                if Chars (Id) = Chars (Unit_Name) then
2500                   Set_Entity (Id, Unit_Name);
2501                   Set_Etype (Id, Etype (Unit_Name));
2502                else
2503                   Set_Etype (Id, Any_Type);
2504                   Error_Pragma
2505                     ("cannot find program unit referenced by pragma%");
2506                end if;
2507
2508             else
2509                Set_Etype (Id, Any_Type);
2510                Error_Pragma ("pragma% inapplicable to this unit");
2511             end if;
2512
2513          else
2514             Analyze (Id);
2515          end if;
2516       end Find_Program_Unit_Name;
2517
2518       -----------------------------------------
2519       -- Find_Unique_Parameterless_Procedure --
2520       -----------------------------------------
2521
2522       function Find_Unique_Parameterless_Procedure
2523         (Name : Entity_Id;
2524          Arg  : Node_Id) return Entity_Id
2525       is
2526          Proc : Entity_Id := Empty;
2527
2528       begin
2529          --  The body of this procedure needs some comments ???
2530
2531          if not Is_Entity_Name (Name) then
2532             Error_Pragma_Arg
2533               ("argument of pragma% must be entity name", Arg);
2534
2535          elsif not Is_Overloaded (Name) then
2536             Proc := Entity (Name);
2537
2538             if Ekind (Proc) /= E_Procedure
2539               or else Present (First_Formal (Proc))
2540             then
2541                Error_Pragma_Arg
2542                  ("argument of pragma% must be parameterless procedure", Arg);
2543             end if;
2544
2545          else
2546             declare
2547                Found : Boolean := False;
2548                It    : Interp;
2549                Index : Interp_Index;
2550
2551             begin
2552                Get_First_Interp (Name, Index, It);
2553                while Present (It.Nam) loop
2554                   Proc := It.Nam;
2555
2556                   if Ekind (Proc) = E_Procedure
2557                     and then No (First_Formal (Proc))
2558                   then
2559                      if not Found then
2560                         Found := True;
2561                         Set_Entity (Name, Proc);
2562                         Set_Is_Overloaded (Name, False);
2563                      else
2564                         Error_Pragma_Arg
2565                           ("ambiguous handler name for pragma% ", Arg);
2566                      end if;
2567                   end if;
2568
2569                   Get_Next_Interp (Index, It);
2570                end loop;
2571
2572                if not Found then
2573                   Error_Pragma_Arg
2574                     ("argument of pragma% must be parameterless procedure",
2575                      Arg);
2576                else
2577                   Proc := Entity (Name);
2578                end if;
2579             end;
2580          end if;
2581
2582          return Proc;
2583       end Find_Unique_Parameterless_Procedure;
2584
2585       ---------------
2586       -- Fix_Error --
2587       ---------------
2588
2589       procedure Fix_Error (Msg : in out String) is
2590       begin
2591          if From_Aspect_Specification (N) then
2592             for J in Msg'First .. Msg'Last - 5 loop
2593                if Msg (J .. J + 5) = "pragma" then
2594                   Msg (J .. J + 5) := "aspect";
2595                end if;
2596             end loop;
2597
2598             if Error_Msg_Name_1 = Name_Precondition then
2599                Error_Msg_Name_1 := Name_Pre;
2600             elsif Error_Msg_Name_1 = Name_Postcondition then
2601                Error_Msg_Name_1 := Name_Post;
2602             end if;
2603          end if;
2604       end Fix_Error;
2605
2606       -------------------------
2607       -- Gather_Associations --
2608       -------------------------
2609
2610       procedure Gather_Associations
2611         (Names : Name_List;
2612          Args  : out Args_List)
2613       is
2614          Arg : Node_Id;
2615
2616       begin
2617          --  Initialize all parameters to Empty
2618
2619          for J in Args'Range loop
2620             Args (J) := Empty;
2621          end loop;
2622
2623          --  That's all we have to do if there are no argument associations
2624
2625          if No (Pragma_Argument_Associations (N)) then
2626             return;
2627          end if;
2628
2629          --  Otherwise first deal with any positional parameters present
2630
2631          Arg := First (Pragma_Argument_Associations (N));
2632          for Index in Args'Range loop
2633             exit when No (Arg) or else Chars (Arg) /= No_Name;
2634             Args (Index) := Get_Pragma_Arg (Arg);
2635             Next (Arg);
2636          end loop;
2637
2638          --  Positional parameters all processed, if any left, then we
2639          --  have too many positional parameters.
2640
2641          if Present (Arg) and then Chars (Arg) = No_Name then
2642             Error_Pragma_Arg
2643               ("too many positional associations for pragma%", Arg);
2644          end if;
2645
2646          --  Process named parameters if any are present
2647
2648          while Present (Arg) loop
2649             if Chars (Arg) = No_Name then
2650                Error_Pragma_Arg
2651                  ("positional association cannot follow named association",
2652                   Arg);
2653
2654             else
2655                for Index in Names'Range loop
2656                   if Names (Index) = Chars (Arg) then
2657                      if Present (Args (Index)) then
2658                         Error_Pragma_Arg
2659                           ("duplicate argument association for pragma%", Arg);
2660                      else
2661                         Args (Index) := Get_Pragma_Arg (Arg);
2662                         exit;
2663                      end if;
2664                   end if;
2665
2666                   if Index = Names'Last then
2667                      Error_Msg_Name_1 := Pname;
2668                      Error_Msg_N ("pragma% does not allow & argument", Arg);
2669
2670                      --  Check for possible misspelling
2671
2672                      for Index1 in Names'Range loop
2673                         if Is_Bad_Spelling_Of
2674                              (Chars (Arg), Names (Index1))
2675                         then
2676                            Error_Msg_Name_1 := Names (Index1);
2677                            Error_Msg_N -- CODEFIX
2678                              ("\possible misspelling of%", Arg);
2679                            exit;
2680                         end if;
2681                      end loop;
2682
2683                      raise Pragma_Exit;
2684                   end if;
2685                end loop;
2686             end if;
2687
2688             Next (Arg);
2689          end loop;
2690       end Gather_Associations;
2691
2692       -----------------
2693       -- GNAT_Pragma --
2694       -----------------
2695
2696       procedure GNAT_Pragma is
2697       begin
2698          Check_Restriction (No_Implementation_Pragmas, N);
2699       end GNAT_Pragma;
2700
2701       --------------------------
2702       -- Is_Before_First_Decl --
2703       --------------------------
2704
2705       function Is_Before_First_Decl
2706         (Pragma_Node : Node_Id;
2707          Decls       : List_Id) return Boolean
2708       is
2709          Item : Node_Id := First (Decls);
2710
2711       begin
2712          --  Only other pragmas can come before this pragma
2713
2714          loop
2715             if No (Item) or else Nkind (Item) /= N_Pragma then
2716                return False;
2717
2718             elsif Item = Pragma_Node then
2719                return True;
2720             end if;
2721
2722             Next (Item);
2723          end loop;
2724       end Is_Before_First_Decl;
2725
2726       -----------------------------
2727       -- Is_Configuration_Pragma --
2728       -----------------------------
2729
2730       --  A configuration pragma must appear in the context clause of a
2731       --  compilation unit, and only other pragmas may precede it. Note that
2732       --  the test below also permits use in a configuration pragma file.
2733
2734       function Is_Configuration_Pragma return Boolean is
2735          Lis : constant List_Id := List_Containing (N);
2736          Par : constant Node_Id := Parent (N);
2737          Prg : Node_Id;
2738
2739       begin
2740          --  If no parent, then we are in the configuration pragma file,
2741          --  so the placement is definitely appropriate.
2742
2743          if No (Par) then
2744             return True;
2745
2746          --  Otherwise we must be in the context clause of a compilation unit
2747          --  and the only thing allowed before us in the context list is more
2748          --  configuration pragmas.
2749
2750          elsif Nkind (Par) = N_Compilation_Unit
2751            and then Context_Items (Par) = Lis
2752          then
2753             Prg := First (Lis);
2754
2755             loop
2756                if Prg = N then
2757                   return True;
2758                elsif Nkind (Prg) /= N_Pragma then
2759                   return False;
2760                end if;
2761
2762                Next (Prg);
2763             end loop;
2764
2765          else
2766             return False;
2767          end if;
2768       end Is_Configuration_Pragma;
2769
2770       --------------------------
2771       -- Is_In_Context_Clause --
2772       --------------------------
2773
2774       function Is_In_Context_Clause return Boolean is
2775          Plist       : List_Id;
2776          Parent_Node : Node_Id;
2777
2778       begin
2779          if not Is_List_Member (N) then
2780             return False;
2781
2782          else
2783             Plist := List_Containing (N);
2784             Parent_Node := Parent (Plist);
2785
2786             if Parent_Node = Empty
2787               or else Nkind (Parent_Node) /= N_Compilation_Unit
2788               or else Context_Items (Parent_Node) /= Plist
2789             then
2790                return False;
2791             end if;
2792          end if;
2793
2794          return True;
2795       end Is_In_Context_Clause;
2796
2797       ---------------------------------
2798       -- Is_Static_String_Expression --
2799       ---------------------------------
2800
2801       function Is_Static_String_Expression (Arg : Node_Id) return Boolean is
2802          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
2803
2804       begin
2805          Analyze_And_Resolve (Argx);
2806          return Is_OK_Static_Expression (Argx)
2807            and then Nkind (Argx) = N_String_Literal;
2808       end Is_Static_String_Expression;
2809
2810       ----------------------
2811       -- Pragma_Misplaced --
2812       ----------------------
2813
2814       procedure Pragma_Misplaced is
2815       begin
2816          Error_Pragma ("incorrect placement of pragma%");
2817       end Pragma_Misplaced;
2818
2819       ------------------------------------
2820       -- Process Atomic_Shared_Volatile --
2821       ------------------------------------
2822
2823       procedure Process_Atomic_Shared_Volatile is
2824          E_Id : Node_Id;
2825          E    : Entity_Id;
2826          D    : Node_Id;
2827          K    : Node_Kind;
2828          Utyp : Entity_Id;
2829
2830          procedure Set_Atomic (E : Entity_Id);
2831          --  Set given type as atomic, and if no explicit alignment was given,
2832          --  set alignment to unknown, since back end knows what the alignment
2833          --  requirements are for atomic arrays. Note: this step is necessary
2834          --  for derived types.
2835
2836          ----------------
2837          -- Set_Atomic --
2838          ----------------
2839
2840          procedure Set_Atomic (E : Entity_Id) is
2841          begin
2842             Set_Is_Atomic (E);
2843
2844             if not Has_Alignment_Clause (E) then
2845                Set_Alignment (E, Uint_0);
2846             end if;
2847          end Set_Atomic;
2848
2849       --  Start of processing for Process_Atomic_Shared_Volatile
2850
2851       begin
2852          Check_Ada_83_Warning;
2853          Check_No_Identifiers;
2854          Check_Arg_Count (1);
2855          Check_Arg_Is_Local_Name (Arg1);
2856          E_Id := Get_Pragma_Arg (Arg1);
2857
2858          if Etype (E_Id) = Any_Type then
2859             return;
2860          end if;
2861
2862          E := Entity (E_Id);
2863          D := Declaration_Node (E);
2864          K := Nkind (D);
2865
2866          --  Check duplicate before we chain ourselves!
2867
2868          Check_Duplicate_Pragma (E);
2869
2870          --  Now check appropriateness of the entity
2871
2872          if Is_Type (E) then
2873             if Rep_Item_Too_Early (E, N)
2874                  or else
2875                Rep_Item_Too_Late (E, N)
2876             then
2877                return;
2878             else
2879                Check_First_Subtype (Arg1);
2880             end if;
2881
2882             if Prag_Id /= Pragma_Volatile then
2883                Set_Atomic (E);
2884                Set_Atomic (Underlying_Type (E));
2885                Set_Atomic (Base_Type (E));
2886             end if;
2887
2888             --  Attribute belongs on the base type. If the view of the type is
2889             --  currently private, it also belongs on the underlying type.
2890
2891             Set_Is_Volatile (Base_Type (E));
2892             Set_Is_Volatile (Underlying_Type (E));
2893
2894             Set_Treat_As_Volatile (E);
2895             Set_Treat_As_Volatile (Underlying_Type (E));
2896
2897          elsif K = N_Object_Declaration
2898            or else (K = N_Component_Declaration
2899                      and then Original_Record_Component (E) = E)
2900          then
2901             if Rep_Item_Too_Late (E, N) then
2902                return;
2903             end if;
2904
2905             if Prag_Id /= Pragma_Volatile then
2906                Set_Is_Atomic (E);
2907
2908                --  If the object declaration has an explicit initialization, a
2909                --  temporary may have to be created to hold the expression, to
2910                --  ensure that access to the object remain atomic.
2911
2912                if Nkind (Parent (E)) = N_Object_Declaration
2913                  and then Present (Expression (Parent (E)))
2914                then
2915                   Set_Has_Delayed_Freeze (E);
2916                end if;
2917
2918                --  An interesting improvement here. If an object of type X is
2919                --  declared atomic, and the type X is not atomic, that's a
2920                --  pity, since it may not have appropriate alignment etc. We
2921                --  can rescue this in the special case where the object and
2922                --  type are in the same unit by just setting the type as
2923                --  atomic, so that the back end will process it as atomic.
2924
2925                Utyp := Underlying_Type (Etype (E));
2926
2927                if Present (Utyp)
2928                  and then Sloc (E) > No_Location
2929                  and then Sloc (Utyp) > No_Location
2930                  and then
2931                    Get_Source_File_Index (Sloc (E)) =
2932                    Get_Source_File_Index (Sloc (Underlying_Type (Etype (E))))
2933                then
2934                   Set_Is_Atomic (Underlying_Type (Etype (E)));
2935                end if;
2936             end if;
2937
2938             Set_Is_Volatile (E);
2939             Set_Treat_As_Volatile (E);
2940
2941          else
2942             Error_Pragma_Arg
2943               ("inappropriate entity for pragma%", Arg1);
2944          end if;
2945       end Process_Atomic_Shared_Volatile;
2946
2947       -------------------------------------------
2948       -- Process_Compile_Time_Warning_Or_Error --
2949       -------------------------------------------
2950
2951       procedure Process_Compile_Time_Warning_Or_Error is
2952          Arg1x : constant Node_Id := Get_Pragma_Arg (Arg1);
2953
2954       begin
2955          Check_Arg_Count (2);
2956          Check_No_Identifiers;
2957          Check_Arg_Is_Static_Expression (Arg2, Standard_String);
2958          Analyze_And_Resolve (Arg1x, Standard_Boolean);
2959
2960          if Compile_Time_Known_Value (Arg1x) then
2961             if Is_True (Expr_Value (Get_Pragma_Arg (Arg1))) then
2962                declare
2963                   Str   : constant String_Id :=
2964                             Strval (Get_Pragma_Arg (Arg2));
2965                   Len   : constant Int := String_Length (Str);
2966                   Cont  : Boolean;
2967                   Ptr   : Nat;
2968                   CC    : Char_Code;
2969                   C     : Character;
2970                   Cent  : constant Entity_Id :=
2971                             Cunit_Entity (Current_Sem_Unit);
2972
2973                   Force : constant Boolean :=
2974                             Prag_Id = Pragma_Compile_Time_Warning
2975                               and then
2976                                 Is_Spec_Name (Unit_Name (Current_Sem_Unit))
2977                               and then (Ekind (Cent) /= E_Package
2978                                           or else not In_Private_Part (Cent));
2979                   --  Set True if this is the warning case, and we are in the
2980                   --  visible part of a package spec, or in a subprogram spec,
2981                   --  in which case we want to force the client to see the
2982                   --  warning, even though it is not in the main unit.
2983
2984                begin
2985                   --  Loop through segments of message separated by line feeds.
2986                   --  We output these segments as separate messages with
2987                   --  continuation marks for all but the first.
2988
2989                   Cont := False;
2990                   Ptr := 1;
2991                   loop
2992                      Error_Msg_Strlen := 0;
2993
2994                      --  Loop to copy characters from argument to error message
2995                      --  string buffer.
2996
2997                      loop
2998                         exit when Ptr > Len;
2999                         CC := Get_String_Char (Str, Ptr);
3000                         Ptr := Ptr + 1;
3001
3002                         --  Ignore wide chars ??? else store character
3003
3004                         if In_Character_Range (CC) then
3005                            C := Get_Character (CC);
3006                            exit when C = ASCII.LF;
3007                            Error_Msg_Strlen := Error_Msg_Strlen + 1;
3008                            Error_Msg_String (Error_Msg_Strlen) := C;
3009                         end if;
3010                      end loop;
3011
3012                      --  Here with one line ready to go
3013
3014                      Error_Msg_Warn := Prag_Id = Pragma_Compile_Time_Warning;
3015
3016                      --  If this is a warning in a spec, then we want clients
3017                      --  to see the warning, so mark the message with the
3018                      --  special sequence !! to force the warning. In the case
3019                      --  of a package spec, we do not force this if we are in
3020                      --  the private part of the spec.
3021
3022                      if Force then
3023                         if Cont = False then
3024                            Error_Msg_N ("<~!!", Arg1);
3025                            Cont := True;
3026                         else
3027                            Error_Msg_N ("\<~!!", Arg1);
3028                         end if;
3029
3030                      --  Error, rather than warning, or in a body, so we do not
3031                      --  need to force visibility for client (error will be
3032                      --  output in any case, and this is the situation in which
3033                      --  we do not want a client to get a warning, since the
3034                      --  warning is in the body or the spec private part).
3035
3036                      else
3037                         if Cont = False then
3038                            Error_Msg_N ("<~", Arg1);
3039                            Cont := True;
3040                         else
3041                            Error_Msg_N ("\<~", Arg1);
3042                         end if;
3043                      end if;
3044
3045                      exit when Ptr > Len;
3046                   end loop;
3047                end;
3048             end if;
3049          end if;
3050       end Process_Compile_Time_Warning_Or_Error;
3051
3052       ------------------------
3053       -- Process_Convention --
3054       ------------------------
3055
3056       procedure Process_Convention
3057         (C   : out Convention_Id;
3058          Ent : out Entity_Id)
3059       is
3060          Id        : Node_Id;
3061          E         : Entity_Id;
3062          E1        : Entity_Id;
3063          Cname     : Name_Id;
3064          Comp_Unit : Unit_Number_Type;
3065
3066          procedure Diagnose_Multiple_Pragmas (S : Entity_Id);
3067          --  Called if we have more than one Export/Import/Convention pragma.
3068          --  This is generally illegal, but we have a special case of allowing
3069          --  Import and Interface to coexist if they specify the convention in
3070          --  a consistent manner. We are allowed to do this, since Interface is
3071          --  an implementation defined pragma, and we choose to do it since we
3072          --  know Rational allows this combination. S is the entity id of the
3073          --  subprogram in question. This procedure also sets the special flag
3074          --  Import_Interface_Present in both pragmas in the case where we do
3075          --  have matching Import and Interface pragmas.
3076
3077          procedure Set_Convention_From_Pragma (E : Entity_Id);
3078          --  Set convention in entity E, and also flag that the entity has a
3079          --  convention pragma. If entity is for a private or incomplete type,
3080          --  also set convention and flag on underlying type. This procedure
3081          --  also deals with the special case of C_Pass_By_Copy convention.
3082
3083          -------------------------------
3084          -- Diagnose_Multiple_Pragmas --
3085          -------------------------------
3086
3087          procedure Diagnose_Multiple_Pragmas (S : Entity_Id) is
3088             Pdec : constant Node_Id := Declaration_Node (S);
3089             Decl : Node_Id;
3090             Err  : Boolean;
3091
3092             function Same_Convention (Decl : Node_Id) return Boolean;
3093             --  Decl is a pragma node. This function returns True if this
3094             --  pragma has a first argument that is an identifier with a
3095             --  Chars field corresponding to the Convention_Id C.
3096
3097             function Same_Name (Decl : Node_Id) return Boolean;
3098             --  Decl is a pragma node. This function returns True if this
3099             --  pragma has a second argument that is an identifier with a
3100             --  Chars field that matches the Chars of the current subprogram.
3101
3102             ---------------------
3103             -- Same_Convention --
3104             ---------------------
3105
3106             function Same_Convention (Decl : Node_Id) return Boolean is
3107                Arg1 : constant Node_Id :=
3108                         First (Pragma_Argument_Associations (Decl));
3109
3110             begin
3111                if Present (Arg1) then
3112                   declare
3113                      Arg : constant Node_Id := Get_Pragma_Arg (Arg1);
3114                   begin
3115                      if Nkind (Arg) = N_Identifier
3116                        and then Is_Convention_Name (Chars (Arg))
3117                        and then Get_Convention_Id (Chars (Arg)) = C
3118                      then
3119                         return True;
3120                      end if;
3121                   end;
3122                end if;
3123
3124                return False;
3125             end Same_Convention;
3126
3127             ---------------
3128             -- Same_Name --
3129             ---------------
3130
3131             function Same_Name (Decl : Node_Id) return Boolean is
3132                Arg1 : constant Node_Id :=
3133                         First (Pragma_Argument_Associations (Decl));
3134                Arg2 : Node_Id;
3135
3136             begin
3137                if No (Arg1) then
3138                   return False;
3139                end if;
3140
3141                Arg2 := Next (Arg1);
3142
3143                if No (Arg2) then
3144                   return False;
3145                end if;
3146
3147                declare
3148                   Arg : constant Node_Id := Get_Pragma_Arg (Arg2);
3149                begin
3150                   if Nkind (Arg) = N_Identifier
3151                     and then Chars (Arg) = Chars (S)
3152                   then
3153                      return True;
3154                   end if;
3155                end;
3156
3157                return False;
3158             end Same_Name;
3159
3160          --  Start of processing for Diagnose_Multiple_Pragmas
3161
3162          begin
3163             Err := True;
3164
3165             --  Definitely give message if we have Convention/Export here
3166
3167             if Prag_Id = Pragma_Convention or else Prag_Id = Pragma_Export then
3168                null;
3169
3170                --  If we have an Import or Export, scan back from pragma to
3171                --  find any previous pragma applying to the same procedure.
3172                --  The scan will be terminated by the start of the list, or
3173                --  hitting the subprogram declaration. This won't allow one
3174                --  pragma to appear in the public part and one in the private
3175                --  part, but that seems very unlikely in practice.
3176
3177             else
3178                Decl := Prev (N);
3179                while Present (Decl) and then Decl /= Pdec loop
3180
3181                   --  Look for pragma with same name as us
3182
3183                   if Nkind (Decl) = N_Pragma
3184                     and then Same_Name (Decl)
3185                   then
3186                      --  Give error if same as our pragma or Export/Convention
3187
3188                      if Pragma_Name (Decl) = Name_Export
3189                           or else
3190                         Pragma_Name (Decl) = Name_Convention
3191                           or else
3192                         Pragma_Name (Decl) = Pragma_Name (N)
3193                      then
3194                         exit;
3195
3196                      --  Case of Import/Interface or the other way round
3197
3198                      elsif Pragma_Name (Decl) = Name_Interface
3199                              or else
3200                            Pragma_Name (Decl) = Name_Import
3201                      then
3202                         --  Here we know that we have Import and Interface. It
3203                         --  doesn't matter which way round they are. See if
3204                         --  they specify the same convention. If so, all OK,
3205                         --  and set special flags to stop other messages
3206
3207                         if Same_Convention (Decl) then
3208                            Set_Import_Interface_Present (N);
3209                            Set_Import_Interface_Present (Decl);
3210                            Err := False;
3211
3212                         --  If different conventions, special message
3213
3214                         else
3215                            Error_Msg_Sloc := Sloc (Decl);
3216                            Error_Pragma_Arg
3217                              ("convention differs from that given#", Arg1);
3218                            return;
3219                         end if;
3220                      end if;
3221                   end if;
3222
3223                   Next (Decl);
3224                end loop;
3225             end if;
3226
3227             --  Give message if needed if we fall through those tests
3228
3229             if Err then
3230                Error_Pragma_Arg
3231                  ("at most one Convention/Export/Import pragma is allowed",
3232                   Arg2);
3233             end if;
3234          end Diagnose_Multiple_Pragmas;
3235
3236          --------------------------------
3237          -- Set_Convention_From_Pragma --
3238          --------------------------------
3239
3240          procedure Set_Convention_From_Pragma (E : Entity_Id) is
3241          begin
3242             --  Ada 2005 (AI-430): Check invalid attempt to change convention
3243             --  for an overridden dispatching operation. Technically this is
3244             --  an amendment and should only be done in Ada 2005 mode. However,
3245             --  this is clearly a mistake, since the problem that is addressed
3246             --  by this AI is that there is a clear gap in the RM!
3247
3248             if Is_Dispatching_Operation (E)
3249               and then Present (Overridden_Operation (E))
3250               and then C /= Convention (Overridden_Operation (E))
3251             then
3252                Error_Pragma_Arg
3253                  ("cannot change convention for " &
3254                   "overridden dispatching operation",
3255                   Arg1);
3256             end if;
3257
3258             --  Set the convention
3259
3260             Set_Convention (E, C);
3261             Set_Has_Convention_Pragma (E);
3262
3263             if Is_Incomplete_Or_Private_Type (E)
3264               and then Present (Underlying_Type (E))
3265             then
3266                Set_Convention            (Underlying_Type (E), C);
3267                Set_Has_Convention_Pragma (Underlying_Type (E), True);
3268             end if;
3269
3270             --  A class-wide type should inherit the convention of the specific
3271             --  root type (although this isn't specified clearly by the RM).
3272
3273             if Is_Type (E) and then Present (Class_Wide_Type (E)) then
3274                Set_Convention (Class_Wide_Type (E), C);
3275             end if;
3276
3277             --  If the entity is a record type, then check for special case of
3278             --  C_Pass_By_Copy, which is treated the same as C except that the
3279             --  special record flag is set. This convention is only permitted
3280             --  on record types (see AI95-00131).
3281
3282             if Cname = Name_C_Pass_By_Copy then
3283                if Is_Record_Type (E) then
3284                   Set_C_Pass_By_Copy (Base_Type (E));
3285                elsif Is_Incomplete_Or_Private_Type (E)
3286                  and then Is_Record_Type (Underlying_Type (E))
3287                then
3288                   Set_C_Pass_By_Copy (Base_Type (Underlying_Type (E)));
3289                else
3290                   Error_Pragma_Arg
3291                     ("C_Pass_By_Copy convention allowed only for record type",
3292                      Arg2);
3293                end if;
3294             end if;
3295
3296             --  If the entity is a derived boolean type, check for the special
3297             --  case of convention C, C++, or Fortran, where we consider any
3298             --  nonzero value to represent true.
3299
3300             if Is_Discrete_Type (E)
3301               and then Root_Type (Etype (E)) = Standard_Boolean
3302               and then
3303                 (C = Convention_C
3304                    or else
3305                  C = Convention_CPP
3306                    or else
3307                  C = Convention_Fortran)
3308             then
3309                Set_Nonzero_Is_True (Base_Type (E));
3310             end if;
3311          end Set_Convention_From_Pragma;
3312
3313       --  Start of processing for Process_Convention
3314
3315       begin
3316          Check_At_Least_N_Arguments (2);
3317          Check_Optional_Identifier (Arg1, Name_Convention);
3318          Check_Arg_Is_Identifier (Arg1);
3319          Cname := Chars (Get_Pragma_Arg (Arg1));
3320
3321          --  C_Pass_By_Copy is treated as a synonym for convention C (this is
3322          --  tested again below to set the critical flag).
3323
3324          if Cname = Name_C_Pass_By_Copy then
3325             C := Convention_C;
3326
3327          --  Otherwise we must have something in the standard convention list
3328
3329          elsif Is_Convention_Name (Cname) then
3330             C := Get_Convention_Id (Chars (Get_Pragma_Arg (Arg1)));
3331
3332          --  In DEC VMS, it seems that there is an undocumented feature that
3333          --  any unrecognized convention is treated as the default, which for
3334          --  us is convention C. It does not seem so terrible to do this
3335          --  unconditionally, silently in the VMS case, and with a warning
3336          --  in the non-VMS case.
3337
3338          else
3339             if Warn_On_Export_Import and not OpenVMS_On_Target then
3340                Error_Msg_N
3341                  ("?unrecognized convention name, C assumed",
3342                   Get_Pragma_Arg (Arg1));
3343             end if;
3344
3345             C := Convention_C;
3346          end if;
3347
3348          Check_Optional_Identifier (Arg2, Name_Entity);
3349          Check_Arg_Is_Local_Name (Arg2);
3350
3351          Id := Get_Pragma_Arg (Arg2);
3352          Analyze (Id);
3353
3354          if not Is_Entity_Name (Id) then
3355             Error_Pragma_Arg ("entity name required", Arg2);
3356          end if;
3357
3358          E := Entity (Id);
3359
3360          --  Set entity to return
3361
3362          Ent := E;
3363
3364          --  Ada_Pass_By_Copy special checking
3365
3366          if C = Convention_Ada_Pass_By_Copy then
3367             if not Is_First_Subtype (E) then
3368                Error_Pragma_Arg
3369                  ("convention `Ada_Pass_By_Copy` only "
3370                   & "allowed for types", Arg2);
3371             end if;
3372
3373             if Is_By_Reference_Type (E) then
3374                Error_Pragma_Arg
3375                  ("convention `Ada_Pass_By_Copy` not allowed for "
3376                   & "by-reference type", Arg1);
3377             end if;
3378          end if;
3379
3380          --  Ada_Pass_By_Reference special checking
3381
3382          if C = Convention_Ada_Pass_By_Reference then
3383             if not Is_First_Subtype (E) then
3384                Error_Pragma_Arg
3385                  ("convention `Ada_Pass_By_Reference` only "
3386                   & "allowed for types", Arg2);
3387             end if;
3388
3389             if Is_By_Copy_Type (E) then
3390                Error_Pragma_Arg
3391                  ("convention `Ada_Pass_By_Reference` not allowed for "
3392                   & "by-copy type", Arg1);
3393             end if;
3394          end if;
3395
3396          --  Go to renamed subprogram if present, since convention applies to
3397          --  the actual renamed entity, not to the renaming entity. If the
3398          --  subprogram is inherited, go to parent subprogram.
3399
3400          if Is_Subprogram (E)
3401            and then Present (Alias (E))
3402          then
3403             if Nkind (Parent (Declaration_Node (E))) =
3404                                        N_Subprogram_Renaming_Declaration
3405             then
3406                if Scope (E) /= Scope (Alias (E)) then
3407                   Error_Pragma_Ref
3408                     ("cannot apply pragma% to non-local entity&#", E);
3409                end if;
3410
3411                E := Alias (E);
3412
3413             elsif Nkind_In (Parent (E), N_Full_Type_Declaration,
3414                                         N_Private_Extension_Declaration)
3415               and then Scope (E) = Scope (Alias (E))
3416             then
3417                E := Alias (E);
3418
3419                --  Return the parent subprogram the entity was inherited from
3420
3421                Ent := E;
3422             end if;
3423          end if;
3424
3425          --  Check that we are not applying this to a specless body
3426
3427          if Is_Subprogram (E)
3428            and then Nkind (Parent (Declaration_Node (E))) = N_Subprogram_Body
3429          then
3430             Error_Pragma
3431               ("pragma% requires separate spec and must come before body");
3432          end if;
3433
3434          --  Check that we are not applying this to a named constant
3435
3436          if Ekind_In (E, E_Named_Integer, E_Named_Real) then
3437             Error_Msg_Name_1 := Pname;
3438             Error_Msg_N
3439               ("cannot apply pragma% to named constant!",
3440                Get_Pragma_Arg (Arg2));
3441             Error_Pragma_Arg
3442               ("\supply appropriate type for&!", Arg2);
3443          end if;
3444
3445          if Ekind (E) = E_Enumeration_Literal then
3446             Error_Pragma ("enumeration literal not allowed for pragma%");
3447          end if;
3448
3449          --  Check for rep item appearing too early or too late
3450
3451          if Etype (E) = Any_Type
3452            or else Rep_Item_Too_Early (E, N)
3453          then
3454             raise Pragma_Exit;
3455
3456          elsif Present (Underlying_Type (E)) then
3457             E := Underlying_Type (E);
3458          end if;
3459
3460          if Rep_Item_Too_Late (E, N) then
3461             raise Pragma_Exit;
3462          end if;
3463
3464          if Has_Convention_Pragma (E) then
3465             Diagnose_Multiple_Pragmas (E);
3466
3467          elsif Convention (E) = Convention_Protected
3468            or else Ekind (Scope (E)) = E_Protected_Type
3469          then
3470             Error_Pragma_Arg
3471               ("a protected operation cannot be given a different convention",
3472                 Arg2);
3473          end if;
3474
3475          --  For Intrinsic, a subprogram is required
3476
3477          if C = Convention_Intrinsic
3478            and then not Is_Subprogram (E)
3479            and then not Is_Generic_Subprogram (E)
3480          then
3481             Error_Pragma_Arg
3482               ("second argument of pragma% must be a subprogram", Arg2);
3483          end if;
3484
3485          --  For Stdcall, a subprogram, variable or subprogram type is required
3486
3487          if C = Convention_Stdcall
3488            and then not Is_Subprogram (E)
3489            and then not Is_Generic_Subprogram (E)
3490            and then Ekind (E) /= E_Variable
3491            and then not
3492              (Is_Access_Type (E)
3493                and then Ekind (Designated_Type (E)) = E_Subprogram_Type)
3494          then
3495             Error_Pragma_Arg
3496               ("second argument of pragma% must be subprogram (type)",
3497                Arg2);
3498          end if;
3499
3500          if not Is_Subprogram (E)
3501            and then not Is_Generic_Subprogram (E)
3502          then
3503             Set_Convention_From_Pragma (E);
3504
3505             if Is_Type (E) then
3506                Check_First_Subtype (Arg2);
3507                Set_Convention_From_Pragma (Base_Type (E));
3508
3509                --  For subprograms, we must set the convention on the
3510                --  internally generated directly designated type as well.
3511
3512                if Ekind (E) = E_Access_Subprogram_Type then
3513                   Set_Convention_From_Pragma (Directly_Designated_Type (E));
3514                end if;
3515             end if;
3516
3517          --  For the subprogram case, set proper convention for all homonyms
3518          --  in same scope and the same declarative part, i.e. the same
3519          --  compilation unit.
3520
3521          else
3522             Comp_Unit := Get_Source_Unit (E);
3523             Set_Convention_From_Pragma (E);
3524
3525             --  Treat a pragma Import as an implicit body, for GPS use
3526
3527             if Prag_Id = Pragma_Import then
3528                Generate_Reference (E, Id, 'b');
3529             end if;
3530
3531             --  Loop through the homonyms of the pragma argument's entity
3532
3533             E1 := Ent;
3534             loop
3535                E1 := Homonym (E1);
3536                exit when No (E1) or else Scope (E1) /= Current_Scope;
3537
3538                --  Do not set the pragma on inherited operations or on formal
3539                --  subprograms.
3540
3541                if Comes_From_Source (E1)
3542                  and then Comp_Unit = Get_Source_Unit (E1)
3543                  and then not Is_Formal_Subprogram (E1)
3544                  and then Nkind (Original_Node (Parent (E1))) /=
3545                                                     N_Full_Type_Declaration
3546                then
3547                   if Present (Alias (E1))
3548                     and then Scope (E1) /= Scope (Alias (E1))
3549                   then
3550                      Error_Pragma_Ref
3551                        ("cannot apply pragma% to non-local entity& declared#",
3552                         E1);
3553                   end if;
3554
3555                   Set_Convention_From_Pragma (E1);
3556
3557                   if Prag_Id = Pragma_Import then
3558                      Generate_Reference (E1, Id, 'b');
3559                   end if;
3560                end if;
3561
3562                --  For aspect case, do NOT apply to homonyms
3563
3564                exit when From_Aspect_Specification (N);
3565             end loop;
3566          end if;
3567       end Process_Convention;
3568
3569       -----------------------------------------------------
3570       -- Process_Extended_Import_Export_Exception_Pragma --
3571       -----------------------------------------------------
3572
3573       procedure Process_Extended_Import_Export_Exception_Pragma
3574         (Arg_Internal : Node_Id;
3575          Arg_External : Node_Id;
3576          Arg_Form     : Node_Id;
3577          Arg_Code     : Node_Id)
3578       is
3579          Def_Id   : Entity_Id;
3580          Code_Val : Uint;
3581
3582       begin
3583          if not OpenVMS_On_Target then
3584             Error_Pragma
3585               ("?pragma% ignored (applies only to Open'V'M'S)");
3586          end if;
3587
3588          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3589          Def_Id := Entity (Arg_Internal);
3590
3591          if Ekind (Def_Id) /= E_Exception then
3592             Error_Pragma_Arg
3593               ("pragma% must refer to declared exception", Arg_Internal);
3594          end if;
3595
3596          Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
3597
3598          if Present (Arg_Form) then
3599             Check_Arg_Is_One_Of (Arg_Form, Name_Ada, Name_VMS);
3600          end if;
3601
3602          if Present (Arg_Form)
3603            and then Chars (Arg_Form) = Name_Ada
3604          then
3605             null;
3606          else
3607             Set_Is_VMS_Exception (Def_Id);
3608             Set_Exception_Code (Def_Id, No_Uint);
3609          end if;
3610
3611          if Present (Arg_Code) then
3612             if not Is_VMS_Exception (Def_Id) then
3613                Error_Pragma_Arg
3614                  ("Code option for pragma% not allowed for Ada case",
3615                   Arg_Code);
3616             end if;
3617
3618             Check_Arg_Is_Static_Expression (Arg_Code, Any_Integer);
3619             Code_Val := Expr_Value (Arg_Code);
3620
3621             if not UI_Is_In_Int_Range (Code_Val) then
3622                Error_Pragma_Arg
3623                  ("Code option for pragma% must be in 32-bit range",
3624                   Arg_Code);
3625
3626             else
3627                Set_Exception_Code (Def_Id, Code_Val);
3628             end if;
3629          end if;
3630       end Process_Extended_Import_Export_Exception_Pragma;
3631
3632       -------------------------------------------------
3633       -- Process_Extended_Import_Export_Internal_Arg --
3634       -------------------------------------------------
3635
3636       procedure Process_Extended_Import_Export_Internal_Arg
3637         (Arg_Internal : Node_Id := Empty)
3638       is
3639       begin
3640          if No (Arg_Internal) then
3641             Error_Pragma ("Internal parameter required for pragma%");
3642          end if;
3643
3644          if Nkind (Arg_Internal) = N_Identifier then
3645             null;
3646
3647          elsif Nkind (Arg_Internal) = N_Operator_Symbol
3648            and then (Prag_Id = Pragma_Import_Function
3649                        or else
3650                      Prag_Id = Pragma_Export_Function)
3651          then
3652             null;
3653
3654          else
3655             Error_Pragma_Arg
3656               ("wrong form for Internal parameter for pragma%", Arg_Internal);
3657          end if;
3658
3659          Check_Arg_Is_Local_Name (Arg_Internal);
3660       end Process_Extended_Import_Export_Internal_Arg;
3661
3662       --------------------------------------------------
3663       -- Process_Extended_Import_Export_Object_Pragma --
3664       --------------------------------------------------
3665
3666       procedure Process_Extended_Import_Export_Object_Pragma
3667         (Arg_Internal : Node_Id;
3668          Arg_External : Node_Id;
3669          Arg_Size     : Node_Id)
3670       is
3671          Def_Id : Entity_Id;
3672
3673       begin
3674          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3675          Def_Id := Entity (Arg_Internal);
3676
3677          if not Ekind_In (Def_Id, E_Constant, E_Variable) then
3678             Error_Pragma_Arg
3679               ("pragma% must designate an object", Arg_Internal);
3680          end if;
3681
3682          if Has_Rep_Pragma (Def_Id, Name_Common_Object)
3683               or else
3684             Has_Rep_Pragma (Def_Id, Name_Psect_Object)
3685          then
3686             Error_Pragma_Arg
3687               ("previous Common/Psect_Object applies, pragma % not permitted",
3688                Arg_Internal);
3689          end if;
3690
3691          if Rep_Item_Too_Late (Def_Id, N) then
3692             raise Pragma_Exit;
3693          end if;
3694
3695          Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
3696
3697          if Present (Arg_Size) then
3698             Check_Arg_Is_External_Name (Arg_Size);
3699          end if;
3700
3701          --  Export_Object case
3702
3703          if Prag_Id = Pragma_Export_Object then
3704             if not Is_Library_Level_Entity (Def_Id) then
3705                Error_Pragma_Arg
3706                  ("argument for pragma% must be library level entity",
3707                   Arg_Internal);
3708             end if;
3709
3710             if Ekind (Current_Scope) = E_Generic_Package then
3711                Error_Pragma ("pragma& cannot appear in a generic unit");
3712             end if;
3713
3714             if not Size_Known_At_Compile_Time (Etype (Def_Id)) then
3715                Error_Pragma_Arg
3716                  ("exported object must have compile time known size",
3717                   Arg_Internal);
3718             end if;
3719
3720             if Warn_On_Export_Import and then Is_Exported (Def_Id) then
3721                Error_Msg_N ("?duplicate Export_Object pragma", N);
3722             else
3723                Set_Exported (Def_Id, Arg_Internal);
3724             end if;
3725
3726          --  Import_Object case
3727
3728          else
3729             if Is_Concurrent_Type (Etype (Def_Id)) then
3730                Error_Pragma_Arg
3731                  ("cannot use pragma% for task/protected object",
3732                   Arg_Internal);
3733             end if;
3734
3735             if Ekind (Def_Id) = E_Constant then
3736                Error_Pragma_Arg
3737                  ("cannot import a constant", Arg_Internal);
3738             end if;
3739
3740             if Warn_On_Export_Import
3741               and then Has_Discriminants (Etype (Def_Id))
3742             then
3743                Error_Msg_N
3744                  ("imported value must be initialized?", Arg_Internal);
3745             end if;
3746
3747             if Warn_On_Export_Import
3748               and then Is_Access_Type (Etype (Def_Id))
3749             then
3750                Error_Pragma_Arg
3751                  ("cannot import object of an access type?", Arg_Internal);
3752             end if;
3753
3754             if Warn_On_Export_Import
3755               and then Is_Imported (Def_Id)
3756             then
3757                Error_Msg_N
3758                  ("?duplicate Import_Object pragma", N);
3759
3760             --  Check for explicit initialization present. Note that an
3761             --  initialization generated by the code generator, e.g. for an
3762             --  access type, does not count here.
3763
3764             elsif Present (Expression (Parent (Def_Id)))
3765                and then
3766                  Comes_From_Source
3767                    (Original_Node (Expression (Parent (Def_Id))))
3768             then
3769                Error_Msg_Sloc := Sloc (Def_Id);
3770                Error_Pragma_Arg
3771                  ("imported entities cannot be initialized (RM B.1(24))",
3772                   "\no initialization allowed for & declared#", Arg1);
3773             else
3774                Set_Imported (Def_Id);
3775                Note_Possible_Modification (Arg_Internal, Sure => False);
3776             end if;
3777          end if;
3778       end Process_Extended_Import_Export_Object_Pragma;
3779
3780       ------------------------------------------------------
3781       -- Process_Extended_Import_Export_Subprogram_Pragma --
3782       ------------------------------------------------------
3783
3784       procedure Process_Extended_Import_Export_Subprogram_Pragma
3785         (Arg_Internal                 : Node_Id;
3786          Arg_External                 : Node_Id;
3787          Arg_Parameter_Types          : Node_Id;
3788          Arg_Result_Type              : Node_Id := Empty;
3789          Arg_Mechanism                : Node_Id;
3790          Arg_Result_Mechanism         : Node_Id := Empty;
3791          Arg_First_Optional_Parameter : Node_Id := Empty)
3792       is
3793          Ent       : Entity_Id;
3794          Def_Id    : Entity_Id;
3795          Hom_Id    : Entity_Id;
3796          Formal    : Entity_Id;
3797          Ambiguous : Boolean;
3798          Match     : Boolean;
3799          Dval      : Node_Id;
3800
3801          function Same_Base_Type
3802           (Ptype  : Node_Id;
3803            Formal : Entity_Id) return Boolean;
3804          --  Determines if Ptype references the type of Formal. Note that only
3805          --  the base types need to match according to the spec. Ptype here is
3806          --  the argument from the pragma, which is either a type name, or an
3807          --  access attribute.
3808
3809          --------------------
3810          -- Same_Base_Type --
3811          --------------------
3812
3813          function Same_Base_Type
3814            (Ptype  : Node_Id;
3815             Formal : Entity_Id) return Boolean
3816          is
3817             Ftyp : constant Entity_Id := Base_Type (Etype (Formal));
3818             Pref : Node_Id;
3819
3820          begin
3821             --  Case where pragma argument is typ'Access
3822
3823             if Nkind (Ptype) = N_Attribute_Reference
3824               and then Attribute_Name (Ptype) = Name_Access
3825             then
3826                Pref := Prefix (Ptype);
3827                Find_Type (Pref);
3828
3829                if not Is_Entity_Name (Pref)
3830                  or else Entity (Pref) = Any_Type
3831                then
3832                   raise Pragma_Exit;
3833                end if;
3834
3835                --  We have a match if the corresponding argument is of an
3836                --  anonymous access type, and its designated type matches the
3837                --  type of the prefix of the access attribute
3838
3839                return Ekind (Ftyp) = E_Anonymous_Access_Type
3840                  and then Base_Type (Entity (Pref)) =
3841                             Base_Type (Etype (Designated_Type (Ftyp)));
3842
3843             --  Case where pragma argument is a type name
3844
3845             else
3846                Find_Type (Ptype);
3847
3848                if not Is_Entity_Name (Ptype)
3849                  or else Entity (Ptype) = Any_Type
3850                then
3851                   raise Pragma_Exit;
3852                end if;
3853
3854                --  We have a match if the corresponding argument is of the type
3855                --  given in the pragma (comparing base types)
3856
3857                return Base_Type (Entity (Ptype)) = Ftyp;
3858             end if;
3859          end Same_Base_Type;
3860
3861       --  Start of processing for
3862       --  Process_Extended_Import_Export_Subprogram_Pragma
3863
3864       begin
3865          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3866          Ent := Empty;
3867          Ambiguous := False;
3868
3869          --  Loop through homonyms (overloadings) of the entity
3870
3871          Hom_Id := Entity (Arg_Internal);
3872          while Present (Hom_Id) loop
3873             Def_Id := Get_Base_Subprogram (Hom_Id);
3874
3875             --  We need a subprogram in the current scope
3876
3877             if not Is_Subprogram (Def_Id)
3878               or else Scope (Def_Id) /= Current_Scope
3879             then
3880                null;
3881
3882             else
3883                Match := True;
3884
3885                --  Pragma cannot apply to subprogram body
3886
3887                if Is_Subprogram (Def_Id)
3888                  and then Nkind (Parent (Declaration_Node (Def_Id))) =
3889                                                              N_Subprogram_Body
3890                then
3891                   Error_Pragma
3892                     ("pragma% requires separate spec"
3893                       & " and must come before body");
3894                end if;
3895
3896                --  Test result type if given, note that the result type
3897                --  parameter can only be present for the function cases.
3898
3899                if Present (Arg_Result_Type)
3900                  and then not Same_Base_Type (Arg_Result_Type, Def_Id)
3901                then
3902                   Match := False;
3903
3904                elsif Etype (Def_Id) /= Standard_Void_Type
3905                  and then
3906                    (Pname = Name_Export_Procedure
3907                       or else
3908                     Pname = Name_Import_Procedure)
3909                then
3910                   Match := False;
3911
3912                --  Test parameter types if given. Note that this parameter
3913                --  has not been analyzed (and must not be, since it is
3914                --  semantic nonsense), so we get it as the parser left it.
3915
3916                elsif Present (Arg_Parameter_Types) then
3917                   Check_Matching_Types : declare
3918                      Formal : Entity_Id;
3919                      Ptype  : Node_Id;
3920
3921                   begin
3922                      Formal := First_Formal (Def_Id);
3923
3924                      if Nkind (Arg_Parameter_Types) = N_Null then
3925                         if Present (Formal) then
3926                            Match := False;
3927                         end if;
3928
3929                      --  A list of one type, e.g. (List) is parsed as
3930                      --  a parenthesized expression.
3931
3932                      elsif Nkind (Arg_Parameter_Types) /= N_Aggregate
3933                        and then Paren_Count (Arg_Parameter_Types) = 1
3934                      then
3935                         if No (Formal)
3936                           or else Present (Next_Formal (Formal))
3937                         then
3938                            Match := False;
3939                         else
3940                            Match :=
3941                              Same_Base_Type (Arg_Parameter_Types, Formal);
3942                         end if;
3943
3944                      --  A list of more than one type is parsed as a aggregate
3945
3946                      elsif Nkind (Arg_Parameter_Types) = N_Aggregate
3947                        and then Paren_Count (Arg_Parameter_Types) = 0
3948                      then
3949                         Ptype := First (Expressions (Arg_Parameter_Types));
3950                         while Present (Ptype) or else Present (Formal) loop
3951                            if No (Ptype)
3952                              or else No (Formal)
3953                              or else not Same_Base_Type (Ptype, Formal)
3954                            then
3955                               Match := False;
3956                               exit;
3957                            else
3958                               Next_Formal (Formal);
3959                               Next (Ptype);
3960                            end if;
3961                         end loop;
3962
3963                      --  Anything else is of the wrong form
3964
3965                      else
3966                         Error_Pragma_Arg
3967                           ("wrong form for Parameter_Types parameter",
3968                            Arg_Parameter_Types);
3969                      end if;
3970                   end Check_Matching_Types;
3971                end if;
3972
3973                --  Match is now False if the entry we found did not match
3974                --  either a supplied Parameter_Types or Result_Types argument
3975
3976                if Match then
3977                   if No (Ent) then
3978                      Ent := Def_Id;
3979
3980                   --  Ambiguous case, the flag Ambiguous shows if we already
3981                   --  detected this and output the initial messages.
3982
3983                   else
3984                      if not Ambiguous then
3985                         Ambiguous := True;
3986                         Error_Msg_Name_1 := Pname;
3987                         Error_Msg_N
3988                           ("pragma% does not uniquely identify subprogram!",
3989                            N);
3990                         Error_Msg_Sloc := Sloc (Ent);
3991                         Error_Msg_N ("matching subprogram #!", N);
3992                         Ent := Empty;
3993                      end if;
3994
3995                      Error_Msg_Sloc := Sloc (Def_Id);
3996                      Error_Msg_N ("matching subprogram #!", N);
3997                   end if;
3998                end if;
3999             end if;
4000
4001             Hom_Id := Homonym (Hom_Id);
4002          end loop;
4003
4004          --  See if we found an entry
4005
4006          if No (Ent) then
4007             if not Ambiguous then
4008                if Is_Generic_Subprogram (Entity (Arg_Internal)) then
4009                   Error_Pragma
4010                     ("pragma% cannot be given for generic subprogram");
4011                else
4012                   Error_Pragma
4013                     ("pragma% does not identify local subprogram");
4014                end if;
4015             end if;
4016
4017             return;
4018          end if;
4019
4020          --  Import pragmas must be for imported entities
4021
4022          if Prag_Id = Pragma_Import_Function
4023               or else
4024             Prag_Id = Pragma_Import_Procedure
4025               or else
4026             Prag_Id = Pragma_Import_Valued_Procedure
4027          then
4028             if not Is_Imported (Ent) then
4029                Error_Pragma
4030                  ("pragma Import or Interface must precede pragma%");
4031             end if;
4032
4033          --  Here we have the Export case which can set the entity as exported
4034
4035          --  But does not do so if the specified external name is null, since
4036          --  that is taken as a signal in DEC Ada 83 (with which we want to be
4037          --  compatible) to request no external name.
4038
4039          elsif Nkind (Arg_External) = N_String_Literal
4040            and then String_Length (Strval (Arg_External)) = 0
4041          then
4042             null;
4043
4044          --  In all other cases, set entity as exported
4045
4046          else
4047             Set_Exported (Ent, Arg_Internal);
4048          end if;
4049
4050          --  Special processing for Valued_Procedure cases
4051
4052          if Prag_Id = Pragma_Import_Valued_Procedure
4053            or else
4054             Prag_Id = Pragma_Export_Valued_Procedure
4055          then
4056             Formal := First_Formal (Ent);
4057
4058             if No (Formal) then
4059                Error_Pragma ("at least one parameter required for pragma%");
4060
4061             elsif Ekind (Formal) /= E_Out_Parameter then
4062                Error_Pragma ("first parameter must have mode out for pragma%");
4063
4064             else
4065                Set_Is_Valued_Procedure (Ent);
4066             end if;
4067          end if;
4068
4069          Set_Extended_Import_Export_External_Name (Ent, Arg_External);
4070
4071          --  Process Result_Mechanism argument if present. We have already
4072          --  checked that this is only allowed for the function case.
4073
4074          if Present (Arg_Result_Mechanism) then
4075             Set_Mechanism_Value (Ent, Arg_Result_Mechanism);
4076          end if;
4077
4078          --  Process Mechanism parameter if present. Note that this parameter
4079          --  is not analyzed, and must not be analyzed since it is semantic
4080          --  nonsense, so we get it in exactly as the parser left it.
4081
4082          if Present (Arg_Mechanism) then
4083             declare
4084                Formal : Entity_Id;
4085                Massoc : Node_Id;
4086                Mname  : Node_Id;
4087                Choice : Node_Id;
4088
4089             begin
4090                --  A single mechanism association without a formal parameter
4091                --  name is parsed as a parenthesized expression. All other
4092                --  cases are parsed as aggregates, so we rewrite the single
4093                --  parameter case as an aggregate for consistency.
4094
4095                if Nkind (Arg_Mechanism) /= N_Aggregate
4096                  and then Paren_Count (Arg_Mechanism) = 1
4097                then
4098                   Rewrite (Arg_Mechanism,
4099                     Make_Aggregate (Sloc (Arg_Mechanism),
4100                       Expressions => New_List (
4101                         Relocate_Node (Arg_Mechanism))));
4102                end if;
4103
4104                --  Case of only mechanism name given, applies to all formals
4105
4106                if Nkind (Arg_Mechanism) /= N_Aggregate then
4107                   Formal := First_Formal (Ent);
4108                   while Present (Formal) loop
4109                      Set_Mechanism_Value (Formal, Arg_Mechanism);
4110                      Next_Formal (Formal);
4111                   end loop;
4112
4113                --  Case of list of mechanism associations given
4114
4115                else
4116                   if Null_Record_Present (Arg_Mechanism) then
4117                      Error_Pragma_Arg
4118                        ("inappropriate form for Mechanism parameter",
4119                         Arg_Mechanism);
4120                   end if;
4121
4122                   --  Deal with positional ones first
4123
4124                   Formal := First_Formal (Ent);
4125
4126                   if Present (Expressions (Arg_Mechanism)) then
4127                      Mname := First (Expressions (Arg_Mechanism));
4128                      while Present (Mname) loop
4129                         if No (Formal) then
4130                            Error_Pragma_Arg
4131                              ("too many mechanism associations", Mname);
4132                         end if;
4133
4134                         Set_Mechanism_Value (Formal, Mname);
4135                         Next_Formal (Formal);
4136                         Next (Mname);
4137                      end loop;
4138                   end if;
4139
4140                   --  Deal with named entries
4141
4142                   if Present (Component_Associations (Arg_Mechanism)) then
4143                      Massoc := First (Component_Associations (Arg_Mechanism));
4144                      while Present (Massoc) loop
4145                         Choice := First (Choices (Massoc));
4146
4147                         if Nkind (Choice) /= N_Identifier
4148                           or else Present (Next (Choice))
4149                         then
4150                            Error_Pragma_Arg
4151                              ("incorrect form for mechanism association",
4152                               Massoc);
4153                         end if;
4154
4155                         Formal := First_Formal (Ent);
4156                         loop
4157                            if No (Formal) then
4158                               Error_Pragma_Arg
4159                                 ("parameter name & not present", Choice);
4160                            end if;
4161
4162                            if Chars (Choice) = Chars (Formal) then
4163                               Set_Mechanism_Value
4164                                 (Formal, Expression (Massoc));
4165
4166                               --  Set entity on identifier (needed by ASIS)
4167
4168                               Set_Entity (Choice, Formal);
4169
4170                               exit;
4171                            end if;
4172
4173                            Next_Formal (Formal);
4174                         end loop;
4175
4176                         Next (Massoc);
4177                      end loop;
4178                   end if;
4179                end if;
4180             end;
4181          end if;
4182
4183          --  Process First_Optional_Parameter argument if present. We have
4184          --  already checked that this is only allowed for the Import case.
4185
4186          if Present (Arg_First_Optional_Parameter) then
4187             if Nkind (Arg_First_Optional_Parameter) /= N_Identifier then
4188                Error_Pragma_Arg
4189                  ("first optional parameter must be formal parameter name",
4190                   Arg_First_Optional_Parameter);
4191             end if;
4192
4193             Formal := First_Formal (Ent);
4194             loop
4195                if No (Formal) then
4196                   Error_Pragma_Arg
4197                     ("specified formal parameter& not found",
4198                      Arg_First_Optional_Parameter);
4199                end if;
4200
4201                exit when Chars (Formal) =
4202                          Chars (Arg_First_Optional_Parameter);
4203
4204                Next_Formal (Formal);
4205             end loop;
4206
4207             Set_First_Optional_Parameter (Ent, Formal);
4208
4209             --  Check specified and all remaining formals have right form
4210
4211             while Present (Formal) loop
4212                if Ekind (Formal) /= E_In_Parameter then
4213                   Error_Msg_NE
4214                     ("optional formal& is not of mode in!",
4215                      Arg_First_Optional_Parameter, Formal);
4216
4217                else
4218                   Dval := Default_Value (Formal);
4219
4220                   if No (Dval) then
4221                      Error_Msg_NE
4222                        ("optional formal& does not have default value!",
4223                         Arg_First_Optional_Parameter, Formal);
4224
4225                   elsif Compile_Time_Known_Value_Or_Aggr (Dval) then
4226                      null;
4227
4228                   else
4229                      Error_Msg_FE
4230                        ("default value for optional formal& is non-static!",
4231                         Arg_First_Optional_Parameter, Formal);
4232                   end if;
4233                end if;
4234
4235                Set_Is_Optional_Parameter (Formal);
4236                Next_Formal (Formal);
4237             end loop;
4238          end if;
4239       end Process_Extended_Import_Export_Subprogram_Pragma;
4240
4241       --------------------------
4242       -- Process_Generic_List --
4243       --------------------------
4244
4245       procedure Process_Generic_List is
4246          Arg : Node_Id;
4247          Exp : Node_Id;
4248
4249       begin
4250          Check_No_Identifiers;
4251          Check_At_Least_N_Arguments (1);
4252
4253          Arg := Arg1;
4254          while Present (Arg) loop
4255             Exp := Get_Pragma_Arg (Arg);
4256             Analyze (Exp);
4257
4258             if not Is_Entity_Name (Exp)
4259               or else
4260                 (not Is_Generic_Instance (Entity (Exp))
4261                   and then
4262                  not Is_Generic_Unit (Entity (Exp)))
4263             then
4264                Error_Pragma_Arg
4265                  ("pragma% argument must be name of generic unit/instance",
4266                   Arg);
4267             end if;
4268
4269             Next (Arg);
4270          end loop;
4271       end Process_Generic_List;
4272
4273       ------------------------------------
4274       -- Process_Import_Predefined_Type --
4275       ------------------------------------
4276
4277       procedure Process_Import_Predefined_Type is
4278          Loc  : constant Source_Ptr := Sloc (N);
4279          Elmt : Elmt_Id;
4280          Ftyp : Node_Id := Empty;
4281          Decl : Node_Id;
4282          Def  : Node_Id;
4283          Nam  : Name_Id;
4284
4285       begin
4286          String_To_Name_Buffer (Strval (Expression (Arg3)));
4287          Nam := Name_Find;
4288
4289          Elmt := First_Elmt (Predefined_Float_Types);
4290          while Present (Elmt) and then Chars (Node (Elmt)) /= Nam loop
4291             Next_Elmt (Elmt);
4292          end loop;
4293
4294          Ftyp := Node (Elmt);
4295
4296          if Present (Ftyp) then
4297
4298             --  Don't build a derived type declaration, because predefined C
4299             --  types have no declaration anywhere, so cannot really be named.
4300             --  Instead build a full type declaration, starting with an
4301             --  appropriate type definition is built
4302
4303             if Is_Floating_Point_Type (Ftyp) then
4304                Def := Make_Floating_Point_Definition (Loc,
4305                  Make_Integer_Literal (Loc, Digits_Value (Ftyp)),
4306                  Make_Real_Range_Specification (Loc,
4307                    Make_Real_Literal (Loc, Realval (Type_Low_Bound (Ftyp))),
4308                    Make_Real_Literal (Loc, Realval (Type_High_Bound (Ftyp)))));
4309
4310             --  Should never have a predefined type we cannot handle
4311
4312             else
4313                raise Program_Error;
4314             end if;
4315
4316             --  Build and insert a Full_Type_Declaration, which will be
4317             --  analyzed as soon as this list entry has been analyzed.
4318
4319             Decl := Make_Full_Type_Declaration (Loc,
4320               Make_Defining_Identifier (Loc, Chars (Expression (Arg2))),
4321               Type_Definition => Def);
4322
4323             Insert_After (N, Decl);
4324             Mark_Rewrite_Insertion (Decl);
4325
4326          else
4327             Error_Pragma_Arg ("no matching type found for pragma%",
4328             Arg2);
4329          end if;
4330       end Process_Import_Predefined_Type;
4331
4332       ---------------------------------
4333       -- Process_Import_Or_Interface --
4334       ---------------------------------
4335
4336       procedure Process_Import_Or_Interface is
4337          C      : Convention_Id;
4338          Def_Id : Entity_Id;
4339          Hom_Id : Entity_Id;
4340
4341       begin
4342          Process_Convention (C, Def_Id);
4343          Kill_Size_Check_Code (Def_Id);
4344          Note_Possible_Modification (Get_Pragma_Arg (Arg2), Sure => False);
4345
4346          if Ekind_In (Def_Id, E_Variable, E_Constant) then
4347
4348             --  We do not permit Import to apply to a renaming declaration
4349
4350             if Present (Renamed_Object (Def_Id)) then
4351                Error_Pragma_Arg
4352                  ("pragma% not allowed for object renaming", Arg2);
4353
4354             --  User initialization is not allowed for imported object, but
4355             --  the object declaration may contain a default initialization,
4356             --  that will be discarded. Note that an explicit initialization
4357             --  only counts if it comes from source, otherwise it is simply
4358             --  the code generator making an implicit initialization explicit.
4359
4360             elsif Present (Expression (Parent (Def_Id)))
4361               and then Comes_From_Source (Expression (Parent (Def_Id)))
4362             then
4363                Error_Msg_Sloc := Sloc (Def_Id);
4364                Error_Pragma_Arg
4365                  ("no initialization allowed for declaration of& #",
4366                   "\imported entities cannot be initialized (RM B.1(24))",
4367                   Arg2);
4368
4369             else
4370                Set_Imported (Def_Id);
4371                Process_Interface_Name (Def_Id, Arg3, Arg4);
4372
4373                --  Note that we do not set Is_Public here. That's because we
4374                --  only want to set it if there is no address clause, and we
4375                --  don't know that yet, so we delay that processing till
4376                --  freeze time.
4377
4378                --  pragma Import completes deferred constants
4379
4380                if Ekind (Def_Id) = E_Constant then
4381                   Set_Has_Completion (Def_Id);
4382                end if;
4383
4384                --  It is not possible to import a constant of an unconstrained
4385                --  array type (e.g. string) because there is no simple way to
4386                --  write a meaningful subtype for it.
4387
4388                if Is_Array_Type (Etype (Def_Id))
4389                  and then not Is_Constrained (Etype (Def_Id))
4390                then
4391                   Error_Msg_NE
4392                     ("imported constant& must have a constrained subtype",
4393                       N, Def_Id);
4394                end if;
4395             end if;
4396
4397          elsif Is_Subprogram (Def_Id)
4398            or else Is_Generic_Subprogram (Def_Id)
4399          then
4400             --  If the name is overloaded, pragma applies to all of the denoted
4401             --  entities in the same declarative part.
4402
4403             Hom_Id := Def_Id;
4404             while Present (Hom_Id) loop
4405                Def_Id := Get_Base_Subprogram (Hom_Id);
4406
4407                --  Ignore inherited subprograms because the pragma will apply
4408                --  to the parent operation, which is the one called.
4409
4410                if Is_Overloadable (Def_Id)
4411                  and then Present (Alias (Def_Id))
4412                then
4413                   null;
4414
4415                --  If it is not a subprogram, it must be in an outer scope and
4416                --  pragma does not apply.
4417
4418                elsif not Is_Subprogram (Def_Id)
4419                  and then not Is_Generic_Subprogram (Def_Id)
4420                then
4421                   null;
4422
4423                --  The pragma does not apply to primitives of interfaces
4424
4425                elsif Is_Dispatching_Operation (Def_Id)
4426                  and then Present (Find_Dispatching_Type (Def_Id))
4427                  and then Is_Interface (Find_Dispatching_Type (Def_Id))
4428                then
4429                   null;
4430
4431                --  Verify that the homonym is in the same declarative part (not
4432                --  just the same scope).
4433
4434                elsif Parent (Unit_Declaration_Node (Def_Id)) /= Parent (N)
4435                  and then Nkind (Parent (N)) /= N_Compilation_Unit_Aux
4436                then
4437                   exit;
4438
4439                else
4440                   Set_Imported (Def_Id);
4441
4442                   --  Reject an Import applied to an abstract subprogram
4443
4444                   if Is_Subprogram (Def_Id)
4445                     and then Is_Abstract_Subprogram (Def_Id)
4446                   then
4447                      Error_Msg_Sloc := Sloc (Def_Id);
4448                      Error_Msg_NE
4449                        ("cannot import abstract subprogram& declared#",
4450                         Arg2, Def_Id);
4451                   end if;
4452
4453                   --  Special processing for Convention_Intrinsic
4454
4455                   if C = Convention_Intrinsic then
4456
4457                      --  Link_Name argument not allowed for intrinsic
4458
4459                      Check_No_Link_Name;
4460
4461                      Set_Is_Intrinsic_Subprogram (Def_Id);
4462
4463                      --  If no external name is present, then check that this
4464                      --  is a valid intrinsic subprogram. If an external name
4465                      --  is present, then this is handled by the back end.
4466
4467                      if No (Arg3) then
4468                         Check_Intrinsic_Subprogram
4469                           (Def_Id, Get_Pragma_Arg (Arg2));
4470                      end if;
4471                   end if;
4472
4473                   --  All interfaced procedures need an external symbol created
4474                   --  for them since they are always referenced from another
4475                   --  object file.
4476
4477                   Set_Is_Public (Def_Id);
4478
4479                   --  Verify that the subprogram does not have a completion
4480                   --  through a renaming declaration. For other completions the
4481                   --  pragma appears as a too late representation.
4482
4483                   declare
4484                      Decl : constant Node_Id := Unit_Declaration_Node (Def_Id);
4485
4486                   begin
4487                      if Present (Decl)
4488                        and then Nkind (Decl) = N_Subprogram_Declaration
4489                        and then Present (Corresponding_Body (Decl))
4490                        and then Nkind (Unit_Declaration_Node
4491                                         (Corresponding_Body (Decl))) =
4492                                              N_Subprogram_Renaming_Declaration
4493                      then
4494                         Error_Msg_Sloc := Sloc (Def_Id);
4495                         Error_Msg_NE
4496                           ("cannot import&, renaming already provided for " &
4497                            "declaration #", N, Def_Id);
4498                      end if;
4499                   end;
4500
4501                   Set_Has_Completion (Def_Id);
4502                   Process_Interface_Name (Def_Id, Arg3, Arg4);
4503                end if;
4504
4505                if Is_Compilation_Unit (Hom_Id) then
4506
4507                   --  Its possible homonyms are not affected by the pragma.
4508                   --  Such homonyms might be present in the context of other
4509                   --  units being compiled.
4510
4511                   exit;
4512
4513                else
4514                   Hom_Id := Homonym (Hom_Id);
4515                end if;
4516             end loop;
4517
4518          --  When the convention is Java or CIL, we also allow Import to be
4519          --  given for packages, generic packages, exceptions, record
4520          --  components, and access to subprograms.
4521
4522          elsif (C = Convention_Java or else C = Convention_CIL)
4523            and then
4524              (Is_Package_Or_Generic_Package (Def_Id)
4525                or else Ekind (Def_Id) = E_Exception
4526                or else Ekind (Def_Id) = E_Access_Subprogram_Type
4527                or else Nkind (Parent (Def_Id)) = N_Component_Declaration)
4528          then
4529             Set_Imported (Def_Id);
4530             Set_Is_Public (Def_Id);
4531             Process_Interface_Name (Def_Id, Arg3, Arg4);
4532
4533          --  Import a CPP class
4534
4535          elsif Is_Record_Type (Def_Id)
4536            and then C = Convention_CPP
4537          then
4538             --  Types treated as CPP classes must be declared limited (note:
4539             --  this used to be a warning but there is no real benefit to it
4540             --  since we did effectively intend to treat the type as limited
4541             --  anyway).
4542
4543             if not Is_Limited_Type (Def_Id) then
4544                Error_Msg_N
4545                  ("imported 'C'P'P type must be limited",
4546                   Get_Pragma_Arg (Arg2));
4547             end if;
4548
4549             Set_Is_CPP_Class (Def_Id);
4550
4551             --  Imported CPP types must not have discriminants (because C++
4552             --  classes do not have discriminants).
4553
4554             if Has_Discriminants (Def_Id) then
4555                Error_Msg_N
4556                  ("imported 'C'P'P type cannot have discriminants",
4557                   First (Discriminant_Specifications
4558                           (Declaration_Node (Def_Id))));
4559             end if;
4560
4561             --  Components of imported CPP types must not have default
4562             --  expressions because the constructor (if any) is on the
4563             --  C++ side.
4564
4565             declare
4566                Tdef  : constant Node_Id :=
4567                          Type_Definition (Declaration_Node (Def_Id));
4568                Clist : Node_Id;
4569                Comp  : Node_Id;
4570
4571             begin
4572                if Nkind (Tdef) = N_Record_Definition then
4573                   Clist := Component_List (Tdef);
4574
4575                else
4576                   pragma Assert (Nkind (Tdef) = N_Derived_Type_Definition);
4577                   Clist := Component_List (Record_Extension_Part (Tdef));
4578                end if;
4579
4580                if Present (Clist) then
4581                   Comp := First (Component_Items (Clist));
4582                   while Present (Comp) loop
4583                      if Present (Expression (Comp)) then
4584                         Error_Msg_N
4585                           ("component of imported 'C'P'P type cannot have" &
4586                            " default expression", Expression (Comp));
4587                      end if;
4588
4589                      Next (Comp);
4590                   end loop;
4591                end if;
4592             end;
4593
4594          elsif Nkind (Parent (Def_Id)) = N_Incomplete_Type_Declaration then
4595             Check_No_Link_Name;
4596             Check_Arg_Count (3);
4597             Check_Arg_Is_Static_Expression (Arg3, Standard_String);
4598
4599             Process_Import_Predefined_Type;
4600
4601          else
4602             Error_Pragma_Arg
4603               ("second argument of pragma% must be object, subprogram" &
4604                " or incomplete type",
4605                Arg2);
4606          end if;
4607
4608          --  If this pragma applies to a compilation unit, then the unit, which
4609          --  is a subprogram, does not require (or allow) a body. We also do
4610          --  not need to elaborate imported procedures.
4611
4612          if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
4613             declare
4614                Cunit : constant Node_Id := Parent (Parent (N));
4615             begin
4616                Set_Body_Required (Cunit, False);
4617             end;
4618          end if;
4619       end Process_Import_Or_Interface;
4620
4621       --------------------
4622       -- Process_Inline --
4623       --------------------
4624
4625       procedure Process_Inline (Active : Boolean) is
4626          Assoc     : Node_Id;
4627          Decl      : Node_Id;
4628          Subp_Id   : Node_Id;
4629          Subp      : Entity_Id;
4630          Applies   : Boolean;
4631
4632          Effective : Boolean := False;
4633          --  Set True if inline has some effect, i.e. if there is at least one
4634          --  subprogram set as inlined as a result of the use of the pragma.
4635
4636          procedure Make_Inline (Subp : Entity_Id);
4637          --  Subp is the defining unit name of the subprogram declaration. Set
4638          --  the flag, as well as the flag in the corresponding body, if there
4639          --  is one present.
4640
4641          procedure Set_Inline_Flags (Subp : Entity_Id);
4642          --  Sets Is_Inlined and Has_Pragma_Inline flags for Subp and also
4643          --  Has_Pragma_Inline_Always for the Inline_Always case.
4644
4645          function Inlining_Not_Possible (Subp : Entity_Id) return Boolean;
4646          --  Returns True if it can be determined at this stage that inlining
4647          --  is not possible, for example if the body is available and contains
4648          --  exception handlers, we prevent inlining, since otherwise we can
4649          --  get undefined symbols at link time. This function also emits a
4650          --  warning if front-end inlining is enabled and the pragma appears
4651          --  too late.
4652          --
4653          --  ??? is business with link symbols still valid, or does it relate
4654          --  to front end ZCX which is being phased out ???
4655
4656          ---------------------------
4657          -- Inlining_Not_Possible --
4658          ---------------------------
4659
4660          function Inlining_Not_Possible (Subp : Entity_Id) return Boolean is
4661             Decl  : constant Node_Id := Unit_Declaration_Node (Subp);
4662             Stats : Node_Id;
4663
4664          begin
4665             if Nkind (Decl) = N_Subprogram_Body then
4666                Stats := Handled_Statement_Sequence (Decl);
4667                return Present (Exception_Handlers (Stats))
4668                  or else Present (At_End_Proc (Stats));
4669
4670             elsif Nkind (Decl) = N_Subprogram_Declaration
4671               and then Present (Corresponding_Body (Decl))
4672             then
4673                if Front_End_Inlining
4674                  and then Analyzed (Corresponding_Body (Decl))
4675                then
4676                   Error_Msg_N ("pragma appears too late, ignored?", N);
4677                   return True;
4678
4679                --  If the subprogram is a renaming as body, the body is just a
4680                --  call to the renamed subprogram, and inlining is trivially
4681                --  possible.
4682
4683                elsif
4684                  Nkind (Unit_Declaration_Node (Corresponding_Body (Decl))) =
4685                                              N_Subprogram_Renaming_Declaration
4686                then
4687                   return False;
4688
4689                else
4690                   Stats :=
4691                     Handled_Statement_Sequence
4692                         (Unit_Declaration_Node (Corresponding_Body (Decl)));
4693
4694                   return
4695                     Present (Exception_Handlers (Stats))
4696                       or else Present (At_End_Proc (Stats));
4697                end if;
4698
4699             else
4700                --  If body is not available, assume the best, the check is
4701                --  performed again when compiling enclosing package bodies.
4702
4703                return False;
4704             end if;
4705          end Inlining_Not_Possible;
4706
4707          -----------------
4708          -- Make_Inline --
4709          -----------------
4710
4711          procedure Make_Inline (Subp : Entity_Id) is
4712             Kind       : constant Entity_Kind := Ekind (Subp);
4713             Inner_Subp : Entity_Id   := Subp;
4714
4715          begin
4716             --  Ignore if bad type, avoid cascaded error
4717
4718             if Etype (Subp) = Any_Type then
4719                Applies := True;
4720                return;
4721
4722             --  Ignore if all inlining is suppressed
4723
4724             elsif Suppress_All_Inlining then
4725                Applies := True;
4726                return;
4727
4728             --  If inlining is not possible, for now do not treat as an error
4729
4730             elsif Inlining_Not_Possible (Subp) then
4731                Applies := True;
4732                return;
4733
4734             --  Here we have a candidate for inlining, but we must exclude
4735             --  derived operations. Otherwise we would end up trying to inline
4736             --  a phantom declaration, and the result would be to drag in a
4737             --  body which has no direct inlining associated with it. That
4738             --  would not only be inefficient but would also result in the
4739             --  backend doing cross-unit inlining in cases where it was
4740             --  definitely inappropriate to do so.
4741
4742             --  However, a simple Comes_From_Source test is insufficient, since
4743             --  we do want to allow inlining of generic instances which also do
4744             --  not come from source. We also need to recognize specs generated
4745             --  by the front-end for bodies that carry the pragma. Finally,
4746             --  predefined operators do not come from source but are not
4747             --  inlineable either.
4748
4749             elsif Is_Generic_Instance (Subp)
4750               or else Nkind (Parent (Parent (Subp))) = N_Subprogram_Declaration
4751             then
4752                null;
4753
4754             elsif not Comes_From_Source (Subp)
4755               and then Scope (Subp) /= Standard_Standard
4756             then
4757                Applies := True;
4758                return;
4759             end if;
4760
4761             --  The referenced entity must either be the enclosing entity, or
4762             --  an entity declared within the current open scope.
4763
4764             if Present (Scope (Subp))
4765               and then Scope (Subp) /= Current_Scope
4766               and then Subp /= Current_Scope
4767             then
4768                Error_Pragma_Arg
4769                  ("argument of% must be entity in current scope", Assoc);
4770                return;
4771             end if;
4772
4773             --  Processing for procedure, operator or function. If subprogram
4774             --  is aliased (as for an instance) indicate that the renamed
4775             --  entity (if declared in the same unit) is inlined.
4776
4777             if Is_Subprogram (Subp) then
4778                Inner_Subp := Ultimate_Alias (Inner_Subp);
4779
4780                if In_Same_Source_Unit (Subp, Inner_Subp) then
4781                   Set_Inline_Flags (Inner_Subp);
4782
4783                   Decl := Parent (Parent (Inner_Subp));
4784
4785                   if Nkind (Decl) = N_Subprogram_Declaration
4786                     and then Present (Corresponding_Body (Decl))
4787                   then
4788                      Set_Inline_Flags (Corresponding_Body (Decl));
4789
4790                   elsif Is_Generic_Instance (Subp) then
4791
4792                      --  Indicate that the body needs to be created for
4793                      --  inlining subsequent calls. The instantiation node
4794                      --  follows the declaration of the wrapper package
4795                      --  created for it.
4796
4797                      if Scope (Subp) /= Standard_Standard
4798                        and then
4799                          Need_Subprogram_Instance_Body
4800                           (Next (Unit_Declaration_Node (Scope (Alias (Subp)))),
4801                               Subp)
4802                      then
4803                         null;
4804                      end if;
4805
4806                   --  Inline is a program unit pragma (RM 10.1.5) and cannot
4807                   --  appear in a formal part to apply to a formal subprogram.
4808                   --  Do not apply check within an instance or a formal package
4809                   --  the test will have been applied to the original generic.
4810
4811                   elsif Nkind (Decl) in N_Formal_Subprogram_Declaration
4812                     and then List_Containing (Decl) = List_Containing (N)
4813                     and then not In_Instance
4814                   then
4815                      Error_Msg_N
4816                        ("Inline cannot apply to a formal subprogram", N);
4817                   end if;
4818                end if;
4819
4820                Applies := True;
4821
4822             --  For a generic subprogram set flag as well, for use at the point
4823             --  of instantiation, to determine whether the body should be
4824             --  generated.
4825
4826             elsif Is_Generic_Subprogram (Subp) then
4827                Set_Inline_Flags (Subp);
4828                Applies := True;
4829
4830             --  Literals are by definition inlined
4831
4832             elsif Kind = E_Enumeration_Literal then
4833                null;
4834
4835             --  Anything else is an error
4836
4837             else
4838                Error_Pragma_Arg
4839                  ("expect subprogram name for pragma%", Assoc);
4840             end if;
4841          end Make_Inline;
4842
4843          ----------------------
4844          -- Set_Inline_Flags --
4845          ----------------------
4846
4847          procedure Set_Inline_Flags (Subp : Entity_Id) is
4848          begin
4849             if Active then
4850                Set_Is_Inlined (Subp);
4851             end if;
4852
4853             if not Has_Pragma_Inline (Subp) then
4854                Set_Has_Pragma_Inline (Subp);
4855                Effective := True;
4856             end if;
4857
4858             if Prag_Id = Pragma_Inline_Always then
4859                Set_Has_Pragma_Inline_Always (Subp);
4860             end if;
4861          end Set_Inline_Flags;
4862
4863       --  Start of processing for Process_Inline
4864
4865       begin
4866          Check_No_Identifiers;
4867          Check_At_Least_N_Arguments (1);
4868
4869          if Active then
4870             Inline_Processing_Required := True;
4871          end if;
4872
4873          Assoc := Arg1;
4874          while Present (Assoc) loop
4875             Subp_Id := Get_Pragma_Arg (Assoc);
4876             Analyze (Subp_Id);
4877             Applies := False;
4878
4879             if Is_Entity_Name (Subp_Id) then
4880                Subp := Entity (Subp_Id);
4881
4882                if Subp = Any_Id then
4883
4884                   --  If previous error, avoid cascaded errors
4885
4886                   Applies := True;
4887                   Effective := True;
4888
4889                else
4890                   Make_Inline (Subp);
4891
4892                   --  For the pragma case, climb homonym chain. This is
4893                   --  what implements allowing the pragma in the renaming
4894                   --  case, with the result applying to the ancestors, and
4895                   --  also allows Inline to apply to all previous homonyms.
4896
4897                   if not From_Aspect_Specification (N) then
4898                      while Present (Homonym (Subp))
4899                        and then Scope (Homonym (Subp)) = Current_Scope
4900                      loop
4901                         Make_Inline (Homonym (Subp));
4902                         Subp := Homonym (Subp);
4903                      end loop;
4904                   end if;
4905                end if;
4906             end if;
4907
4908             if not Applies then
4909                Error_Pragma_Arg
4910                  ("inappropriate argument for pragma%", Assoc);
4911
4912             elsif not Effective
4913               and then Warn_On_Redundant_Constructs
4914               and then not Suppress_All_Inlining
4915             then
4916                if Inlining_Not_Possible (Subp) then
4917                   Error_Msg_NE
4918                     ("pragma Inline for& is ignored?", N, Entity (Subp_Id));
4919                else
4920                   Error_Msg_NE
4921                     ("pragma Inline for& is redundant?", N, Entity (Subp_Id));
4922                end if;
4923             end if;
4924
4925             Next (Assoc);
4926          end loop;
4927       end Process_Inline;
4928
4929       ----------------------------
4930       -- Process_Interface_Name --
4931       ----------------------------
4932
4933       procedure Process_Interface_Name
4934         (Subprogram_Def : Entity_Id;
4935          Ext_Arg        : Node_Id;
4936          Link_Arg       : Node_Id)
4937       is
4938          Ext_Nam    : Node_Id;
4939          Link_Nam   : Node_Id;
4940          String_Val : String_Id;
4941
4942          procedure Check_Form_Of_Interface_Name
4943            (SN            : Node_Id;
4944             Ext_Name_Case : Boolean);
4945          --  SN is a string literal node for an interface name. This routine
4946          --  performs some minimal checks that the name is reasonable. In
4947          --  particular that no spaces or other obviously incorrect characters
4948          --  appear. This is only a warning, since any characters are allowed.
4949          --  Ext_Name_Case is True for an External_Name, False for a Link_Name.
4950
4951          ----------------------------------
4952          -- Check_Form_Of_Interface_Name --
4953          ----------------------------------
4954
4955          procedure Check_Form_Of_Interface_Name
4956            (SN            : Node_Id;
4957             Ext_Name_Case : Boolean)
4958          is
4959             S  : constant String_Id := Strval (Expr_Value_S (SN));
4960             SL : constant Nat       := String_Length (S);
4961             C  : Char_Code;
4962
4963          begin
4964             if SL = 0 then
4965                Error_Msg_N ("interface name cannot be null string", SN);
4966             end if;
4967
4968             for J in 1 .. SL loop
4969                C := Get_String_Char (S, J);
4970
4971                --  Look for dubious character and issue unconditional warning.
4972                --  Definitely dubious if not in character range.
4973
4974                if not In_Character_Range (C)
4975
4976                   --  For all cases except CLI target,
4977                   --  commas, spaces and slashes are dubious (in CLI, we use
4978                   --  commas and backslashes in external names to specify
4979                   --  assembly version and public key, while slashes and spaces
4980                   --  can be used in names to mark nested classes and
4981                   --  valuetypes).
4982
4983                   or else ((not Ext_Name_Case or else VM_Target /= CLI_Target)
4984                              and then (Get_Character (C) = ','
4985                                          or else
4986                                        Get_Character (C) = '\'))
4987                  or else (VM_Target /= CLI_Target
4988                             and then (Get_Character (C) = ' '
4989                                         or else
4990                                       Get_Character (C) = '/'))
4991                then
4992                   Error_Msg
4993                     ("?interface name contains illegal character",
4994                      Sloc (SN) + Source_Ptr (J));
4995                end if;
4996             end loop;
4997          end Check_Form_Of_Interface_Name;
4998
4999       --  Start of processing for Process_Interface_Name
5000
5001       begin
5002          if No (Link_Arg) then
5003             if No (Ext_Arg) then
5004                if VM_Target = CLI_Target
5005                  and then Ekind (Subprogram_Def) = E_Package
5006                  and then Nkind (Parent (Subprogram_Def)) =
5007                                                  N_Package_Specification
5008                  and then Present (Generic_Parent (Parent (Subprogram_Def)))
5009                then
5010                   Set_Interface_Name
5011                      (Subprogram_Def,
5012                       Interface_Name
5013                         (Generic_Parent (Parent (Subprogram_Def))));
5014                end if;
5015
5016                return;
5017
5018             elsif Chars (Ext_Arg) = Name_Link_Name then
5019                Ext_Nam  := Empty;
5020                Link_Nam := Expression (Ext_Arg);
5021
5022             else
5023                Check_Optional_Identifier (Ext_Arg, Name_External_Name);
5024                Ext_Nam  := Expression (Ext_Arg);
5025                Link_Nam := Empty;
5026             end if;
5027
5028          else
5029             Check_Optional_Identifier (Ext_Arg,  Name_External_Name);
5030             Check_Optional_Identifier (Link_Arg, Name_Link_Name);
5031             Ext_Nam  := Expression (Ext_Arg);
5032             Link_Nam := Expression (Link_Arg);
5033          end if;
5034
5035          --  Check expressions for external name and link name are static
5036
5037          if Present (Ext_Nam) then
5038             Check_Arg_Is_Static_Expression (Ext_Nam, Standard_String);
5039             Check_Form_Of_Interface_Name (Ext_Nam, Ext_Name_Case => True);
5040
5041             --  Verify that external name is not the name of a local entity,
5042             --  which would hide the imported one and could lead to run-time
5043             --  surprises. The problem can only arise for entities declared in
5044             --  a package body (otherwise the external name is fully qualified
5045             --  and will not conflict).
5046
5047             declare
5048                Nam : Name_Id;
5049                E   : Entity_Id;
5050                Par : Node_Id;
5051
5052             begin
5053                if Prag_Id = Pragma_Import then
5054                   String_To_Name_Buffer (Strval (Expr_Value_S (Ext_Nam)));
5055                   Nam := Name_Find;
5056                   E   := Entity_Id (Get_Name_Table_Info (Nam));
5057
5058                   if Nam /= Chars (Subprogram_Def)
5059                     and then Present (E)
5060                     and then not Is_Overloadable (E)
5061                     and then Is_Immediately_Visible (E)
5062                     and then not Is_Imported (E)
5063                     and then Ekind (Scope (E)) = E_Package
5064                   then
5065                      Par := Parent (E);
5066                      while Present (Par) loop
5067                         if Nkind (Par) = N_Package_Body then
5068                            Error_Msg_Sloc := Sloc (E);
5069                            Error_Msg_NE
5070                              ("imported entity is hidden by & declared#",
5071                               Ext_Arg, E);
5072                            exit;
5073                         end if;
5074
5075                         Par := Parent (Par);
5076                      end loop;
5077                   end if;
5078                end if;
5079             end;
5080          end if;
5081
5082          if Present (Link_Nam) then
5083             Check_Arg_Is_Static_Expression (Link_Nam, Standard_String);
5084             Check_Form_Of_Interface_Name (Link_Nam, Ext_Name_Case => False);
5085          end if;
5086
5087          --  If there is no link name, just set the external name
5088
5089          if No (Link_Nam) then
5090             Link_Nam := Adjust_External_Name_Case (Expr_Value_S (Ext_Nam));
5091
5092          --  For the Link_Name case, the given literal is preceded by an
5093          --  asterisk, which indicates to GCC that the given name should be
5094          --  taken literally, and in particular that no prepending of
5095          --  underlines should occur, even in systems where this is the
5096          --  normal default.
5097
5098          else
5099             Start_String;
5100
5101             if VM_Target = No_VM then
5102                Store_String_Char (Get_Char_Code ('*'));
5103             end if;
5104
5105             String_Val := Strval (Expr_Value_S (Link_Nam));
5106             Store_String_Chars (String_Val);
5107             Link_Nam :=
5108               Make_String_Literal (Sloc (Link_Nam),
5109                 Strval => End_String);
5110          end if;
5111
5112          --  Set the interface name. If the entity is a generic instance, use
5113          --  its alias, which is the callable entity.
5114
5115          if Is_Generic_Instance (Subprogram_Def) then
5116             Set_Encoded_Interface_Name
5117               (Alias (Get_Base_Subprogram (Subprogram_Def)), Link_Nam);
5118          else
5119             Set_Encoded_Interface_Name
5120               (Get_Base_Subprogram (Subprogram_Def), Link_Nam);
5121          end if;
5122
5123          --  We allow duplicated export names in CIL/Java, as they are always
5124          --  enclosed in a namespace that differentiates them, and overloaded
5125          --  entities are supported by the VM.
5126
5127          if Convention (Subprogram_Def) /= Convention_CIL
5128               and then
5129             Convention (Subprogram_Def) /= Convention_Java
5130          then
5131             Check_Duplicated_Export_Name (Link_Nam);
5132          end if;
5133       end Process_Interface_Name;
5134
5135       -----------------------------------------
5136       -- Process_Interrupt_Or_Attach_Handler --
5137       -----------------------------------------
5138
5139       procedure Process_Interrupt_Or_Attach_Handler is
5140          Arg1_X       : constant Node_Id   := Get_Pragma_Arg (Arg1);
5141          Handler_Proc : constant Entity_Id := Entity (Arg1_X);
5142          Proc_Scope   : constant Entity_Id := Scope (Handler_Proc);
5143
5144       begin
5145          Set_Is_Interrupt_Handler (Handler_Proc);
5146
5147          --  If the pragma is not associated with a handler procedure within a
5148          --  protected type, then it must be for a nonprotected procedure for
5149          --  the AAMP target, in which case we don't associate a representation
5150          --  item with the procedure's scope.
5151
5152          if Ekind (Proc_Scope) = E_Protected_Type then
5153             if Prag_Id = Pragma_Interrupt_Handler
5154                  or else
5155                Prag_Id = Pragma_Attach_Handler
5156             then
5157                Record_Rep_Item (Proc_Scope, N);
5158             end if;
5159          end if;
5160       end Process_Interrupt_Or_Attach_Handler;
5161
5162       --------------------------------------------------
5163       -- Process_Restrictions_Or_Restriction_Warnings --
5164       --------------------------------------------------
5165
5166       --  Note: some of the simple identifier cases were handled in par-prag,
5167       --  but it is harmless (and more straightforward) to simply handle all
5168       --  cases here, even if it means we repeat a bit of work in some cases.
5169
5170       procedure Process_Restrictions_Or_Restriction_Warnings
5171         (Warn : Boolean)
5172       is
5173          Arg   : Node_Id;
5174          R_Id  : Restriction_Id;
5175          Id    : Name_Id;
5176          Expr  : Node_Id;
5177          Val   : Uint;
5178
5179          procedure Check_Unit_Name (N : Node_Id);
5180          --  Checks unit name parameter for No_Dependence. Returns if it has
5181          --  an appropriate form, otherwise raises pragma argument error.
5182
5183          ---------------------
5184          -- Check_Unit_Name --
5185          ---------------------
5186
5187          procedure Check_Unit_Name (N : Node_Id) is
5188          begin
5189             if Nkind (N) = N_Selected_Component then
5190                Check_Unit_Name (Prefix (N));
5191                Check_Unit_Name (Selector_Name (N));
5192
5193             elsif Nkind (N) = N_Identifier then
5194                return;
5195
5196             else
5197                Error_Pragma_Arg
5198                  ("wrong form for unit name for No_Dependence", N);
5199             end if;
5200          end Check_Unit_Name;
5201
5202       --  Start of processing for Process_Restrictions_Or_Restriction_Warnings
5203
5204       begin
5205          --  Ignore all Restrictions pragma in CodePeer mode
5206
5207          if CodePeer_Mode then
5208             return;
5209          end if;
5210
5211          Check_Ada_83_Warning;
5212          Check_At_Least_N_Arguments (1);
5213          Check_Valid_Configuration_Pragma;
5214
5215          Arg := Arg1;
5216          while Present (Arg) loop
5217             Id := Chars (Arg);
5218             Expr := Get_Pragma_Arg (Arg);
5219
5220             --  Case of no restriction identifier present
5221
5222             if Id = No_Name then
5223                if Nkind (Expr) /= N_Identifier then
5224                   Error_Pragma_Arg
5225                     ("invalid form for restriction", Arg);
5226                end if;
5227
5228                R_Id :=
5229                  Get_Restriction_Id
5230                    (Process_Restriction_Synonyms (Expr));
5231
5232                if R_Id not in All_Boolean_Restrictions then
5233                   Error_Msg_Name_1 := Pname;
5234                   Error_Msg_N
5235                     ("invalid restriction identifier&", Get_Pragma_Arg (Arg));
5236
5237                   --  Check for possible misspelling
5238
5239                   for J in Restriction_Id loop
5240                      declare
5241                         Rnm : constant String := Restriction_Id'Image (J);
5242
5243                      begin
5244                         Name_Buffer (1 .. Rnm'Length) := Rnm;
5245                         Name_Len := Rnm'Length;
5246                         Set_Casing (All_Lower_Case);
5247
5248                         if Is_Bad_Spelling_Of (Chars (Expr), Name_Enter) then
5249                            Set_Casing
5250                              (Identifier_Casing (Current_Source_File));
5251                            Error_Msg_String (1 .. Rnm'Length) :=
5252                              Name_Buffer (1 .. Name_Len);
5253                            Error_Msg_Strlen := Rnm'Length;
5254                            Error_Msg_N -- CODEFIX
5255                              ("\possible misspelling of ""~""",
5256                               Get_Pragma_Arg (Arg));
5257                            exit;
5258                         end if;
5259                      end;
5260                   end loop;
5261
5262                   raise Pragma_Exit;
5263                end if;
5264
5265                if Implementation_Restriction (R_Id) then
5266                   Check_Restriction (No_Implementation_Restrictions, Arg);
5267                end if;
5268
5269                --  If this is a warning, then set the warning unless we already
5270                --  have a real restriction active (we never want a warning to
5271                --  override a real restriction).
5272
5273                if Warn then
5274                   if not Restriction_Active (R_Id) then
5275                      Set_Restriction (R_Id, N);
5276                      Restriction_Warnings (R_Id) := True;
5277                   end if;
5278
5279                --  If real restriction case, then set it and make sure that the
5280                --  restriction warning flag is off, since a real restriction
5281                --  always overrides a warning.
5282
5283                else
5284                   Set_Restriction (R_Id, N);
5285                   Restriction_Warnings (R_Id) := False;
5286                end if;
5287
5288                --  Check for obsolescent restrictions in Ada 2005 mode
5289
5290                if not Warn
5291                  and then Ada_Version >= Ada_2005
5292                  and then (R_Id = No_Asynchronous_Control
5293                             or else
5294                            R_Id = No_Unchecked_Deallocation
5295                             or else
5296                            R_Id = No_Unchecked_Conversion)
5297                then
5298                   Check_Restriction (No_Obsolescent_Features, N);
5299                end if;
5300
5301                --  A very special case that must be processed here: pragma
5302                --  Restrictions (No_Exceptions) turns off all run-time
5303                --  checking. This is a bit dubious in terms of the formal
5304                --  language definition, but it is what is intended by RM
5305                --  H.4(12). Restriction_Warnings never affects generated code
5306                --  so this is done only in the real restriction case.
5307
5308                if R_Id = No_Exceptions and then not Warn then
5309                   Scope_Suppress := (others => True);
5310                end if;
5311
5312             --  Case of No_Dependence => unit-name. Note that the parser
5313             --  already made the necessary entry in the No_Dependence table.
5314
5315             elsif Id = Name_No_Dependence then
5316                Check_Unit_Name (Expr);
5317
5318             --  Case of No_Specification_Of_Aspect => Identifier.
5319
5320             elsif Id = Name_No_Specification_Of_Aspect then
5321                declare
5322                   A_Id : Aspect_Id;
5323
5324                begin
5325                   if Nkind (Expr) /= N_Identifier then
5326                      A_Id := No_Aspect;
5327                   else
5328                      A_Id := Get_Aspect_Id (Chars (Expr));
5329                   end if;
5330
5331                   if A_Id = No_Aspect then
5332                      Error_Pragma_Arg ("invalid restriction name", Arg);
5333                   else
5334                      Set_Restriction_No_Specification_Of_Aspect (Expr, Warn);
5335                   end if;
5336                end;
5337
5338             --  All other cases of restriction identifier present
5339
5340             else
5341                R_Id := Get_Restriction_Id (Process_Restriction_Synonyms (Arg));
5342                Analyze_And_Resolve (Expr, Any_Integer);
5343
5344                if R_Id not in All_Parameter_Restrictions then
5345                   Error_Pragma_Arg
5346                     ("invalid restriction parameter identifier", Arg);
5347
5348                elsif not Is_OK_Static_Expression (Expr) then
5349                   Flag_Non_Static_Expr
5350                     ("value must be static expression!", Expr);
5351                   raise Pragma_Exit;
5352
5353                elsif not Is_Integer_Type (Etype (Expr))
5354                  or else Expr_Value (Expr) < 0
5355                then
5356                   Error_Pragma_Arg
5357                     ("value must be non-negative integer", Arg);
5358                end if;
5359
5360                --  Restriction pragma is active
5361
5362                Val := Expr_Value (Expr);
5363
5364                if not UI_Is_In_Int_Range (Val) then
5365                   Error_Pragma_Arg
5366                     ("pragma ignored, value too large?", Arg);
5367                end if;
5368
5369                --  Warning case. If the real restriction is active, then we
5370                --  ignore the request, since warning never overrides a real
5371                --  restriction. Otherwise we set the proper warning. Note that
5372                --  this circuit sets the warning again if it is already set,
5373                --  which is what we want, since the constant may have changed.
5374
5375                if Warn then
5376                   if not Restriction_Active (R_Id) then
5377                      Set_Restriction
5378                        (R_Id, N, Integer (UI_To_Int (Val)));
5379                      Restriction_Warnings (R_Id) := True;
5380                   end if;
5381
5382                --  Real restriction case, set restriction and make sure warning
5383                --  flag is off since real restriction always overrides warning.
5384
5385                else
5386                   Set_Restriction (R_Id, N, Integer (UI_To_Int (Val)));
5387                   Restriction_Warnings (R_Id) := False;
5388                end if;
5389             end if;
5390
5391             Next (Arg);
5392          end loop;
5393       end Process_Restrictions_Or_Restriction_Warnings;
5394
5395       ---------------------------------
5396       -- Process_Suppress_Unsuppress --
5397       ---------------------------------
5398
5399       --  Note: this procedure makes entries in the check suppress data
5400       --  structures managed by Sem. See spec of package Sem for full
5401       --  details on how we handle recording of check suppression.
5402
5403       procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean) is
5404          C    : Check_Id;
5405          E_Id : Node_Id;
5406          E    : Entity_Id;
5407
5408          In_Package_Spec : constant Boolean :=
5409                              Is_Package_Or_Generic_Package (Current_Scope)
5410                                and then not In_Package_Body (Current_Scope);
5411
5412          procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id);
5413          --  Used to suppress a single check on the given entity
5414
5415          --------------------------------
5416          -- Suppress_Unsuppress_Echeck --
5417          --------------------------------
5418
5419          procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id) is
5420          begin
5421             Set_Checks_May_Be_Suppressed (E);
5422
5423             if In_Package_Spec then
5424                Push_Global_Suppress_Stack_Entry
5425                  (Entity   => E,
5426                   Check    => C,
5427                   Suppress => Suppress_Case);
5428
5429             else
5430                Push_Local_Suppress_Stack_Entry
5431                  (Entity   => E,
5432                   Check    => C,
5433                   Suppress => Suppress_Case);
5434             end if;
5435
5436             --  If this is a first subtype, and the base type is distinct,
5437             --  then also set the suppress flags on the base type.
5438
5439             if Is_First_Subtype (E)
5440               and then Etype (E) /= E
5441             then
5442                Suppress_Unsuppress_Echeck (Etype (E), C);
5443             end if;
5444          end Suppress_Unsuppress_Echeck;
5445
5446       --  Start of processing for Process_Suppress_Unsuppress
5447
5448       begin
5449          --  Ignore pragma Suppress/Unsuppress in CodePeer and Alfa modes on
5450          --  user code: we want to generate checks for analysis purposes, as
5451          --  set respectively by -gnatC and -gnatd.F
5452
5453          if (CodePeer_Mode or Alfa_Mode)
5454            and then Comes_From_Source (N)
5455          then
5456             return;
5457          end if;
5458
5459          --  Suppress/Unsuppress can appear as a configuration pragma, or in a
5460          --  declarative part or a package spec (RM 11.5(5)).
5461
5462          if not Is_Configuration_Pragma then
5463             Check_Is_In_Decl_Part_Or_Package_Spec;
5464          end if;
5465
5466          Check_At_Least_N_Arguments (1);
5467          Check_At_Most_N_Arguments (2);
5468          Check_No_Identifier (Arg1);
5469          Check_Arg_Is_Identifier (Arg1);
5470
5471          C := Get_Check_Id (Chars (Get_Pragma_Arg (Arg1)));
5472
5473          if C = No_Check_Id then
5474             Error_Pragma_Arg
5475               ("argument of pragma% is not valid check name", Arg1);
5476          end if;
5477
5478          if not Suppress_Case
5479            and then (C = All_Checks or else C = Overflow_Check)
5480          then
5481             Opt.Overflow_Checks_Unsuppressed := True;
5482          end if;
5483
5484          if Arg_Count = 1 then
5485
5486             --  Make an entry in the local scope suppress table. This is the
5487             --  table that directly shows the current value of the scope
5488             --  suppress check for any check id value.
5489
5490             if C = All_Checks then
5491
5492                --  For All_Checks, we set all specific predefined checks with
5493                --  the exception of Elaboration_Check, which is handled
5494                --  specially because of not wanting All_Checks to have the
5495                --  effect of deactivating static elaboration order processing.
5496
5497                for J in Scope_Suppress'Range loop
5498                   if J /= Elaboration_Check then
5499                      Scope_Suppress (J) := Suppress_Case;
5500                   end if;
5501                end loop;
5502
5503             --  If not All_Checks, and predefined check, then set appropriate
5504             --  scope entry. Note that we will set Elaboration_Check if this
5505             --  is explicitly specified.
5506
5507             elsif C in Predefined_Check_Id then
5508                Scope_Suppress (C) := Suppress_Case;
5509             end if;
5510
5511             --  Also make an entry in the Local_Entity_Suppress table
5512
5513             Push_Local_Suppress_Stack_Entry
5514               (Entity   => Empty,
5515                Check    => C,
5516                Suppress => Suppress_Case);
5517
5518          --  Case of two arguments present, where the check is suppressed for
5519          --  a specified entity (given as the second argument of the pragma)
5520
5521          else
5522             --  This is obsolescent in Ada 2005 mode
5523
5524             if Ada_Version >= Ada_2005 then
5525                Check_Restriction (No_Obsolescent_Features, Arg2);
5526             end if;
5527
5528             Check_Optional_Identifier (Arg2, Name_On);
5529             E_Id := Get_Pragma_Arg (Arg2);
5530             Analyze (E_Id);
5531
5532             if not Is_Entity_Name (E_Id) then
5533                Error_Pragma_Arg
5534                  ("second argument of pragma% must be entity name", Arg2);
5535             end if;
5536
5537             E := Entity (E_Id);
5538
5539             if E = Any_Id then
5540                return;
5541             end if;
5542
5543             --  Enforce RM 11.5(7) which requires that for a pragma that
5544             --  appears within a package spec, the named entity must be
5545             --  within the package spec. We allow the package name itself
5546             --  to be mentioned since that makes sense, although it is not
5547             --  strictly allowed by 11.5(7).
5548
5549             if In_Package_Spec
5550               and then E /= Current_Scope
5551               and then Scope (E) /= Current_Scope
5552             then
5553                Error_Pragma_Arg
5554                  ("entity in pragma% is not in package spec (RM 11.5(7))",
5555                   Arg2);
5556             end if;
5557
5558             --  Loop through homonyms. As noted below, in the case of a package
5559             --  spec, only homonyms within the package spec are considered.
5560
5561             loop
5562                Suppress_Unsuppress_Echeck (E, C);
5563
5564                if Is_Generic_Instance (E)
5565                  and then Is_Subprogram (E)
5566                  and then Present (Alias (E))
5567                then
5568                   Suppress_Unsuppress_Echeck (Alias (E), C);
5569                end if;
5570
5571                --  Move to next homonym if not aspect spec case
5572
5573                exit when From_Aspect_Specification (N);
5574                E := Homonym (E);
5575                exit when No (E);
5576
5577                --  If we are within a package specification, the pragma only
5578                --  applies to homonyms in the same scope.
5579
5580                exit when In_Package_Spec
5581                  and then Scope (E) /= Current_Scope;
5582             end loop;
5583          end if;
5584       end Process_Suppress_Unsuppress;
5585
5586       ------------------
5587       -- Set_Exported --
5588       ------------------
5589
5590       procedure Set_Exported (E : Entity_Id; Arg : Node_Id) is
5591       begin
5592          if Is_Imported (E) then
5593             Error_Pragma_Arg
5594               ("cannot export entity& that was previously imported", Arg);
5595
5596          elsif Present (Address_Clause (E)) and then not CodePeer_Mode then
5597             Error_Pragma_Arg
5598               ("cannot export entity& that has an address clause", Arg);
5599          end if;
5600
5601          Set_Is_Exported (E);
5602
5603          --  Generate a reference for entity explicitly, because the
5604          --  identifier may be overloaded and name resolution will not
5605          --  generate one.
5606
5607          Generate_Reference (E, Arg);
5608
5609          --  Deal with exporting non-library level entity
5610
5611          if not Is_Library_Level_Entity (E) then
5612
5613             --  Not allowed at all for subprograms
5614
5615             if Is_Subprogram (E) then
5616                Error_Pragma_Arg ("local subprogram& cannot be exported", Arg);
5617
5618             --  Otherwise set public and statically allocated
5619
5620             else
5621                Set_Is_Public (E);
5622                Set_Is_Statically_Allocated (E);
5623
5624                --  Warn if the corresponding W flag is set and the pragma comes
5625                --  from source. The latter may not be true e.g. on VMS where we
5626                --  expand export pragmas for exception codes associated with
5627                --  imported or exported exceptions. We do not want to generate
5628                --  a warning for something that the user did not write.
5629
5630                if Warn_On_Export_Import
5631                  and then Comes_From_Source (Arg)
5632                then
5633                   Error_Msg_NE
5634                     ("?& has been made static as a result of Export", Arg, E);
5635                   Error_Msg_N
5636                     ("\this usage is non-standard and non-portable", Arg);
5637                end if;
5638             end if;
5639          end if;
5640
5641          if Warn_On_Export_Import and then Is_Type (E) then
5642             Error_Msg_NE ("exporting a type has no effect?", Arg, E);
5643          end if;
5644
5645          if Warn_On_Export_Import and Inside_A_Generic then
5646             Error_Msg_NE
5647               ("all instances of& will have the same external name?", Arg, E);
5648          end if;
5649       end Set_Exported;
5650
5651       ----------------------------------------------
5652       -- Set_Extended_Import_Export_External_Name --
5653       ----------------------------------------------
5654
5655       procedure Set_Extended_Import_Export_External_Name
5656         (Internal_Ent : Entity_Id;
5657          Arg_External : Node_Id)
5658       is
5659          Old_Name : constant Node_Id := Interface_Name (Internal_Ent);
5660          New_Name : Node_Id;
5661
5662       begin
5663          if No (Arg_External) then
5664             return;
5665          end if;
5666
5667          Check_Arg_Is_External_Name (Arg_External);
5668
5669          if Nkind (Arg_External) = N_String_Literal then
5670             if String_Length (Strval (Arg_External)) = 0 then
5671                return;
5672             else
5673                New_Name := Adjust_External_Name_Case (Arg_External);
5674             end if;
5675
5676          elsif Nkind (Arg_External) = N_Identifier then
5677             New_Name := Get_Default_External_Name (Arg_External);
5678
5679          --  Check_Arg_Is_External_Name should let through only identifiers and
5680          --  string literals or static string expressions (which are folded to
5681          --  string literals).
5682
5683          else
5684             raise Program_Error;
5685          end if;
5686
5687          --  If we already have an external name set (by a prior normal Import
5688          --  or Export pragma), then the external names must match
5689
5690          if Present (Interface_Name (Internal_Ent)) then
5691             Check_Matching_Internal_Names : declare
5692                S1 : constant String_Id := Strval (Old_Name);
5693                S2 : constant String_Id := Strval (New_Name);
5694
5695                procedure Mismatch;
5696                --  Called if names do not match
5697
5698                --------------
5699                -- Mismatch --
5700                --------------
5701
5702                procedure Mismatch is
5703                begin
5704                   Error_Msg_Sloc := Sloc (Old_Name);
5705                   Error_Pragma_Arg
5706                     ("external name does not match that given #",
5707                      Arg_External);
5708                end Mismatch;
5709
5710             --  Start of processing for Check_Matching_Internal_Names
5711
5712             begin
5713                if String_Length (S1) /= String_Length (S2) then
5714                   Mismatch;
5715
5716                else
5717                   for J in 1 .. String_Length (S1) loop
5718                      if Get_String_Char (S1, J) /= Get_String_Char (S2, J) then
5719                         Mismatch;
5720                      end if;
5721                   end loop;
5722                end if;
5723             end Check_Matching_Internal_Names;
5724
5725          --  Otherwise set the given name
5726
5727          else
5728             Set_Encoded_Interface_Name (Internal_Ent, New_Name);
5729             Check_Duplicated_Export_Name (New_Name);
5730          end if;
5731       end Set_Extended_Import_Export_External_Name;
5732
5733       ------------------
5734       -- Set_Imported --
5735       ------------------
5736
5737       procedure Set_Imported (E : Entity_Id) is
5738       begin
5739          --  Error message if already imported or exported
5740
5741          if Is_Exported (E) or else Is_Imported (E) then
5742
5743             --  Error if being set Exported twice
5744
5745             if Is_Exported (E) then
5746                Error_Msg_NE ("entity& was previously exported", N, E);
5747
5748             --  OK if Import/Interface case
5749
5750             elsif Import_Interface_Present (N) then
5751                goto OK;
5752
5753             --  Error if being set Imported twice
5754
5755             else
5756                Error_Msg_NE ("entity& was previously imported", N, E);
5757             end if;
5758
5759             Error_Msg_Name_1 := Pname;
5760             Error_Msg_N
5761               ("\(pragma% applies to all previous entities)", N);
5762
5763             Error_Msg_Sloc  := Sloc (E);
5764             Error_Msg_NE ("\import not allowed for& declared#", N, E);
5765
5766          --  Here if not previously imported or exported, OK to import
5767
5768          else
5769             Set_Is_Imported (E);
5770
5771             --  If the entity is an object that is not at the library level,
5772             --  then it is statically allocated. We do not worry about objects
5773             --  with address clauses in this context since they are not really
5774             --  imported in the linker sense.
5775
5776             if Is_Object (E)
5777               and then not Is_Library_Level_Entity (E)
5778               and then No (Address_Clause (E))
5779             then
5780                Set_Is_Statically_Allocated (E);
5781             end if;
5782          end if;
5783
5784          <<OK>> null;
5785       end Set_Imported;
5786
5787       -------------------------
5788       -- Set_Mechanism_Value --
5789       -------------------------
5790
5791       --  Note: the mechanism name has not been analyzed (and cannot indeed be
5792       --  analyzed, since it is semantic nonsense), so we get it in the exact
5793       --  form created by the parser.
5794
5795       procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id) is
5796          Class        : Node_Id;
5797          Param        : Node_Id;
5798          Mech_Name_Id : Name_Id;
5799
5800          procedure Bad_Class;
5801          --  Signal bad descriptor class name
5802
5803          procedure Bad_Mechanism;
5804          --  Signal bad mechanism name
5805
5806          ---------------
5807          -- Bad_Class --
5808          ---------------
5809
5810          procedure Bad_Class is
5811          begin
5812             Error_Pragma_Arg ("unrecognized descriptor class name", Class);
5813          end Bad_Class;
5814
5815          -------------------------
5816          -- Bad_Mechanism_Value --
5817          -------------------------
5818
5819          procedure Bad_Mechanism is
5820          begin
5821             Error_Pragma_Arg ("unrecognized mechanism name", Mech_Name);
5822          end Bad_Mechanism;
5823
5824       --  Start of processing for Set_Mechanism_Value
5825
5826       begin
5827          if Mechanism (Ent) /= Default_Mechanism then
5828             Error_Msg_NE
5829               ("mechanism for & has already been set", Mech_Name, Ent);
5830          end if;
5831
5832          --  MECHANISM_NAME ::= value | reference | descriptor |
5833          --                     short_descriptor
5834
5835          if Nkind (Mech_Name) = N_Identifier then
5836             if Chars (Mech_Name) = Name_Value then
5837                Set_Mechanism (Ent, By_Copy);
5838                return;
5839
5840             elsif Chars (Mech_Name) = Name_Reference then
5841                Set_Mechanism (Ent, By_Reference);
5842                return;
5843
5844             elsif Chars (Mech_Name) = Name_Descriptor then
5845                Check_VMS (Mech_Name);
5846
5847                --  Descriptor => Short_Descriptor if pragma was given
5848
5849                if Short_Descriptors then
5850                   Set_Mechanism (Ent, By_Short_Descriptor);
5851                else
5852                   Set_Mechanism (Ent, By_Descriptor);
5853                end if;
5854
5855                return;
5856
5857             elsif Chars (Mech_Name) = Name_Short_Descriptor then
5858                Check_VMS (Mech_Name);
5859                Set_Mechanism (Ent, By_Short_Descriptor);
5860                return;
5861
5862             elsif Chars (Mech_Name) = Name_Copy then
5863                Error_Pragma_Arg
5864                  ("bad mechanism name, Value assumed", Mech_Name);
5865
5866             else
5867                Bad_Mechanism;
5868             end if;
5869
5870          --  MECHANISM_NAME ::= descriptor (CLASS_NAME) |
5871          --                     short_descriptor (CLASS_NAME)
5872          --  CLASS_NAME     ::= ubs | ubsb | uba | s | sb | a | nca
5873
5874          --  Note: this form is parsed as an indexed component
5875
5876          elsif Nkind (Mech_Name) = N_Indexed_Component then
5877             Class := First (Expressions (Mech_Name));
5878
5879             if Nkind (Prefix (Mech_Name)) /= N_Identifier
5880              or else not (Chars (Prefix (Mech_Name)) = Name_Descriptor or else
5881                           Chars (Prefix (Mech_Name)) = Name_Short_Descriptor)
5882              or else Present (Next (Class))
5883             then
5884                Bad_Mechanism;
5885             else
5886                Mech_Name_Id := Chars (Prefix (Mech_Name));
5887
5888                --  Change Descriptor => Short_Descriptor if pragma was given
5889
5890                if Mech_Name_Id = Name_Descriptor
5891                  and then Short_Descriptors
5892                then
5893                   Mech_Name_Id := Name_Short_Descriptor;
5894                end if;
5895             end if;
5896
5897          --  MECHANISM_NAME ::= descriptor (Class => CLASS_NAME) |
5898          --                     short_descriptor (Class => CLASS_NAME)
5899          --  CLASS_NAME     ::= ubs | ubsb | uba | s | sb | a | nca
5900
5901          --  Note: this form is parsed as a function call
5902
5903          elsif Nkind (Mech_Name) = N_Function_Call then
5904             Param := First (Parameter_Associations (Mech_Name));
5905
5906             if Nkind (Name (Mech_Name)) /= N_Identifier
5907               or else not (Chars (Name (Mech_Name)) = Name_Descriptor or else
5908                            Chars (Name (Mech_Name)) = Name_Short_Descriptor)
5909               or else Present (Next (Param))
5910               or else No (Selector_Name (Param))
5911               or else Chars (Selector_Name (Param)) /= Name_Class
5912             then
5913                Bad_Mechanism;
5914             else
5915                Class := Explicit_Actual_Parameter (Param);
5916                Mech_Name_Id := Chars (Name (Mech_Name));
5917             end if;
5918
5919          else
5920             Bad_Mechanism;
5921          end if;
5922
5923          --  Fall through here with Class set to descriptor class name
5924
5925          Check_VMS (Mech_Name);
5926
5927          if Nkind (Class) /= N_Identifier then
5928             Bad_Class;
5929
5930          elsif Mech_Name_Id = Name_Descriptor
5931            and then Chars (Class) = Name_UBS
5932          then
5933             Set_Mechanism (Ent, By_Descriptor_UBS);
5934
5935          elsif Mech_Name_Id = Name_Descriptor
5936            and then Chars (Class) = Name_UBSB
5937          then
5938             Set_Mechanism (Ent, By_Descriptor_UBSB);
5939
5940          elsif Mech_Name_Id = Name_Descriptor
5941            and then Chars (Class) = Name_UBA
5942          then
5943             Set_Mechanism (Ent, By_Descriptor_UBA);
5944
5945          elsif Mech_Name_Id = Name_Descriptor
5946            and then Chars (Class) = Name_S
5947          then
5948             Set_Mechanism (Ent, By_Descriptor_S);
5949
5950          elsif Mech_Name_Id = Name_Descriptor
5951            and then Chars (Class) = Name_SB
5952          then
5953             Set_Mechanism (Ent, By_Descriptor_SB);
5954
5955          elsif Mech_Name_Id = Name_Descriptor
5956            and then Chars (Class) = Name_A
5957          then
5958             Set_Mechanism (Ent, By_Descriptor_A);
5959
5960          elsif Mech_Name_Id = Name_Descriptor
5961            and then Chars (Class) = Name_NCA
5962          then
5963             Set_Mechanism (Ent, By_Descriptor_NCA);
5964
5965          elsif Mech_Name_Id = Name_Short_Descriptor
5966            and then Chars (Class) = Name_UBS
5967          then
5968             Set_Mechanism (Ent, By_Short_Descriptor_UBS);
5969
5970          elsif Mech_Name_Id = Name_Short_Descriptor
5971            and then Chars (Class) = Name_UBSB
5972          then
5973             Set_Mechanism (Ent, By_Short_Descriptor_UBSB);
5974
5975          elsif Mech_Name_Id = Name_Short_Descriptor
5976            and then Chars (Class) = Name_UBA
5977          then
5978             Set_Mechanism (Ent, By_Short_Descriptor_UBA);
5979
5980          elsif Mech_Name_Id = Name_Short_Descriptor
5981            and then Chars (Class) = Name_S
5982          then
5983             Set_Mechanism (Ent, By_Short_Descriptor_S);
5984
5985          elsif Mech_Name_Id = Name_Short_Descriptor
5986            and then Chars (Class) = Name_SB
5987          then
5988             Set_Mechanism (Ent, By_Short_Descriptor_SB);
5989
5990          elsif Mech_Name_Id = Name_Short_Descriptor
5991            and then Chars (Class) = Name_A
5992          then
5993             Set_Mechanism (Ent, By_Short_Descriptor_A);
5994
5995          elsif Mech_Name_Id = Name_Short_Descriptor
5996            and then Chars (Class) = Name_NCA
5997          then
5998             Set_Mechanism (Ent, By_Short_Descriptor_NCA);
5999
6000          else
6001             Bad_Class;
6002          end if;
6003       end Set_Mechanism_Value;
6004
6005       ---------------------------
6006       -- Set_Ravenscar_Profile --
6007       ---------------------------
6008
6009       --  The tasks to be done here are
6010
6011       --    Set required policies
6012
6013       --      pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
6014       --      pragma Locking_Policy (Ceiling_Locking)
6015
6016       --    Set Detect_Blocking mode
6017
6018       --    Set required restrictions (see System.Rident for detailed list)
6019
6020       --    Set the No_Dependence rules
6021       --      No_Dependence => Ada.Asynchronous_Task_Control
6022       --      No_Dependence => Ada.Calendar
6023       --      No_Dependence => Ada.Execution_Time.Group_Budget
6024       --      No_Dependence => Ada.Execution_Time.Timers
6025       --      No_Dependence => Ada.Task_Attributes
6026       --      No_Dependence => System.Multiprocessors.Dispatching_Domains
6027
6028       procedure Set_Ravenscar_Profile (N : Node_Id) is
6029          Prefix_Entity   : Entity_Id;
6030          Selector_Entity : Entity_Id;
6031          Prefix_Node     : Node_Id;
6032          Node            : Node_Id;
6033
6034       begin
6035          --  pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
6036
6037          if Task_Dispatching_Policy /= ' '
6038            and then Task_Dispatching_Policy /= 'F'
6039          then
6040             Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
6041             Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
6042
6043          --  Set the FIFO_Within_Priorities policy, but always preserve
6044          --  System_Location since we like the error message with the run time
6045          --  name.
6046
6047          else
6048             Task_Dispatching_Policy := 'F';
6049
6050             if Task_Dispatching_Policy_Sloc /= System_Location then
6051                Task_Dispatching_Policy_Sloc := Loc;
6052             end if;
6053          end if;
6054
6055          --  pragma Locking_Policy (Ceiling_Locking)
6056
6057          if Locking_Policy /= ' '
6058            and then Locking_Policy /= 'C'
6059          then
6060             Error_Msg_Sloc := Locking_Policy_Sloc;
6061             Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
6062
6063          --  Set the Ceiling_Locking policy, but preserve System_Location since
6064          --  we like the error message with the run time name.
6065
6066          else
6067             Locking_Policy := 'C';
6068
6069             if Locking_Policy_Sloc /= System_Location then
6070                Locking_Policy_Sloc := Loc;
6071             end if;
6072          end if;
6073
6074          --  pragma Detect_Blocking
6075
6076          Detect_Blocking := True;
6077
6078          --  Set the corresponding restrictions
6079
6080          Set_Profile_Restrictions
6081            (Ravenscar, N, Warn => Treat_Restrictions_As_Warnings);
6082
6083          --  Set the No_Dependence restrictions
6084
6085          --  The following No_Dependence restrictions:
6086          --    No_Dependence => Ada.Asynchronous_Task_Control
6087          --    No_Dependence => Ada.Calendar
6088          --    No_Dependence => Ada.Task_Attributes
6089          --  are already set by previous call to Set_Profile_Restrictions.
6090
6091          --  Set the following restrictions which were added to Ada 2005:
6092          --    No_Dependence => Ada.Execution_Time.Group_Budget
6093          --    No_Dependence => Ada.Execution_Time.Timers
6094
6095          if Ada_Version >= Ada_2005 then
6096             Name_Buffer (1 .. 3) := "ada";
6097             Name_Len := 3;
6098
6099             Prefix_Entity := Make_Identifier (Loc, Name_Find);
6100
6101             Name_Buffer (1 .. 14) := "execution_time";
6102             Name_Len := 14;
6103
6104             Selector_Entity := Make_Identifier (Loc, Name_Find);
6105
6106             Prefix_Node :=
6107               Make_Selected_Component
6108                 (Sloc          => Loc,
6109                  Prefix        => Prefix_Entity,
6110                  Selector_Name => Selector_Entity);
6111
6112             Name_Buffer (1 .. 13) := "group_budgets";
6113             Name_Len := 13;
6114
6115             Selector_Entity := Make_Identifier (Loc, Name_Find);
6116
6117             Node :=
6118               Make_Selected_Component
6119                 (Sloc          => Loc,
6120                  Prefix        => Prefix_Node,
6121                  Selector_Name => Selector_Entity);
6122
6123             Set_Restriction_No_Dependence
6124               (Unit    => Node,
6125                Warn    => Treat_Restrictions_As_Warnings,
6126                Profile => Ravenscar);
6127
6128             Name_Buffer (1 .. 6) := "timers";
6129             Name_Len := 6;
6130
6131             Selector_Entity := Make_Identifier (Loc, Name_Find);
6132
6133             Node :=
6134               Make_Selected_Component
6135                 (Sloc          => Loc,
6136                  Prefix        => Prefix_Node,
6137                  Selector_Name => Selector_Entity);
6138
6139             Set_Restriction_No_Dependence
6140               (Unit    => Node,
6141                Warn    => Treat_Restrictions_As_Warnings,
6142                Profile => Ravenscar);
6143          end if;
6144
6145          --  Set the following restrictions which was added to Ada 2012 (see
6146          --  AI-0171):
6147          --    No_Dependence => System.Multiprocessors.Dispatching_Domains
6148
6149          if Ada_Version >= Ada_2012 then
6150             Name_Buffer (1 .. 6) := "system";
6151             Name_Len := 6;
6152
6153             Prefix_Entity := Make_Identifier (Loc, Name_Find);
6154
6155             Name_Buffer (1 .. 15) := "multiprocessors";
6156             Name_Len := 15;
6157
6158             Selector_Entity := Make_Identifier (Loc, Name_Find);
6159
6160             Prefix_Node :=
6161               Make_Selected_Component
6162                 (Sloc          => Loc,
6163                  Prefix        => Prefix_Entity,
6164                  Selector_Name => Selector_Entity);
6165
6166             Name_Buffer (1 .. 19) := "dispatching_domains";
6167             Name_Len := 19;
6168
6169             Selector_Entity := Make_Identifier (Loc, Name_Find);
6170
6171             Node :=
6172               Make_Selected_Component
6173                 (Sloc          => Loc,
6174                  Prefix        => Prefix_Node,
6175                  Selector_Name => Selector_Entity);
6176
6177             Set_Restriction_No_Dependence
6178               (Unit    => Node,
6179                Warn    => Treat_Restrictions_As_Warnings,
6180                Profile => Ravenscar);
6181          end if;
6182       end Set_Ravenscar_Profile;
6183
6184    --  Start of processing for Analyze_Pragma
6185
6186    begin
6187       --  The following code is a defense against recursion. Not clear that
6188       --  this can happen legitimately, but perhaps some error situations
6189       --  can cause it, and we did see this recursion during testing.
6190
6191       if Analyzed (N) then
6192          return;
6193       else
6194          Set_Analyzed (N, True);
6195       end if;
6196
6197       --  Deal with unrecognized pragma
6198
6199       Pname := Pragma_Name (N);
6200
6201       if not Is_Pragma_Name (Pname) then
6202          if Warn_On_Unrecognized_Pragma then
6203             Error_Msg_Name_1 := Pname;
6204             Error_Msg_N ("?unrecognized pragma%!", Pragma_Identifier (N));
6205
6206             for PN in First_Pragma_Name .. Last_Pragma_Name loop
6207                if Is_Bad_Spelling_Of (Pname, PN) then
6208                   Error_Msg_Name_1 := PN;
6209                   Error_Msg_N -- CODEFIX
6210                     ("\?possible misspelling of %!", Pragma_Identifier (N));
6211                   exit;
6212                end if;
6213             end loop;
6214          end if;
6215
6216          return;
6217       end if;
6218
6219       --  Here to start processing for recognized pragma
6220
6221       Prag_Id := Get_Pragma_Id (Pname);
6222
6223       if Present (Corresponding_Aspect (N)) then
6224          Pname := Chars (Identifier (Corresponding_Aspect (N)));
6225       end if;
6226
6227       --  Preset arguments
6228
6229       Arg_Count := 0;
6230       Arg1      := Empty;
6231       Arg2      := Empty;
6232       Arg3      := Empty;
6233       Arg4      := Empty;
6234
6235       if Present (Pragma_Argument_Associations (N)) then
6236          Arg_Count := List_Length (Pragma_Argument_Associations (N));
6237          Arg1 := First (Pragma_Argument_Associations (N));
6238
6239          if Present (Arg1) then
6240             Arg2 := Next (Arg1);
6241
6242             if Present (Arg2) then
6243                Arg3 := Next (Arg2);
6244
6245                if Present (Arg3) then
6246                   Arg4 := Next (Arg3);
6247                end if;
6248             end if;
6249          end if;
6250       end if;
6251
6252       --  An enumeration type defines the pragmas that are supported by the
6253       --  implementation. Get_Pragma_Id (in package Prag) transforms a name
6254       --  into the corresponding enumeration value for the following case.
6255
6256       case Prag_Id is
6257
6258          -----------------
6259          -- Abort_Defer --
6260          -----------------
6261
6262          --  pragma Abort_Defer;
6263
6264          when Pragma_Abort_Defer =>
6265             GNAT_Pragma;
6266             Check_Arg_Count (0);
6267
6268             --  The only required semantic processing is to check the
6269             --  placement. This pragma must appear at the start of the
6270             --  statement sequence of a handled sequence of statements.
6271
6272             if Nkind (Parent (N)) /= N_Handled_Sequence_Of_Statements
6273               or else N /= First (Statements (Parent (N)))
6274             then
6275                Pragma_Misplaced;
6276             end if;
6277
6278          ------------
6279          -- Ada_83 --
6280          ------------
6281
6282          --  pragma Ada_83;
6283
6284          --  Note: this pragma also has some specific processing in Par.Prag
6285          --  because we want to set the Ada version mode during parsing.
6286
6287          when Pragma_Ada_83 =>
6288             GNAT_Pragma;
6289             Check_Arg_Count (0);
6290
6291             --  We really should check unconditionally for proper configuration
6292             --  pragma placement, since we really don't want mixed Ada modes
6293             --  within a single unit, and the GNAT reference manual has always
6294             --  said this was a configuration pragma, but we did not check and
6295             --  are hesitant to add the check now.
6296
6297             --  However, we really cannot tolerate mixing Ada 2005 or Ada 2012
6298             --  with Ada 83 or Ada 95, so we must check if we are in Ada 2005
6299             --  or Ada 2012 mode.
6300
6301             if Ada_Version >= Ada_2005 then
6302                Check_Valid_Configuration_Pragma;
6303             end if;
6304
6305             --  Now set Ada 83 mode
6306
6307             Ada_Version := Ada_83;
6308             Ada_Version_Explicit := Ada_Version;
6309
6310          ------------
6311          -- Ada_95 --
6312          ------------
6313
6314          --  pragma Ada_95;
6315
6316          --  Note: this pragma also has some specific processing in Par.Prag
6317          --  because we want to set the Ada 83 version mode during parsing.
6318
6319          when Pragma_Ada_95 =>
6320             GNAT_Pragma;
6321             Check_Arg_Count (0);
6322
6323             --  We really should check unconditionally for proper configuration
6324             --  pragma placement, since we really don't want mixed Ada modes
6325             --  within a single unit, and the GNAT reference manual has always
6326             --  said this was a configuration pragma, but we did not check and
6327             --  are hesitant to add the check now.
6328
6329             --  However, we really cannot tolerate mixing Ada 2005 with Ada 83
6330             --  or Ada 95, so we must check if we are in Ada 2005 mode.
6331
6332             if Ada_Version >= Ada_2005 then
6333                Check_Valid_Configuration_Pragma;
6334             end if;
6335
6336             --  Now set Ada 95 mode
6337
6338             Ada_Version := Ada_95;
6339             Ada_Version_Explicit := Ada_Version;
6340
6341          ---------------------
6342          -- Ada_05/Ada_2005 --
6343          ---------------------
6344
6345          --  pragma Ada_05;
6346          --  pragma Ada_05 (LOCAL_NAME);
6347
6348          --  pragma Ada_2005;
6349          --  pragma Ada_2005 (LOCAL_NAME):
6350
6351          --  Note: these pragmas also have some specific processing in Par.Prag
6352          --  because we want to set the Ada 2005 version mode during parsing.
6353
6354          when Pragma_Ada_05 | Pragma_Ada_2005 => declare
6355             E_Id : Node_Id;
6356
6357          begin
6358             GNAT_Pragma;
6359
6360             if Arg_Count = 1 then
6361                Check_Arg_Is_Local_Name (Arg1);
6362                E_Id := Get_Pragma_Arg (Arg1);
6363
6364                if Etype (E_Id) = Any_Type then
6365                   return;
6366                end if;
6367
6368                Set_Is_Ada_2005_Only (Entity (E_Id));
6369
6370             else
6371                Check_Arg_Count (0);
6372
6373                --  For Ada_2005 we unconditionally enforce the documented
6374                --  configuration pragma placement, since we do not want to
6375                --  tolerate mixed modes in a unit involving Ada 2005. That
6376                --  would cause real difficulties for those cases where there
6377                --  are incompatibilities between Ada 95 and Ada 2005.
6378
6379                Check_Valid_Configuration_Pragma;
6380
6381                --  Now set appropriate Ada mode
6382
6383                Ada_Version          := Ada_2005;
6384                Ada_Version_Explicit := Ada_2005;
6385             end if;
6386          end;
6387
6388          ---------------------
6389          -- Ada_12/Ada_2012 --
6390          ---------------------
6391
6392          --  pragma Ada_12;
6393          --  pragma Ada_12 (LOCAL_NAME);
6394
6395          --  pragma Ada_2012;
6396          --  pragma Ada_2012 (LOCAL_NAME):
6397
6398          --  Note: these pragmas also have some specific processing in Par.Prag
6399          --  because we want to set the Ada 2012 version mode during parsing.
6400
6401          when Pragma_Ada_12 | Pragma_Ada_2012 => declare
6402             E_Id : Node_Id;
6403
6404          begin
6405             GNAT_Pragma;
6406
6407             if Arg_Count = 1 then
6408                Check_Arg_Is_Local_Name (Arg1);
6409                E_Id := Get_Pragma_Arg (Arg1);
6410
6411                if Etype (E_Id) = Any_Type then
6412                   return;
6413                end if;
6414
6415                Set_Is_Ada_2012_Only (Entity (E_Id));
6416
6417             else
6418                Check_Arg_Count (0);
6419
6420                --  For Ada_2012 we unconditionally enforce the documented
6421                --  configuration pragma placement, since we do not want to
6422                --  tolerate mixed modes in a unit involving Ada 2012. That
6423                --  would cause real difficulties for those cases where there
6424                --  are incompatibilities between Ada 95 and Ada 2012. We could
6425                --  allow mixing of Ada 2005 and Ada 2012 but it's not worth it.
6426
6427                Check_Valid_Configuration_Pragma;
6428
6429                --  Now set appropriate Ada mode
6430
6431                Ada_Version          := Ada_2012;
6432                Ada_Version_Explicit := Ada_2012;
6433             end if;
6434          end;
6435
6436          ----------------------
6437          -- All_Calls_Remote --
6438          ----------------------
6439
6440          --  pragma All_Calls_Remote [(library_package_NAME)];
6441
6442          when Pragma_All_Calls_Remote => All_Calls_Remote : declare
6443             Lib_Entity : Entity_Id;
6444
6445          begin
6446             Check_Ada_83_Warning;
6447             Check_Valid_Library_Unit_Pragma;
6448
6449             if Nkind (N) = N_Null_Statement then
6450                return;
6451             end if;
6452
6453             Lib_Entity := Find_Lib_Unit_Name;
6454
6455             --  This pragma should only apply to a RCI unit (RM E.2.3(23))
6456
6457             if Present (Lib_Entity)
6458               and then not Debug_Flag_U
6459             then
6460                if not Is_Remote_Call_Interface (Lib_Entity) then
6461                   Error_Pragma ("pragma% only apply to rci unit");
6462
6463                --  Set flag for entity of the library unit
6464
6465                else
6466                   Set_Has_All_Calls_Remote (Lib_Entity);
6467                end if;
6468
6469             end if;
6470          end All_Calls_Remote;
6471
6472          --------------
6473          -- Annotate --
6474          --------------
6475
6476          --  pragma Annotate (IDENTIFIER [, IDENTIFIER {, ARG}]);
6477          --  ARG ::= NAME | EXPRESSION
6478
6479          --  The first two arguments are by convention intended to refer to an
6480          --  external tool and a tool-specific function. These arguments are
6481          --  not analyzed.
6482
6483          when Pragma_Annotate => Annotate : declare
6484             Arg : Node_Id;
6485             Exp : Node_Id;
6486
6487          begin
6488             GNAT_Pragma;
6489             Check_At_Least_N_Arguments (1);
6490             Check_Arg_Is_Identifier (Arg1);
6491             Check_No_Identifiers;
6492             Store_Note (N);
6493
6494             --  Second parameter is optional, it is never analyzed
6495
6496             if No (Arg2) then
6497                null;
6498
6499             --  Here if we have a second parameter
6500
6501             else
6502                --  Second parameter must be identifier
6503
6504                Check_Arg_Is_Identifier (Arg2);
6505
6506                --  Process remaining parameters if any
6507
6508                Arg := Next (Arg2);
6509                while Present (Arg) loop
6510                   Exp := Get_Pragma_Arg (Arg);
6511                   Analyze (Exp);
6512
6513                   if Is_Entity_Name (Exp) then
6514                      null;
6515
6516                   --  For string literals, we assume Standard_String as the
6517                   --  type, unless the string contains wide or wide_wide
6518                   --  characters.
6519
6520                   elsif Nkind (Exp) = N_String_Literal then
6521                      if Has_Wide_Wide_Character (Exp) then
6522                         Resolve (Exp, Standard_Wide_Wide_String);
6523                      elsif Has_Wide_Character (Exp) then
6524                         Resolve (Exp, Standard_Wide_String);
6525                      else
6526                         Resolve (Exp, Standard_String);
6527                      end if;
6528
6529                   elsif Is_Overloaded (Exp) then
6530                         Error_Pragma_Arg
6531                           ("ambiguous argument for pragma%", Exp);
6532
6533                   else
6534                      Resolve (Exp);
6535                   end if;
6536
6537                   Next (Arg);
6538                end loop;
6539             end if;
6540          end Annotate;
6541
6542          ------------
6543          -- Assert --
6544          ------------
6545
6546          --  pragma Assert ([Check =>] Boolean_EXPRESSION
6547          --                 [, [Message =>] Static_String_EXPRESSION]);
6548
6549          when Pragma_Assert => Assert : declare
6550             Expr : Node_Id;
6551             Newa : List_Id;
6552
6553          begin
6554             Ada_2005_Pragma;
6555             Check_At_Least_N_Arguments (1);
6556             Check_At_Most_N_Arguments (2);
6557             Check_Arg_Order ((Name_Check, Name_Message));
6558             Check_Optional_Identifier (Arg1, Name_Check);
6559
6560             --  We treat pragma Assert as equivalent to:
6561
6562             --    pragma Check (Assertion, condition [, msg]);
6563
6564             --  So rewrite pragma in this manner, and analyze the result
6565
6566             Expr := Get_Pragma_Arg (Arg1);
6567             Newa := New_List (
6568               Make_Pragma_Argument_Association (Loc,
6569                 Expression => Make_Identifier (Loc, Name_Assertion)),
6570
6571               Make_Pragma_Argument_Association (Sloc (Expr),
6572                 Expression => Expr));
6573
6574             if Arg_Count > 1 then
6575                Check_Optional_Identifier (Arg2, Name_Message);
6576                Analyze_And_Resolve (Get_Pragma_Arg (Arg2), Standard_String);
6577                Append_To (Newa, Relocate_Node (Arg2));
6578             end if;
6579
6580             Rewrite (N,
6581               Make_Pragma (Loc,
6582                 Chars                        => Name_Check,
6583                 Pragma_Argument_Associations => Newa));
6584             Analyze (N);
6585          end Assert;
6586
6587          ----------------------
6588          -- Assertion_Policy --
6589          ----------------------
6590
6591          --  pragma Assertion_Policy (Check | Disable |Ignore)
6592
6593          when Pragma_Assertion_Policy => Assertion_Policy : declare
6594             Policy : Node_Id;
6595
6596          begin
6597             Ada_2005_Pragma;
6598             Check_Valid_Configuration_Pragma;
6599             Check_Arg_Count (1);
6600             Check_No_Identifiers;
6601             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Disable, Name_Ignore);
6602
6603             --  We treat pragma Assertion_Policy as equivalent to:
6604
6605             --    pragma Check_Policy (Assertion, policy)
6606
6607             --  So rewrite the pragma in that manner and link on to the chain
6608             --  of Check_Policy pragmas, marking the pragma as analyzed.
6609
6610             Policy := Get_Pragma_Arg (Arg1);
6611
6612             Rewrite (N,
6613               Make_Pragma (Loc,
6614                 Chars => Name_Check_Policy,
6615
6616                 Pragma_Argument_Associations => New_List (
6617                   Make_Pragma_Argument_Association (Loc,
6618                     Expression => Make_Identifier (Loc, Name_Assertion)),
6619
6620                   Make_Pragma_Argument_Association (Loc,
6621                     Expression =>
6622                       Make_Identifier (Sloc (Policy), Chars (Policy))))));
6623
6624             Set_Analyzed (N);
6625             Set_Next_Pragma (N, Opt.Check_Policy_List);
6626             Opt.Check_Policy_List := N;
6627          end Assertion_Policy;
6628
6629          ------------------------------
6630          -- Assume_No_Invalid_Values --
6631          ------------------------------
6632
6633          --  pragma Assume_No_Invalid_Values (On | Off);
6634
6635          when Pragma_Assume_No_Invalid_Values =>
6636             GNAT_Pragma;
6637             Check_Valid_Configuration_Pragma;
6638             Check_Arg_Count (1);
6639             Check_No_Identifiers;
6640             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
6641
6642             if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
6643                Assume_No_Invalid_Values := True;
6644             else
6645                Assume_No_Invalid_Values := False;
6646             end if;
6647
6648          ---------------
6649          -- AST_Entry --
6650          ---------------
6651
6652          --  pragma AST_Entry (entry_IDENTIFIER);
6653
6654          when Pragma_AST_Entry => AST_Entry : declare
6655             Ent : Node_Id;
6656
6657          begin
6658             GNAT_Pragma;
6659             Check_VMS (N);
6660             Check_Arg_Count (1);
6661             Check_No_Identifiers;
6662             Check_Arg_Is_Local_Name (Arg1);
6663             Ent := Entity (Get_Pragma_Arg (Arg1));
6664
6665             --  Note: the implementation of the AST_Entry pragma could handle
6666             --  the entry family case fine, but for now we are consistent with
6667             --  the DEC rules, and do not allow the pragma, which of course
6668             --  has the effect of also forbidding the attribute.
6669
6670             if Ekind (Ent) /= E_Entry then
6671                Error_Pragma_Arg
6672                  ("pragma% argument must be simple entry name", Arg1);
6673
6674             elsif Is_AST_Entry (Ent) then
6675                Error_Pragma_Arg
6676                  ("duplicate % pragma for entry", Arg1);
6677
6678             elsif Has_Homonym (Ent) then
6679                Error_Pragma_Arg
6680                  ("pragma% argument cannot specify overloaded entry", Arg1);
6681
6682             else
6683                declare
6684                   FF : constant Entity_Id := First_Formal (Ent);
6685
6686                begin
6687                   if Present (FF) then
6688                      if Present (Next_Formal (FF)) then
6689                         Error_Pragma_Arg
6690                           ("entry for pragma% can have only one argument",
6691                            Arg1);
6692
6693                      elsif Parameter_Mode (FF) /= E_In_Parameter then
6694                         Error_Pragma_Arg
6695                           ("entry parameter for pragma% must have mode IN",
6696                            Arg1);
6697                      end if;
6698                   end if;
6699                end;
6700
6701                Set_Is_AST_Entry (Ent);
6702             end if;
6703          end AST_Entry;
6704
6705          ------------------
6706          -- Asynchronous --
6707          ------------------
6708
6709          --  pragma Asynchronous (LOCAL_NAME);
6710
6711          when Pragma_Asynchronous => Asynchronous : declare
6712             Nm     : Entity_Id;
6713             C_Ent  : Entity_Id;
6714             L      : List_Id;
6715             S      : Node_Id;
6716             N      : Node_Id;
6717             Formal : Entity_Id;
6718
6719             procedure Process_Async_Pragma;
6720             --  Common processing for procedure and access-to-procedure case
6721
6722             --------------------------
6723             -- Process_Async_Pragma --
6724             --------------------------
6725
6726             procedure Process_Async_Pragma is
6727             begin
6728                if No (L) then
6729                   Set_Is_Asynchronous (Nm);
6730                   return;
6731                end if;
6732
6733                --  The formals should be of mode IN (RM E.4.1(6))
6734
6735                S := First (L);
6736                while Present (S) loop
6737                   Formal := Defining_Identifier (S);
6738
6739                   if Nkind (Formal) = N_Defining_Identifier
6740                     and then Ekind (Formal) /= E_In_Parameter
6741                   then
6742                      Error_Pragma_Arg
6743                        ("pragma% procedure can only have IN parameter",
6744                         Arg1);
6745                   end if;
6746
6747                   Next (S);
6748                end loop;
6749
6750                Set_Is_Asynchronous (Nm);
6751             end Process_Async_Pragma;
6752
6753          --  Start of processing for pragma Asynchronous
6754
6755          begin
6756             Check_Ada_83_Warning;
6757             Check_No_Identifiers;
6758             Check_Arg_Count (1);
6759             Check_Arg_Is_Local_Name (Arg1);
6760
6761             if Debug_Flag_U then
6762                return;
6763             end if;
6764
6765             C_Ent := Cunit_Entity (Current_Sem_Unit);
6766             Analyze (Get_Pragma_Arg (Arg1));
6767             Nm := Entity (Get_Pragma_Arg (Arg1));
6768
6769             if not Is_Remote_Call_Interface (C_Ent)
6770               and then not Is_Remote_Types (C_Ent)
6771             then
6772                --  This pragma should only appear in an RCI or Remote Types
6773                --  unit (RM E.4.1(4)).
6774
6775                Error_Pragma
6776                  ("pragma% not in Remote_Call_Interface or " &
6777                   "Remote_Types unit");
6778             end if;
6779
6780             if Ekind (Nm) = E_Procedure
6781               and then Nkind (Parent (Nm)) = N_Procedure_Specification
6782             then
6783                if not Is_Remote_Call_Interface (Nm) then
6784                   Error_Pragma_Arg
6785                     ("pragma% cannot be applied on non-remote procedure",
6786                      Arg1);
6787                end if;
6788
6789                L := Parameter_Specifications (Parent (Nm));
6790                Process_Async_Pragma;
6791                return;
6792
6793             elsif Ekind (Nm) = E_Function then
6794                Error_Pragma_Arg
6795                  ("pragma% cannot be applied to function", Arg1);
6796
6797             elsif Is_Remote_Access_To_Subprogram_Type (Nm) then
6798                   if Is_Record_Type (Nm) then
6799
6800                   --  A record type that is the Equivalent_Type for a remote
6801                   --  access-to-subprogram type.
6802
6803                      N := Declaration_Node (Corresponding_Remote_Type (Nm));
6804
6805                   else
6806                      --  A non-expanded RAS type (distribution is not enabled)
6807
6808                      N := Declaration_Node (Nm);
6809                   end if;
6810
6811                if Nkind (N) = N_Full_Type_Declaration
6812                  and then Nkind (Type_Definition (N)) =
6813                                      N_Access_Procedure_Definition
6814                then
6815                   L := Parameter_Specifications (Type_Definition (N));
6816                   Process_Async_Pragma;
6817
6818                   if Is_Asynchronous (Nm)
6819                     and then Expander_Active
6820                     and then Get_PCS_Name /= Name_No_DSA
6821                   then
6822                      RACW_Type_Is_Asynchronous (Underlying_RACW_Type (Nm));
6823                   end if;
6824
6825                else
6826                   Error_Pragma_Arg
6827                     ("pragma% cannot reference access-to-function type",
6828                     Arg1);
6829                end if;
6830
6831             --  Only other possibility is Access-to-class-wide type
6832
6833             elsif Is_Access_Type (Nm)
6834               and then Is_Class_Wide_Type (Designated_Type (Nm))
6835             then
6836                Check_First_Subtype (Arg1);
6837                Set_Is_Asynchronous (Nm);
6838                if Expander_Active then
6839                   RACW_Type_Is_Asynchronous (Nm);
6840                end if;
6841
6842             else
6843                Error_Pragma_Arg ("inappropriate argument for pragma%", Arg1);
6844             end if;
6845          end Asynchronous;
6846
6847          ------------
6848          -- Atomic --
6849          ------------
6850
6851          --  pragma Atomic (LOCAL_NAME);
6852
6853          when Pragma_Atomic =>
6854             Process_Atomic_Shared_Volatile;
6855
6856          -----------------------
6857          -- Atomic_Components --
6858          -----------------------
6859
6860          --  pragma Atomic_Components (array_LOCAL_NAME);
6861
6862          --  This processing is shared by Volatile_Components
6863
6864          when Pragma_Atomic_Components   |
6865               Pragma_Volatile_Components =>
6866
6867          Atomic_Components : declare
6868             E_Id : Node_Id;
6869             E    : Entity_Id;
6870             D    : Node_Id;
6871             K    : Node_Kind;
6872
6873          begin
6874             Check_Ada_83_Warning;
6875             Check_No_Identifiers;
6876             Check_Arg_Count (1);
6877             Check_Arg_Is_Local_Name (Arg1);
6878             E_Id := Get_Pragma_Arg (Arg1);
6879
6880             if Etype (E_Id) = Any_Type then
6881                return;
6882             end if;
6883
6884             E := Entity (E_Id);
6885
6886             Check_Duplicate_Pragma (E);
6887
6888             if Rep_Item_Too_Early (E, N)
6889                  or else
6890                Rep_Item_Too_Late (E, N)
6891             then
6892                return;
6893             end if;
6894
6895             D := Declaration_Node (E);
6896             K := Nkind (D);
6897
6898             if (K = N_Full_Type_Declaration and then Is_Array_Type (E))
6899               or else
6900                 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
6901                    and then Nkind (D) = N_Object_Declaration
6902                    and then Nkind (Object_Definition (D)) =
6903                                        N_Constrained_Array_Definition)
6904             then
6905                --  The flag is set on the object, or on the base type
6906
6907                if Nkind (D) /= N_Object_Declaration then
6908                   E := Base_Type (E);
6909                end if;
6910
6911                Set_Has_Volatile_Components (E);
6912
6913                if Prag_Id = Pragma_Atomic_Components then
6914                   Set_Has_Atomic_Components (E);
6915                end if;
6916
6917             else
6918                Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
6919             end if;
6920          end Atomic_Components;
6921
6922          --------------------
6923          -- Attach_Handler --
6924          --------------------
6925
6926          --  pragma Attach_Handler (handler_NAME, EXPRESSION);
6927
6928          when Pragma_Attach_Handler =>
6929             Check_Ada_83_Warning;
6930             Check_No_Identifiers;
6931             Check_Arg_Count (2);
6932
6933             if No_Run_Time_Mode then
6934                Error_Msg_CRT ("Attach_Handler pragma", N);
6935             else
6936                Check_Interrupt_Or_Attach_Handler;
6937
6938                --  The expression that designates the attribute may depend on a
6939                --  discriminant, and is therefore a per- object expression, to
6940                --  be expanded in the init proc. If expansion is enabled, then
6941                --  perform semantic checks on a copy only.
6942
6943                if Expander_Active then
6944                   declare
6945                      Temp : constant Node_Id :=
6946                               New_Copy_Tree (Get_Pragma_Arg (Arg2));
6947                   begin
6948                      Set_Parent (Temp, N);
6949                      Preanalyze_And_Resolve (Temp, RTE (RE_Interrupt_ID));
6950                   end;
6951
6952                else
6953                   Analyze (Get_Pragma_Arg (Arg2));
6954                   Resolve (Get_Pragma_Arg (Arg2), RTE (RE_Interrupt_ID));
6955                end if;
6956
6957                Process_Interrupt_Or_Attach_Handler;
6958             end if;
6959
6960          --------------------
6961          -- C_Pass_By_Copy --
6962          --------------------
6963
6964          --  pragma C_Pass_By_Copy ([Max_Size =>] static_integer_EXPRESSION);
6965
6966          when Pragma_C_Pass_By_Copy => C_Pass_By_Copy : declare
6967             Arg : Node_Id;
6968             Val : Uint;
6969
6970          begin
6971             GNAT_Pragma;
6972             Check_Valid_Configuration_Pragma;
6973             Check_Arg_Count (1);
6974             Check_Optional_Identifier (Arg1, "max_size");
6975
6976             Arg := Get_Pragma_Arg (Arg1);
6977             Check_Arg_Is_Static_Expression (Arg, Any_Integer);
6978
6979             Val := Expr_Value (Arg);
6980
6981             if Val <= 0 then
6982                Error_Pragma_Arg
6983                  ("maximum size for pragma% must be positive", Arg1);
6984
6985             elsif UI_Is_In_Int_Range (Val) then
6986                Default_C_Record_Mechanism := UI_To_Int (Val);
6987
6988             --  If a giant value is given, Int'Last will do well enough.
6989             --  If sometime someone complains that a record larger than
6990             --  two gigabytes is not copied, we will worry about it then!
6991
6992             else
6993                Default_C_Record_Mechanism := Mechanism_Type'Last;
6994             end if;
6995          end C_Pass_By_Copy;
6996
6997          -----------
6998          -- Check --
6999          -----------
7000
7001          --  pragma Check ([Name    =>] IDENTIFIER,
7002          --                [Check   =>] Boolean_EXPRESSION
7003          --              [,[Message =>] String_EXPRESSION]);
7004
7005          when Pragma_Check => Check : declare
7006             Expr : Node_Id;
7007             Eloc : Source_Ptr;
7008
7009             Check_On : Boolean;
7010             --  Set True if category of assertions referenced by Name enabled
7011
7012          begin
7013             GNAT_Pragma;
7014             Check_At_Least_N_Arguments (2);
7015             Check_At_Most_N_Arguments (3);
7016             Check_Optional_Identifier (Arg1, Name_Name);
7017             Check_Optional_Identifier (Arg2, Name_Check);
7018
7019             if Arg_Count = 3 then
7020                Check_Optional_Identifier (Arg3, Name_Message);
7021                Analyze_And_Resolve (Get_Pragma_Arg (Arg3), Standard_String);
7022             end if;
7023
7024             Check_Arg_Is_Identifier (Arg1);
7025
7026             --  Completely ignore if disabled
7027
7028             if Check_Disabled (Chars (Get_Pragma_Arg (Arg1))) then
7029                Rewrite (N, Make_Null_Statement (Loc));
7030                Analyze (N);
7031                return;
7032             end if;
7033
7034             --  Indicate if pragma is enabled. The Original_Node reference here
7035             --  is to deal with pragma Assert rewritten as a Check pragma.
7036
7037             Check_On := Check_Enabled (Chars (Get_Pragma_Arg (Arg1)));
7038
7039             if Check_On then
7040                Set_SCO_Pragma_Enabled (Loc);
7041             end if;
7042
7043             --  If expansion is active and the check is not enabled then we
7044             --  rewrite the Check as:
7045
7046             --    if False and then condition then
7047             --       null;
7048             --    end if;
7049
7050             --  The reason we do this rewriting during semantic analysis rather
7051             --  than as part of normal expansion is that we cannot analyze and
7052             --  expand the code for the boolean expression directly, or it may
7053             --  cause insertion of actions that would escape the attempt to
7054             --  suppress the check code.
7055
7056             --  Note that the Sloc for the if statement corresponds to the
7057             --  argument condition, not the pragma itself. The reason for this
7058             --  is that we may generate a warning if the condition is False at
7059             --  compile time, and we do not want to delete this warning when we
7060             --  delete the if statement.
7061
7062             Expr := Get_Pragma_Arg (Arg2);
7063
7064             if Expander_Active and then not Check_On then
7065                Eloc := Sloc (Expr);
7066
7067                Rewrite (N,
7068                  Make_If_Statement (Eloc,
7069                    Condition =>
7070                      Make_And_Then (Eloc,
7071                        Left_Opnd  => New_Occurrence_Of (Standard_False, Eloc),
7072                        Right_Opnd => Expr),
7073                    Then_Statements => New_List (
7074                      Make_Null_Statement (Eloc))));
7075
7076                Analyze (N);
7077
7078             --  Check is active
7079
7080             else
7081                Analyze_And_Resolve (Expr, Any_Boolean);
7082             end if;
7083          end Check;
7084
7085          ----------------
7086          -- Check_Name --
7087          ----------------
7088
7089          --  pragma Check_Name (check_IDENTIFIER);
7090
7091          when Pragma_Check_Name =>
7092             Check_No_Identifiers;
7093             GNAT_Pragma;
7094             Check_Valid_Configuration_Pragma;
7095             Check_Arg_Count (1);
7096             Check_Arg_Is_Identifier (Arg1);
7097
7098             declare
7099                Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
7100
7101             begin
7102                for J in Check_Names.First .. Check_Names.Last loop
7103                   if Check_Names.Table (J) = Nam then
7104                      return;
7105                   end if;
7106                end loop;
7107
7108                Check_Names.Append (Nam);
7109             end;
7110
7111          ------------------
7112          -- Check_Policy --
7113          ------------------
7114
7115          --  pragma Check_Policy (
7116          --    [Name   =>] IDENTIFIER,
7117          --    [Policy =>] POLICY_IDENTIFIER);
7118
7119          --  POLICY_IDENTIFIER ::= ON | OFF | CHECK | DISABLE | IGNORE
7120
7121          --  Note: this is a configuration pragma, but it is allowed to appear
7122          --  anywhere else.
7123
7124          when Pragma_Check_Policy =>
7125             GNAT_Pragma;
7126             Check_Arg_Count (2);
7127             Check_Optional_Identifier (Arg1, Name_Name);
7128             Check_Optional_Identifier (Arg2, Name_Policy);
7129             Check_Arg_Is_One_Of
7130               (Arg2, Name_On, Name_Off, Name_Check, Name_Disable, Name_Ignore);
7131
7132             --  A Check_Policy pragma can appear either as a configuration
7133             --  pragma, or in a declarative part or a package spec (see RM
7134             --  11.5(5) for rules for Suppress/Unsuppress which are also
7135             --  followed for Check_Policy).
7136
7137             if not Is_Configuration_Pragma then
7138                Check_Is_In_Decl_Part_Or_Package_Spec;
7139             end if;
7140
7141             Set_Next_Pragma (N, Opt.Check_Policy_List);
7142             Opt.Check_Policy_List := N;
7143
7144          ---------------------
7145          -- CIL_Constructor --
7146          ---------------------
7147
7148          --  pragma CIL_Constructor ([Entity =>] LOCAL_NAME);
7149
7150          --  Processing for this pragma is shared with Java_Constructor
7151
7152          -------------
7153          -- Comment --
7154          -------------
7155
7156          --  pragma Comment (static_string_EXPRESSION)
7157
7158          --  Processing for pragma Comment shares the circuitry for pragma
7159          --  Ident. The only differences are that Ident enforces a limit of 31
7160          --  characters on its argument, and also enforces limitations on
7161          --  placement for DEC compatibility. Pragma Comment shares neither of
7162          --  these restrictions.
7163
7164          -------------------
7165          -- Common_Object --
7166          -------------------
7167
7168          --  pragma Common_Object (
7169          --        [Internal =>] LOCAL_NAME
7170          --     [, [External =>] EXTERNAL_SYMBOL]
7171          --     [, [Size     =>] EXTERNAL_SYMBOL]);
7172
7173          --  Processing for this pragma is shared with Psect_Object
7174
7175          ------------------------
7176          -- Compile_Time_Error --
7177          ------------------------
7178
7179          --  pragma Compile_Time_Error
7180          --    (boolean_EXPRESSION, static_string_EXPRESSION);
7181
7182          when Pragma_Compile_Time_Error =>
7183             GNAT_Pragma;
7184             Process_Compile_Time_Warning_Or_Error;
7185
7186          --------------------------
7187          -- Compile_Time_Warning --
7188          --------------------------
7189
7190          --  pragma Compile_Time_Warning
7191          --    (boolean_EXPRESSION, static_string_EXPRESSION);
7192
7193          when Pragma_Compile_Time_Warning =>
7194             GNAT_Pragma;
7195             Process_Compile_Time_Warning_Or_Error;
7196
7197          -------------------
7198          -- Compiler_Unit --
7199          -------------------
7200
7201          when Pragma_Compiler_Unit =>
7202             GNAT_Pragma;
7203             Check_Arg_Count (0);
7204             Set_Is_Compiler_Unit (Get_Source_Unit (N));
7205
7206          -----------------------------
7207          -- Complete_Representation --
7208          -----------------------------
7209
7210          --  pragma Complete_Representation;
7211
7212          when Pragma_Complete_Representation =>
7213             GNAT_Pragma;
7214             Check_Arg_Count (0);
7215
7216             if Nkind (Parent (N)) /= N_Record_Representation_Clause then
7217                Error_Pragma
7218                  ("pragma & must appear within record representation clause");
7219             end if;
7220
7221          ----------------------------
7222          -- Complex_Representation --
7223          ----------------------------
7224
7225          --  pragma Complex_Representation ([Entity =>] LOCAL_NAME);
7226
7227          when Pragma_Complex_Representation => Complex_Representation : declare
7228             E_Id : Entity_Id;
7229             E    : Entity_Id;
7230             Ent  : Entity_Id;
7231
7232          begin
7233             GNAT_Pragma;
7234             Check_Arg_Count (1);
7235             Check_Optional_Identifier (Arg1, Name_Entity);
7236             Check_Arg_Is_Local_Name (Arg1);
7237             E_Id := Get_Pragma_Arg (Arg1);
7238
7239             if Etype (E_Id) = Any_Type then
7240                return;
7241             end if;
7242
7243             E := Entity (E_Id);
7244
7245             if not Is_Record_Type (E) then
7246                Error_Pragma_Arg
7247                  ("argument for pragma% must be record type", Arg1);
7248             end if;
7249
7250             Ent := First_Entity (E);
7251
7252             if No (Ent)
7253               or else No (Next_Entity (Ent))
7254               or else Present (Next_Entity (Next_Entity (Ent)))
7255               or else not Is_Floating_Point_Type (Etype (Ent))
7256               or else Etype (Ent) /= Etype (Next_Entity (Ent))
7257             then
7258                Error_Pragma_Arg
7259                  ("record for pragma% must have two fields of the same "
7260                   & "floating-point type", Arg1);
7261
7262             else
7263                Set_Has_Complex_Representation (Base_Type (E));
7264
7265                --  We need to treat the type has having a non-standard
7266                --  representation, for back-end purposes, even though in
7267                --  general a complex will have the default representation
7268                --  of a record with two real components.
7269
7270                Set_Has_Non_Standard_Rep (Base_Type (E));
7271             end if;
7272          end Complex_Representation;
7273
7274          -------------------------
7275          -- Component_Alignment --
7276          -------------------------
7277
7278          --  pragma Component_Alignment (
7279          --        [Form =>] ALIGNMENT_CHOICE
7280          --     [, [Name =>] type_LOCAL_NAME]);
7281          --
7282          --   ALIGNMENT_CHOICE ::=
7283          --     Component_Size
7284          --   | Component_Size_4
7285          --   | Storage_Unit
7286          --   | Default
7287
7288          when Pragma_Component_Alignment => Component_AlignmentP : declare
7289             Args  : Args_List (1 .. 2);
7290             Names : constant Name_List (1 .. 2) := (
7291                       Name_Form,
7292                       Name_Name);
7293
7294             Form  : Node_Id renames Args (1);
7295             Name  : Node_Id renames Args (2);
7296
7297             Atype : Component_Alignment_Kind;
7298             Typ   : Entity_Id;
7299
7300          begin
7301             GNAT_Pragma;
7302             Gather_Associations (Names, Args);
7303
7304             if No (Form) then
7305                Error_Pragma ("missing Form argument for pragma%");
7306             end if;
7307
7308             Check_Arg_Is_Identifier (Form);
7309
7310             --  Get proper alignment, note that Default = Component_Size on all
7311             --  machines we have so far, and we want to set this value rather
7312             --  than the default value to indicate that it has been explicitly
7313             --  set (and thus will not get overridden by the default component
7314             --  alignment for the current scope)
7315
7316             if Chars (Form) = Name_Component_Size then
7317                Atype := Calign_Component_Size;
7318
7319             elsif Chars (Form) = Name_Component_Size_4 then
7320                Atype := Calign_Component_Size_4;
7321
7322             elsif Chars (Form) = Name_Default then
7323                Atype := Calign_Component_Size;
7324
7325             elsif Chars (Form) = Name_Storage_Unit then
7326                Atype := Calign_Storage_Unit;
7327
7328             else
7329                Error_Pragma_Arg
7330                  ("invalid Form parameter for pragma%", Form);
7331             end if;
7332
7333             --  Case with no name, supplied, affects scope table entry
7334
7335             if No (Name) then
7336                Scope_Stack.Table
7337                  (Scope_Stack.Last).Component_Alignment_Default := Atype;
7338
7339             --  Case of name supplied
7340
7341             else
7342                Check_Arg_Is_Local_Name (Name);
7343                Find_Type (Name);
7344                Typ := Entity (Name);
7345
7346                if Typ = Any_Type
7347                  or else Rep_Item_Too_Early (Typ, N)
7348                then
7349                   return;
7350                else
7351                   Typ := Underlying_Type (Typ);
7352                end if;
7353
7354                if not Is_Record_Type (Typ)
7355                  and then not Is_Array_Type (Typ)
7356                then
7357                   Error_Pragma_Arg
7358                     ("Name parameter of pragma% must identify record or " &
7359                      "array type", Name);
7360                end if;
7361
7362                --  An explicit Component_Alignment pragma overrides an
7363                --  implicit pragma Pack, but not an explicit one.
7364
7365                if not Has_Pragma_Pack (Base_Type (Typ)) then
7366                   Set_Is_Packed (Base_Type (Typ), False);
7367                   Set_Component_Alignment (Base_Type (Typ), Atype);
7368                end if;
7369             end if;
7370          end Component_AlignmentP;
7371
7372          ----------------
7373          -- Controlled --
7374          ----------------
7375
7376          --  pragma Controlled (first_subtype_LOCAL_NAME);
7377
7378          when Pragma_Controlled => Controlled : declare
7379             Arg : Node_Id;
7380
7381          begin
7382             Check_No_Identifiers;
7383             Check_Arg_Count (1);
7384             Check_Arg_Is_Local_Name (Arg1);
7385             Arg := Get_Pragma_Arg (Arg1);
7386
7387             if not Is_Entity_Name (Arg)
7388               or else not Is_Access_Type (Entity (Arg))
7389             then
7390                Error_Pragma_Arg ("pragma% requires access type", Arg1);
7391             else
7392                Set_Has_Pragma_Controlled (Base_Type (Entity (Arg)));
7393             end if;
7394          end Controlled;
7395
7396          ----------------
7397          -- Convention --
7398          ----------------
7399
7400          --  pragma Convention ([Convention =>] convention_IDENTIFIER,
7401          --    [Entity =>] LOCAL_NAME);
7402
7403          when Pragma_Convention => Convention : declare
7404             C : Convention_Id;
7405             E : Entity_Id;
7406             pragma Warnings (Off, C);
7407             pragma Warnings (Off, E);
7408          begin
7409             Check_Arg_Order ((Name_Convention, Name_Entity));
7410             Check_Ada_83_Warning;
7411             Check_Arg_Count (2);
7412             Process_Convention (C, E);
7413          end Convention;
7414
7415          ---------------------------
7416          -- Convention_Identifier --
7417          ---------------------------
7418
7419          --  pragma Convention_Identifier ([Name =>] IDENTIFIER,
7420          --    [Convention =>] convention_IDENTIFIER);
7421
7422          when Pragma_Convention_Identifier => Convention_Identifier : declare
7423             Idnam : Name_Id;
7424             Cname : Name_Id;
7425
7426          begin
7427             GNAT_Pragma;
7428             Check_Arg_Order ((Name_Name, Name_Convention));
7429             Check_Arg_Count (2);
7430             Check_Optional_Identifier (Arg1, Name_Name);
7431             Check_Optional_Identifier (Arg2, Name_Convention);
7432             Check_Arg_Is_Identifier (Arg1);
7433             Check_Arg_Is_Identifier (Arg2);
7434             Idnam := Chars (Get_Pragma_Arg (Arg1));
7435             Cname := Chars (Get_Pragma_Arg (Arg2));
7436
7437             if Is_Convention_Name (Cname) then
7438                Record_Convention_Identifier
7439                  (Idnam, Get_Convention_Id (Cname));
7440             else
7441                Error_Pragma_Arg
7442                  ("second arg for % pragma must be convention", Arg2);
7443             end if;
7444          end Convention_Identifier;
7445
7446          ---------------
7447          -- CPP_Class --
7448          ---------------
7449
7450          --  pragma CPP_Class ([Entity =>] local_NAME)
7451
7452          when Pragma_CPP_Class => CPP_Class : declare
7453             Arg : Node_Id;
7454             Typ : Entity_Id;
7455
7456          begin
7457             if Warn_On_Obsolescent_Feature then
7458                Error_Msg_N
7459                  ("'G'N'A'T pragma cpp'_class is now obsolete; replace it" &
7460                   " by pragma import?", N);
7461             end if;
7462
7463             GNAT_Pragma;
7464             Check_Arg_Count (1);
7465             Check_Optional_Identifier (Arg1, Name_Entity);
7466             Check_Arg_Is_Local_Name (Arg1);
7467
7468             Arg := Get_Pragma_Arg (Arg1);
7469             Analyze (Arg);
7470
7471             if Etype (Arg) = Any_Type then
7472                return;
7473             end if;
7474
7475             if not Is_Entity_Name (Arg)
7476               or else not Is_Type (Entity (Arg))
7477             then
7478                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
7479             end if;
7480
7481             Typ := Entity (Arg);
7482
7483             if not Is_Tagged_Type (Typ) then
7484                Error_Pragma_Arg ("pragma% applicable to tagged types ", Arg1);
7485             end if;
7486
7487             --  Types treated as CPP classes must be declared limited (note:
7488             --  this used to be a warning but there is no real benefit to it
7489             --  since we did effectively intend to treat the type as limited
7490             --  anyway).
7491
7492             if not Is_Limited_Type (Typ) then
7493                Error_Msg_N
7494                  ("imported 'C'P'P type must be limited",
7495                   Get_Pragma_Arg (Arg1));
7496             end if;
7497
7498             Set_Is_CPP_Class      (Typ);
7499             Set_Convention        (Typ, Convention_CPP);
7500
7501             --  Imported CPP types must not have discriminants (because C++
7502             --  classes do not have discriminants).
7503
7504             if Has_Discriminants (Typ) then
7505                Error_Msg_N
7506                  ("imported 'C'P'P type cannot have discriminants",
7507                   First (Discriminant_Specifications
7508                           (Declaration_Node (Typ))));
7509             end if;
7510
7511             --  Components of imported CPP types must not have default
7512             --  expressions because the constructor (if any) is in the
7513             --  C++ side.
7514
7515             if Is_Incomplete_Or_Private_Type (Typ)
7516               and then No (Underlying_Type (Typ))
7517             then
7518                --  It should be an error to apply pragma CPP to a private
7519                --  type if the underlying type is not visible (as it is
7520                --  for any representation item). For now, for backward
7521                --  compatibility we do nothing but we cannot check components
7522                --  because they are not available at this stage. All this code
7523                --  will be removed when we cleanup this obsolete GNAT pragma???
7524
7525                null;
7526
7527             else
7528                declare
7529                   Tdef  : constant Node_Id :=
7530                             Type_Definition (Declaration_Node (Typ));
7531                   Clist : Node_Id;
7532                   Comp  : Node_Id;
7533
7534                begin
7535                   if Nkind (Tdef) = N_Record_Definition then
7536                      Clist := Component_List (Tdef);
7537                   else
7538                      pragma Assert (Nkind (Tdef) = N_Derived_Type_Definition);
7539                      Clist := Component_List (Record_Extension_Part (Tdef));
7540                   end if;
7541
7542                   if Present (Clist) then
7543                      Comp := First (Component_Items (Clist));
7544                      while Present (Comp) loop
7545                         if Present (Expression (Comp)) then
7546                            Error_Msg_N
7547                              ("component of imported 'C'P'P type cannot have" &
7548                               " default expression", Expression (Comp));
7549                         end if;
7550
7551                         Next (Comp);
7552                      end loop;
7553                   end if;
7554                end;
7555             end if;
7556          end CPP_Class;
7557
7558          ---------------------
7559          -- CPP_Constructor --
7560          ---------------------
7561
7562          --  pragma CPP_Constructor ([Entity =>] LOCAL_NAME
7563          --    [, [External_Name =>] static_string_EXPRESSION ]
7564          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
7565
7566          when Pragma_CPP_Constructor => CPP_Constructor : declare
7567             Elmt    : Elmt_Id;
7568             Id      : Entity_Id;
7569             Def_Id  : Entity_Id;
7570             Tag_Typ : Entity_Id;
7571
7572          begin
7573             GNAT_Pragma;
7574             Check_At_Least_N_Arguments (1);
7575             Check_At_Most_N_Arguments (3);
7576             Check_Optional_Identifier (Arg1, Name_Entity);
7577             Check_Arg_Is_Local_Name (Arg1);
7578
7579             Id := Get_Pragma_Arg (Arg1);
7580             Find_Program_Unit_Name (Id);
7581
7582             --  If we did not find the name, we are done
7583
7584             if Etype (Id) = Any_Type then
7585                return;
7586             end if;
7587
7588             Def_Id := Entity (Id);
7589
7590             --  Check if already defined as constructor
7591
7592             if Is_Constructor (Def_Id) then
7593                Error_Msg_N
7594                  ("?duplicate argument for pragma 'C'P'P_Constructor", Arg1);
7595                return;
7596             end if;
7597
7598             if Ekind (Def_Id) = E_Function
7599               and then (Is_CPP_Class (Etype (Def_Id))
7600                          or else (Is_Class_Wide_Type (Etype (Def_Id))
7601                                    and then
7602                                   Is_CPP_Class (Root_Type (Etype (Def_Id)))))
7603             then
7604                if Arg_Count >= 2 then
7605                   Set_Imported (Def_Id);
7606                   Set_Is_Public (Def_Id);
7607                   Process_Interface_Name (Def_Id, Arg2, Arg3);
7608                end if;
7609
7610                Set_Has_Completion (Def_Id);
7611                Set_Is_Constructor (Def_Id);
7612
7613                --  Imported C++ constructors are not dispatching primitives
7614                --  because in C++ they don't have a dispatch table slot.
7615                --  However, in Ada the constructor has the profile of a
7616                --  function that returns a tagged type and therefore it has
7617                --  been treated as a primitive operation during semantic
7618                --  analysis. We now remove it from the list of primitive
7619                --  operations of the type.
7620
7621                if Is_Tagged_Type (Etype (Def_Id))
7622                  and then not Is_Class_Wide_Type (Etype (Def_Id))
7623                then
7624                   pragma Assert (Is_Dispatching_Operation (Def_Id));
7625                   Tag_Typ := Etype (Def_Id);
7626
7627                   Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
7628                   while Present (Elmt) and then Node (Elmt) /= Def_Id loop
7629                      Next_Elmt (Elmt);
7630                   end loop;
7631
7632                   Remove_Elmt (Primitive_Operations (Tag_Typ), Elmt);
7633                   Set_Is_Dispatching_Operation (Def_Id, False);
7634                end if;
7635
7636                --  For backward compatibility, if the constructor returns a
7637                --  class wide type, and we internally change the return type to
7638                --  the corresponding root type.
7639
7640                if Is_Class_Wide_Type (Etype (Def_Id)) then
7641                   Set_Etype (Def_Id, Root_Type (Etype (Def_Id)));
7642                end if;
7643             else
7644                Error_Pragma_Arg
7645                  ("pragma% requires function returning a 'C'P'P_Class type",
7646                    Arg1);
7647             end if;
7648          end CPP_Constructor;
7649
7650          -----------------
7651          -- CPP_Virtual --
7652          -----------------
7653
7654          when Pragma_CPP_Virtual => CPP_Virtual : declare
7655          begin
7656             GNAT_Pragma;
7657
7658             if Warn_On_Obsolescent_Feature then
7659                Error_Msg_N
7660                  ("'G'N'A'T pragma cpp'_virtual is now obsolete and has " &
7661                   "no effect?", N);
7662             end if;
7663          end CPP_Virtual;
7664
7665          ----------------
7666          -- CPP_Vtable --
7667          ----------------
7668
7669          when Pragma_CPP_Vtable => CPP_Vtable : declare
7670          begin
7671             GNAT_Pragma;
7672
7673             if Warn_On_Obsolescent_Feature then
7674                Error_Msg_N
7675                  ("'G'N'A'T pragma cpp'_vtable is now obsolete and has " &
7676                   "no effect?", N);
7677             end if;
7678          end CPP_Vtable;
7679
7680          ---------
7681          -- CPU --
7682          ---------
7683
7684          --  pragma CPU (EXPRESSION);
7685
7686          when Pragma_CPU => CPU : declare
7687             P   : constant Node_Id := Parent (N);
7688             Arg : Node_Id;
7689
7690          begin
7691             Ada_2012_Pragma;
7692             Check_No_Identifiers;
7693             Check_Arg_Count (1);
7694
7695             --  Subprogram case
7696
7697             if Nkind (P) = N_Subprogram_Body then
7698                Check_In_Main_Program;
7699
7700                Arg := Get_Pragma_Arg (Arg1);
7701                Analyze_And_Resolve (Arg, Any_Integer);
7702
7703                --  Must be static
7704
7705                if not Is_Static_Expression (Arg) then
7706                   Flag_Non_Static_Expr
7707                     ("main subprogram affinity is not static!", Arg);
7708                   raise Pragma_Exit;
7709
7710                --  If constraint error, then we already signalled an error
7711
7712                elsif Raises_Constraint_Error (Arg) then
7713                   null;
7714
7715                --  Otherwise check in range
7716
7717                else
7718                   declare
7719                      CPU_Id : constant Entity_Id := RTE (RE_CPU_Range);
7720                      --  This is the entity System.Multiprocessors.CPU_Range;
7721
7722                      Val : constant Uint := Expr_Value (Arg);
7723
7724                   begin
7725                      if Val < Expr_Value (Type_Low_Bound (CPU_Id))
7726                           or else
7727                         Val > Expr_Value (Type_High_Bound (CPU_Id))
7728                      then
7729                         Error_Pragma_Arg
7730                           ("main subprogram CPU is out of range", Arg1);
7731                      end if;
7732                   end;
7733                end if;
7734
7735                Set_Main_CPU
7736                     (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
7737
7738             --  Task case
7739
7740             elsif Nkind (P) = N_Task_Definition then
7741                Arg := Get_Pragma_Arg (Arg1);
7742
7743                --  The expression must be analyzed in the special manner
7744                --  described in "Handling of Default and Per-Object
7745                --  Expressions" in sem.ads.
7746
7747                Preanalyze_Spec_Expression (Arg, RTE (RE_CPU_Range));
7748
7749             --  Anything else is incorrect
7750
7751             else
7752                Pragma_Misplaced;
7753             end if;
7754
7755             if Has_Pragma_CPU (P) then
7756                Error_Pragma ("duplicate pragma% not allowed");
7757             else
7758                Set_Has_Pragma_CPU (P, True);
7759
7760                if Nkind (P) = N_Task_Definition then
7761                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
7762                end if;
7763             end if;
7764          end CPU;
7765
7766          -----------
7767          -- Debug --
7768          -----------
7769
7770          --  pragma Debug ([boolean_EXPRESSION,] PROCEDURE_CALL_STATEMENT);
7771
7772          when Pragma_Debug => Debug : declare
7773             Cond : Node_Id;
7774             Call : Node_Id;
7775
7776          begin
7777             GNAT_Pragma;
7778
7779             --  Skip analysis if disabled
7780
7781             if Debug_Pragmas_Disabled then
7782                Rewrite (N, Make_Null_Statement (Loc));
7783                Analyze (N);
7784                return;
7785             end if;
7786
7787             Cond :=
7788               New_Occurrence_Of
7789                 (Boolean_Literals (Debug_Pragmas_Enabled and Expander_Active),
7790                  Loc);
7791
7792             if Debug_Pragmas_Enabled then
7793                Set_SCO_Pragma_Enabled (Loc);
7794             end if;
7795
7796             if Arg_Count = 2 then
7797                Cond :=
7798                  Make_And_Then (Loc,
7799                    Left_Opnd  => Relocate_Node (Cond),
7800                    Right_Opnd => Get_Pragma_Arg (Arg1));
7801                Call := Get_Pragma_Arg (Arg2);
7802             else
7803                Call := Get_Pragma_Arg (Arg1);
7804             end if;
7805
7806             if Nkind_In (Call,
7807                  N_Indexed_Component,
7808                  N_Function_Call,
7809                  N_Identifier,
7810                  N_Selected_Component)
7811             then
7812                --  If this pragma Debug comes from source, its argument was
7813                --  parsed as a name form (which is syntactically identical).
7814                --  Change it to a procedure call statement now.
7815
7816                Change_Name_To_Procedure_Call_Statement (Call);
7817
7818             elsif Nkind (Call) = N_Procedure_Call_Statement then
7819
7820                --  Already in the form of a procedure call statement: nothing
7821                --  to do (could happen in case of an internally generated
7822                --  pragma Debug).
7823
7824                null;
7825
7826             else
7827                --  All other cases: diagnose error
7828
7829                Error_Msg
7830                  ("argument of pragma% is not procedure call", Sloc (Call));
7831                return;
7832             end if;
7833
7834             --  Rewrite into a conditional with an appropriate condition. We
7835             --  wrap the procedure call in a block so that overhead from e.g.
7836             --  use of the secondary stack does not generate execution overhead
7837             --  for suppressed conditions.
7838
7839             Rewrite (N, Make_Implicit_If_Statement (N,
7840               Condition => Cond,
7841                  Then_Statements => New_List (
7842                    Make_Block_Statement (Loc,
7843                      Handled_Statement_Sequence =>
7844                        Make_Handled_Sequence_Of_Statements (Loc,
7845                          Statements => New_List (Relocate_Node (Call)))))));
7846             Analyze (N);
7847          end Debug;
7848
7849          ------------------
7850          -- Debug_Policy --
7851          ------------------
7852
7853          --  pragma Debug_Policy (Check | Ignore)
7854
7855          when Pragma_Debug_Policy =>
7856             GNAT_Pragma;
7857             Check_Arg_Count (1);
7858             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Disable, Name_Ignore);
7859             Debug_Pragmas_Enabled :=
7860               Chars (Get_Pragma_Arg (Arg1)) = Name_Check;
7861             Debug_Pragmas_Disabled :=
7862               Chars (Get_Pragma_Arg (Arg1)) = Name_Disable;
7863
7864          ---------------------
7865          -- Detect_Blocking --
7866          ---------------------
7867
7868          --  pragma Detect_Blocking;
7869
7870          when Pragma_Detect_Blocking =>
7871             Ada_2005_Pragma;
7872             Check_Arg_Count (0);
7873             Check_Valid_Configuration_Pragma;
7874             Detect_Blocking := True;
7875
7876          --------------------------
7877          -- Default_Storage_Pool --
7878          --------------------------
7879
7880          --  pragma Default_Storage_Pool (storage_pool_NAME | null);
7881
7882          when Pragma_Default_Storage_Pool =>
7883             Ada_2012_Pragma;
7884             Check_Arg_Count (1);
7885
7886             --  Default_Storage_Pool can appear as a configuration pragma, or
7887             --  in a declarative part or a package spec.
7888
7889             if not Is_Configuration_Pragma then
7890                Check_Is_In_Decl_Part_Or_Package_Spec;
7891             end if;
7892
7893             --  Case of Default_Storage_Pool (null);
7894
7895             if Nkind (Expression (Arg1)) = N_Null then
7896                Analyze (Expression (Arg1));
7897
7898                --  This is an odd case, this is not really an expression, so
7899                --  we don't have a type for it. So just set the type to Empty.
7900
7901                Set_Etype (Expression (Arg1), Empty);
7902
7903             --  Case of Default_Storage_Pool (storage_pool_NAME);
7904
7905             else
7906                --  If it's a configuration pragma, then the only allowed
7907                --  argument is "null".
7908
7909                if Is_Configuration_Pragma then
7910                   Error_Pragma_Arg ("NULL expected", Arg1);
7911                end if;
7912
7913                --  The expected type for a non-"null" argument is
7914                --  Root_Storage_Pool'Class.
7915
7916                Analyze_And_Resolve
7917                  (Get_Pragma_Arg (Arg1),
7918                   Typ => Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
7919             end if;
7920
7921             --  Finally, record the pool name (or null). Freeze.Freeze_Entity
7922             --  for an access type will use this information to set the
7923             --  appropriate attributes of the access type.
7924
7925             Default_Pool := Expression (Arg1);
7926
7927          ---------------
7928          -- Dimension --
7929          ---------------
7930
7931          when Pragma_Dimension =>
7932             GNAT_Pragma;
7933             Check_Arg_Count (4);
7934             Check_No_Identifiers;
7935             Check_Arg_Is_Local_Name (Arg1);
7936
7937             if not Is_Type (Arg1) then
7938                Error_Pragma ("first argument for pragma% must be subtype");
7939             end if;
7940
7941             Check_Arg_Is_Static_Expression (Arg2, Standard_Integer);
7942             Check_Arg_Is_Static_Expression (Arg3, Standard_Integer);
7943             Check_Arg_Is_Static_Expression (Arg4, Standard_Integer);
7944
7945          -------------------
7946          -- Discard_Names --
7947          -------------------
7948
7949          --  pragma Discard_Names [([On =>] LOCAL_NAME)];
7950
7951          when Pragma_Discard_Names => Discard_Names : declare
7952             E    : Entity_Id;
7953             E_Id : Entity_Id;
7954
7955          begin
7956             Check_Ada_83_Warning;
7957
7958             --  Deal with configuration pragma case
7959
7960             if Arg_Count = 0 and then Is_Configuration_Pragma then
7961                Global_Discard_Names := True;
7962                return;
7963
7964             --  Otherwise, check correct appropriate context
7965
7966             else
7967                Check_Is_In_Decl_Part_Or_Package_Spec;
7968
7969                if Arg_Count = 0 then
7970
7971                   --  If there is no parameter, then from now on this pragma
7972                   --  applies to any enumeration, exception or tagged type
7973                   --  defined in the current declarative part, and recursively
7974                   --  to any nested scope.
7975
7976                   Set_Discard_Names (Current_Scope);
7977                   return;
7978
7979                else
7980                   Check_Arg_Count (1);
7981                   Check_Optional_Identifier (Arg1, Name_On);
7982                   Check_Arg_Is_Local_Name (Arg1);
7983
7984                   E_Id := Get_Pragma_Arg (Arg1);
7985
7986                   if Etype (E_Id) = Any_Type then
7987                      return;
7988                   else
7989                      E := Entity (E_Id);
7990                   end if;
7991
7992                   if (Is_First_Subtype (E)
7993                       and then
7994                         (Is_Enumeration_Type (E) or else Is_Tagged_Type (E)))
7995                     or else Ekind (E) = E_Exception
7996                   then
7997                      Set_Discard_Names (E);
7998                   else
7999                      Error_Pragma_Arg
8000                        ("inappropriate entity for pragma%", Arg1);
8001                   end if;
8002
8003                end if;
8004             end if;
8005          end Discard_Names;
8006
8007          ------------------------
8008          -- Dispatching_Domain --
8009          ------------------------
8010
8011          --  pragma Dispatching_Domain (EXPRESSION);
8012
8013          when Pragma_Dispatching_Domain => Dispatching_Domain : declare
8014             P   : constant Node_Id := Parent (N);
8015             Arg : Node_Id;
8016
8017          begin
8018             Ada_2012_Pragma;
8019             Check_No_Identifiers;
8020             Check_Arg_Count (1);
8021
8022             --  This pragma is born obsolete, but not the aspect
8023
8024             if not From_Aspect_Specification (N) then
8025                Check_Restriction
8026                  (No_Obsolescent_Features, Pragma_Identifier (N));
8027             end if;
8028
8029             if Nkind (P) = N_Task_Definition then
8030                Arg := Get_Pragma_Arg (Arg1);
8031
8032                --  The expression must be analyzed in the special manner
8033                --  described in "Handling of Default and Per-Object
8034                --  Expressions" in sem.ads.
8035
8036                Preanalyze_Spec_Expression (Arg, RTE (RE_Dispatching_Domain));
8037
8038             --  Anything else is incorrect
8039
8040             else
8041                Pragma_Misplaced;
8042             end if;
8043
8044             if Has_Pragma_Dispatching_Domain (P) then
8045                Error_Pragma ("duplicate pragma% not allowed");
8046             else
8047                Set_Has_Pragma_Dispatching_Domain (P, True);
8048
8049                if Nkind (P) = N_Task_Definition then
8050                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
8051                end if;
8052             end if;
8053          end Dispatching_Domain;
8054
8055          ---------------
8056          -- Elaborate --
8057          ---------------
8058
8059          --  pragma Elaborate (library_unit_NAME {, library_unit_NAME});
8060
8061          when Pragma_Elaborate => Elaborate : declare
8062             Arg   : Node_Id;
8063             Citem : Node_Id;
8064
8065          begin
8066             --  Pragma must be in context items list of a compilation unit
8067
8068             if not Is_In_Context_Clause then
8069                Pragma_Misplaced;
8070             end if;
8071
8072             --  Must be at least one argument
8073
8074             if Arg_Count = 0 then
8075                Error_Pragma ("pragma% requires at least one argument");
8076             end if;
8077
8078             --  In Ada 83 mode, there can be no items following it in the
8079             --  context list except other pragmas and implicit with clauses
8080             --  (e.g. those added by use of Rtsfind). In Ada 95 mode, this
8081             --  placement rule does not apply.
8082
8083             if Ada_Version = Ada_83 and then Comes_From_Source (N) then
8084                Citem := Next (N);
8085                while Present (Citem) loop
8086                   if Nkind (Citem) = N_Pragma
8087                     or else (Nkind (Citem) = N_With_Clause
8088                               and then Implicit_With (Citem))
8089                   then
8090                      null;
8091                   else
8092                      Error_Pragma
8093                        ("(Ada 83) pragma% must be at end of context clause");
8094                   end if;
8095
8096                   Next (Citem);
8097                end loop;
8098             end if;
8099
8100             --  Finally, the arguments must all be units mentioned in a with
8101             --  clause in the same context clause. Note we already checked (in
8102             --  Par.Prag) that the arguments are all identifiers or selected
8103             --  components.
8104
8105             Arg := Arg1;
8106             Outer : while Present (Arg) loop
8107                Citem := First (List_Containing (N));
8108                Inner : while Citem /= N loop
8109                   if Nkind (Citem) = N_With_Clause
8110                     and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
8111                   then
8112                      Set_Elaborate_Present (Citem, True);
8113                      Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
8114                      Generate_Reference (Entity (Name (Citem)), Citem);
8115
8116                      --  With the pragma present, elaboration calls on
8117                      --  subprograms from the named unit need no further
8118                      --  checks, as long as the pragma appears in the current
8119                      --  compilation unit. If the pragma appears in some unit
8120                      --  in the context, there might still be a need for an
8121                      --  Elaborate_All_Desirable from the current compilation
8122                      --  to the named unit, so we keep the check enabled.
8123
8124                      if In_Extended_Main_Source_Unit (N) then
8125                         Set_Suppress_Elaboration_Warnings
8126                           (Entity (Name (Citem)));
8127                      end if;
8128
8129                      exit Inner;
8130                   end if;
8131
8132                   Next (Citem);
8133                end loop Inner;
8134
8135                if Citem = N then
8136                   Error_Pragma_Arg
8137                     ("argument of pragma% is not with'ed unit", Arg);
8138                end if;
8139
8140                Next (Arg);
8141             end loop Outer;
8142
8143             --  Give a warning if operating in static mode with -gnatwl
8144             --  (elaboration warnings enabled) switch set.
8145
8146             if Elab_Warnings and not Dynamic_Elaboration_Checks then
8147                Error_Msg_N
8148                  ("?use of pragma Elaborate may not be safe", N);
8149                Error_Msg_N
8150                  ("?use pragma Elaborate_All instead if possible", N);
8151             end if;
8152          end Elaborate;
8153
8154          -------------------
8155          -- Elaborate_All --
8156          -------------------
8157
8158          --  pragma Elaborate_All (library_unit_NAME {, library_unit_NAME});
8159
8160          when Pragma_Elaborate_All => Elaborate_All : declare
8161             Arg   : Node_Id;
8162             Citem : Node_Id;
8163
8164          begin
8165             Check_Ada_83_Warning;
8166
8167             --  Pragma must be in context items list of a compilation unit
8168
8169             if not Is_In_Context_Clause then
8170                Pragma_Misplaced;
8171             end if;
8172
8173             --  Must be at least one argument
8174
8175             if Arg_Count = 0 then
8176                Error_Pragma ("pragma% requires at least one argument");
8177             end if;
8178
8179             --  Note: unlike pragma Elaborate, pragma Elaborate_All does not
8180             --  have to appear at the end of the context clause, but may
8181             --  appear mixed in with other items, even in Ada 83 mode.
8182
8183             --  Final check: the arguments must all be units mentioned in
8184             --  a with clause in the same context clause. Note that we
8185             --  already checked (in Par.Prag) that all the arguments are
8186             --  either identifiers or selected components.
8187
8188             Arg := Arg1;
8189             Outr : while Present (Arg) loop
8190                Citem := First (List_Containing (N));
8191                Innr : while Citem /= N loop
8192                   if Nkind (Citem) = N_With_Clause
8193                     and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
8194                   then
8195                      Set_Elaborate_All_Present (Citem, True);
8196                      Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
8197
8198                      --  Suppress warnings and elaboration checks on the named
8199                      --  unit if the pragma is in the current compilation, as
8200                      --  for pragma Elaborate.
8201
8202                      if In_Extended_Main_Source_Unit (N) then
8203                         Set_Suppress_Elaboration_Warnings
8204                           (Entity (Name (Citem)));
8205                      end if;
8206                      exit Innr;
8207                   end if;
8208
8209                   Next (Citem);
8210                end loop Innr;
8211
8212                if Citem = N then
8213                   Set_Error_Posted (N);
8214                   Error_Pragma_Arg
8215                     ("argument of pragma% is not with'ed unit", Arg);
8216                end if;
8217
8218                Next (Arg);
8219             end loop Outr;
8220          end Elaborate_All;
8221
8222          --------------------
8223          -- Elaborate_Body --
8224          --------------------
8225
8226          --  pragma Elaborate_Body [( library_unit_NAME )];
8227
8228          when Pragma_Elaborate_Body => Elaborate_Body : declare
8229             Cunit_Node : Node_Id;
8230             Cunit_Ent  : Entity_Id;
8231
8232          begin
8233             Check_Ada_83_Warning;
8234             Check_Valid_Library_Unit_Pragma;
8235
8236             if Nkind (N) = N_Null_Statement then
8237                return;
8238             end if;
8239
8240             Cunit_Node := Cunit (Current_Sem_Unit);
8241             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
8242
8243             if Nkind_In (Unit (Cunit_Node), N_Package_Body,
8244                                             N_Subprogram_Body)
8245             then
8246                Error_Pragma ("pragma% must refer to a spec, not a body");
8247             else
8248                Set_Body_Required (Cunit_Node, True);
8249                Set_Has_Pragma_Elaborate_Body (Cunit_Ent);
8250
8251                --  If we are in dynamic elaboration mode, then we suppress
8252                --  elaboration warnings for the unit, since it is definitely
8253                --  fine NOT to do dynamic checks at the first level (and such
8254                --  checks will be suppressed because no elaboration boolean
8255                --  is created for Elaborate_Body packages).
8256
8257                --  But in the static model of elaboration, Elaborate_Body is
8258                --  definitely NOT good enough to ensure elaboration safety on
8259                --  its own, since the body may WITH other units that are not
8260                --  safe from an elaboration point of view, so a client must
8261                --  still do an Elaborate_All on such units.
8262
8263                --  Debug flag -gnatdD restores the old behavior of 3.13, where
8264                --  Elaborate_Body always suppressed elab warnings.
8265
8266                if Dynamic_Elaboration_Checks or Debug_Flag_DD then
8267                   Set_Suppress_Elaboration_Warnings (Cunit_Ent);
8268                end if;
8269             end if;
8270          end Elaborate_Body;
8271
8272          ------------------------
8273          -- Elaboration_Checks --
8274          ------------------------
8275
8276          --  pragma Elaboration_Checks (Static | Dynamic);
8277
8278          when Pragma_Elaboration_Checks =>
8279             GNAT_Pragma;
8280             Check_Arg_Count (1);
8281             Check_Arg_Is_One_Of (Arg1, Name_Static, Name_Dynamic);
8282             Dynamic_Elaboration_Checks :=
8283               (Chars (Get_Pragma_Arg (Arg1)) = Name_Dynamic);
8284
8285          ---------------
8286          -- Eliminate --
8287          ---------------
8288
8289          --  pragma Eliminate (
8290          --      [Unit_Name  =>] IDENTIFIER | SELECTED_COMPONENT,
8291          --    [,[Entity     =>] IDENTIFIER |
8292          --                      SELECTED_COMPONENT |
8293          --                      STRING_LITERAL]
8294          --    [,                OVERLOADING_RESOLUTION]);
8295
8296          --  OVERLOADING_RESOLUTION ::= PARAMETER_AND_RESULT_TYPE_PROFILE |
8297          --                             SOURCE_LOCATION
8298
8299          --  PARAMETER_AND_RESULT_TYPE_PROFILE ::= PROCEDURE_PROFILE |
8300          --                                        FUNCTION_PROFILE
8301
8302          --  PROCEDURE_PROFILE ::= Parameter_Types => PARAMETER_TYPES
8303
8304          --  FUNCTION_PROFILE ::= [Parameter_Types => PARAMETER_TYPES,]
8305          --                       Result_Type => result_SUBTYPE_NAME]
8306
8307          --  PARAMETER_TYPES ::= (SUBTYPE_NAME {, SUBTYPE_NAME})
8308          --  SUBTYPE_NAME    ::= STRING_LITERAL
8309
8310          --  SOURCE_LOCATION ::= Source_Location => SOURCE_TRACE
8311          --  SOURCE_TRACE    ::= STRING_LITERAL
8312
8313          when Pragma_Eliminate => Eliminate : declare
8314             Args  : Args_List (1 .. 5);
8315             Names : constant Name_List (1 .. 5) := (
8316                       Name_Unit_Name,
8317                       Name_Entity,
8318                       Name_Parameter_Types,
8319                       Name_Result_Type,
8320                       Name_Source_Location);
8321
8322             Unit_Name       : Node_Id renames Args (1);
8323             Entity          : Node_Id renames Args (2);
8324             Parameter_Types : Node_Id renames Args (3);
8325             Result_Type     : Node_Id renames Args (4);
8326             Source_Location : Node_Id renames Args (5);
8327
8328          begin
8329             GNAT_Pragma;
8330             Check_Valid_Configuration_Pragma;
8331             Gather_Associations (Names, Args);
8332
8333             if No (Unit_Name) then
8334                Error_Pragma ("missing Unit_Name argument for pragma%");
8335             end if;
8336
8337             if No (Entity)
8338               and then (Present (Parameter_Types)
8339                           or else
8340                         Present (Result_Type)
8341                           or else
8342                         Present (Source_Location))
8343             then
8344                Error_Pragma ("missing Entity argument for pragma%");
8345             end if;
8346
8347             if (Present (Parameter_Types)
8348                   or else
8349                 Present (Result_Type))
8350               and then
8351                 Present (Source_Location)
8352             then
8353                Error_Pragma
8354                  ("parameter profile and source location cannot " &
8355                   "be used together in pragma%");
8356             end if;
8357
8358             Process_Eliminate_Pragma
8359               (N,
8360                Unit_Name,
8361                Entity,
8362                Parameter_Types,
8363                Result_Type,
8364                Source_Location);
8365          end Eliminate;
8366
8367          ------------
8368          -- Export --
8369          ------------
8370
8371          --  pragma Export (
8372          --    [   Convention    =>] convention_IDENTIFIER,
8373          --    [   Entity        =>] local_NAME
8374          --    [, [External_Name =>] static_string_EXPRESSION ]
8375          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
8376
8377          when Pragma_Export => Export : declare
8378             C      : Convention_Id;
8379             Def_Id : Entity_Id;
8380
8381             pragma Warnings (Off, C);
8382
8383          begin
8384             Check_Ada_83_Warning;
8385             Check_Arg_Order
8386               ((Name_Convention,
8387                 Name_Entity,
8388                 Name_External_Name,
8389                 Name_Link_Name));
8390             Check_At_Least_N_Arguments (2);
8391             Check_At_Most_N_Arguments  (4);
8392             Process_Convention (C, Def_Id);
8393
8394             if Ekind (Def_Id) /= E_Constant then
8395                Note_Possible_Modification
8396                  (Get_Pragma_Arg (Arg2), Sure => False);
8397             end if;
8398
8399             Process_Interface_Name (Def_Id, Arg3, Arg4);
8400             Set_Exported (Def_Id, Arg2);
8401
8402             --  If the entity is a deferred constant, propagate the information
8403             --  to the full view, because gigi elaborates the full view only.
8404
8405             if Ekind (Def_Id) = E_Constant
8406               and then Present (Full_View (Def_Id))
8407             then
8408                declare
8409                   Id2 : constant Entity_Id := Full_View (Def_Id);
8410                begin
8411                   Set_Is_Exported    (Id2, Is_Exported          (Def_Id));
8412                   Set_First_Rep_Item (Id2, First_Rep_Item       (Def_Id));
8413                   Set_Interface_Name (Id2, Einfo.Interface_Name (Def_Id));
8414                end;
8415             end if;
8416          end Export;
8417
8418          ----------------------
8419          -- Export_Exception --
8420          ----------------------
8421
8422          --  pragma Export_Exception (
8423          --        [Internal         =>] LOCAL_NAME
8424          --     [, [External         =>] EXTERNAL_SYMBOL]
8425          --     [, [Form     =>] Ada | VMS]
8426          --     [, [Code     =>] static_integer_EXPRESSION]);
8427
8428          when Pragma_Export_Exception => Export_Exception : declare
8429             Args  : Args_List (1 .. 4);
8430             Names : constant Name_List (1 .. 4) := (
8431                       Name_Internal,
8432                       Name_External,
8433                       Name_Form,
8434                       Name_Code);
8435
8436             Internal : Node_Id renames Args (1);
8437             External : Node_Id renames Args (2);
8438             Form     : Node_Id renames Args (3);
8439             Code     : Node_Id renames Args (4);
8440
8441          begin
8442             GNAT_Pragma;
8443
8444             if Inside_A_Generic then
8445                Error_Pragma ("pragma% cannot be used for generic entities");
8446             end if;
8447
8448             Gather_Associations (Names, Args);
8449             Process_Extended_Import_Export_Exception_Pragma (
8450               Arg_Internal => Internal,
8451               Arg_External => External,
8452               Arg_Form     => Form,
8453               Arg_Code     => Code);
8454
8455             if not Is_VMS_Exception (Entity (Internal)) then
8456                Set_Exported (Entity (Internal), Internal);
8457             end if;
8458          end Export_Exception;
8459
8460          ---------------------
8461          -- Export_Function --
8462          ---------------------
8463
8464          --  pragma Export_Function (
8465          --        [Internal         =>] LOCAL_NAME
8466          --     [, [External         =>] EXTERNAL_SYMBOL]
8467          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8468          --     [, [Result_Type      =>] TYPE_DESIGNATOR]
8469          --     [, [Mechanism        =>] MECHANISM]
8470          --     [, [Result_Mechanism =>] MECHANISM_NAME]);
8471
8472          --  EXTERNAL_SYMBOL ::=
8473          --    IDENTIFIER
8474          --  | static_string_EXPRESSION
8475
8476          --  PARAMETER_TYPES ::=
8477          --    null
8478          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8479
8480          --  TYPE_DESIGNATOR ::=
8481          --    subtype_NAME
8482          --  | subtype_Name ' Access
8483
8484          --  MECHANISM ::=
8485          --    MECHANISM_NAME
8486          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8487
8488          --  MECHANISM_ASSOCIATION ::=
8489          --    [formal_parameter_NAME =>] MECHANISM_NAME
8490
8491          --  MECHANISM_NAME ::=
8492          --    Value
8493          --  | Reference
8494          --  | Descriptor [([Class =>] CLASS_NAME)]
8495
8496          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8497
8498          when Pragma_Export_Function => Export_Function : declare
8499             Args  : Args_List (1 .. 6);
8500             Names : constant Name_List (1 .. 6) := (
8501                       Name_Internal,
8502                       Name_External,
8503                       Name_Parameter_Types,
8504                       Name_Result_Type,
8505                       Name_Mechanism,
8506                       Name_Result_Mechanism);
8507
8508             Internal         : Node_Id renames Args (1);
8509             External         : Node_Id renames Args (2);
8510             Parameter_Types  : Node_Id renames Args (3);
8511             Result_Type      : Node_Id renames Args (4);
8512             Mechanism        : Node_Id renames Args (5);
8513             Result_Mechanism : Node_Id renames Args (6);
8514
8515          begin
8516             GNAT_Pragma;
8517             Gather_Associations (Names, Args);
8518             Process_Extended_Import_Export_Subprogram_Pragma (
8519               Arg_Internal         => Internal,
8520               Arg_External         => External,
8521               Arg_Parameter_Types  => Parameter_Types,
8522               Arg_Result_Type      => Result_Type,
8523               Arg_Mechanism        => Mechanism,
8524               Arg_Result_Mechanism => Result_Mechanism);
8525          end Export_Function;
8526
8527          -------------------
8528          -- Export_Object --
8529          -------------------
8530
8531          --  pragma Export_Object (
8532          --        [Internal =>] LOCAL_NAME
8533          --     [, [External =>] EXTERNAL_SYMBOL]
8534          --     [, [Size     =>] EXTERNAL_SYMBOL]);
8535
8536          --  EXTERNAL_SYMBOL ::=
8537          --    IDENTIFIER
8538          --  | static_string_EXPRESSION
8539
8540          --  PARAMETER_TYPES ::=
8541          --    null
8542          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8543
8544          --  TYPE_DESIGNATOR ::=
8545          --    subtype_NAME
8546          --  | subtype_Name ' Access
8547
8548          --  MECHANISM ::=
8549          --    MECHANISM_NAME
8550          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8551
8552          --  MECHANISM_ASSOCIATION ::=
8553          --    [formal_parameter_NAME =>] MECHANISM_NAME
8554
8555          --  MECHANISM_NAME ::=
8556          --    Value
8557          --  | Reference
8558          --  | Descriptor [([Class =>] CLASS_NAME)]
8559
8560          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8561
8562          when Pragma_Export_Object => Export_Object : declare
8563             Args  : Args_List (1 .. 3);
8564             Names : constant Name_List (1 .. 3) := (
8565                       Name_Internal,
8566                       Name_External,
8567                       Name_Size);
8568
8569             Internal : Node_Id renames Args (1);
8570             External : Node_Id renames Args (2);
8571             Size     : Node_Id renames Args (3);
8572
8573          begin
8574             GNAT_Pragma;
8575             Gather_Associations (Names, Args);
8576             Process_Extended_Import_Export_Object_Pragma (
8577               Arg_Internal => Internal,
8578               Arg_External => External,
8579               Arg_Size     => Size);
8580          end Export_Object;
8581
8582          ----------------------
8583          -- Export_Procedure --
8584          ----------------------
8585
8586          --  pragma Export_Procedure (
8587          --        [Internal         =>] LOCAL_NAME
8588          --     [, [External         =>] EXTERNAL_SYMBOL]
8589          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8590          --     [, [Mechanism        =>] MECHANISM]);
8591
8592          --  EXTERNAL_SYMBOL ::=
8593          --    IDENTIFIER
8594          --  | static_string_EXPRESSION
8595
8596          --  PARAMETER_TYPES ::=
8597          --    null
8598          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8599
8600          --  TYPE_DESIGNATOR ::=
8601          --    subtype_NAME
8602          --  | subtype_Name ' Access
8603
8604          --  MECHANISM ::=
8605          --    MECHANISM_NAME
8606          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8607
8608          --  MECHANISM_ASSOCIATION ::=
8609          --    [formal_parameter_NAME =>] MECHANISM_NAME
8610
8611          --  MECHANISM_NAME ::=
8612          --    Value
8613          --  | Reference
8614          --  | Descriptor [([Class =>] CLASS_NAME)]
8615
8616          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8617
8618          when Pragma_Export_Procedure => Export_Procedure : declare
8619             Args  : Args_List (1 .. 4);
8620             Names : constant Name_List (1 .. 4) := (
8621                       Name_Internal,
8622                       Name_External,
8623                       Name_Parameter_Types,
8624                       Name_Mechanism);
8625
8626             Internal        : Node_Id renames Args (1);
8627             External        : Node_Id renames Args (2);
8628             Parameter_Types : Node_Id renames Args (3);
8629             Mechanism       : Node_Id renames Args (4);
8630
8631          begin
8632             GNAT_Pragma;
8633             Gather_Associations (Names, Args);
8634             Process_Extended_Import_Export_Subprogram_Pragma (
8635               Arg_Internal        => Internal,
8636               Arg_External        => External,
8637               Arg_Parameter_Types => Parameter_Types,
8638               Arg_Mechanism       => Mechanism);
8639          end Export_Procedure;
8640
8641          ------------------
8642          -- Export_Value --
8643          ------------------
8644
8645          --  pragma Export_Value (
8646          --     [Value     =>] static_integer_EXPRESSION,
8647          --     [Link_Name =>] static_string_EXPRESSION);
8648
8649          when Pragma_Export_Value =>
8650             GNAT_Pragma;
8651             Check_Arg_Order ((Name_Value, Name_Link_Name));
8652             Check_Arg_Count (2);
8653
8654             Check_Optional_Identifier (Arg1, Name_Value);
8655             Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
8656
8657             Check_Optional_Identifier (Arg2, Name_Link_Name);
8658             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
8659
8660          -----------------------------
8661          -- Export_Valued_Procedure --
8662          -----------------------------
8663
8664          --  pragma Export_Valued_Procedure (
8665          --        [Internal         =>] LOCAL_NAME
8666          --     [, [External         =>] EXTERNAL_SYMBOL,]
8667          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8668          --     [, [Mechanism        =>] MECHANISM]);
8669
8670          --  EXTERNAL_SYMBOL ::=
8671          --    IDENTIFIER
8672          --  | static_string_EXPRESSION
8673
8674          --  PARAMETER_TYPES ::=
8675          --    null
8676          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8677
8678          --  TYPE_DESIGNATOR ::=
8679          --    subtype_NAME
8680          --  | subtype_Name ' Access
8681
8682          --  MECHANISM ::=
8683          --    MECHANISM_NAME
8684          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8685
8686          --  MECHANISM_ASSOCIATION ::=
8687          --    [formal_parameter_NAME =>] MECHANISM_NAME
8688
8689          --  MECHANISM_NAME ::=
8690          --    Value
8691          --  | Reference
8692          --  | Descriptor [([Class =>] CLASS_NAME)]
8693
8694          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8695
8696          when Pragma_Export_Valued_Procedure =>
8697          Export_Valued_Procedure : declare
8698             Args  : Args_List (1 .. 4);
8699             Names : constant Name_List (1 .. 4) := (
8700                       Name_Internal,
8701                       Name_External,
8702                       Name_Parameter_Types,
8703                       Name_Mechanism);
8704
8705             Internal        : Node_Id renames Args (1);
8706             External        : Node_Id renames Args (2);
8707             Parameter_Types : Node_Id renames Args (3);
8708             Mechanism       : Node_Id renames Args (4);
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_Mechanism       => Mechanism);
8718          end Export_Valued_Procedure;
8719
8720          -------------------
8721          -- Extend_System --
8722          -------------------
8723
8724          --  pragma Extend_System ([Name =>] Identifier);
8725
8726          when Pragma_Extend_System => Extend_System : declare
8727          begin
8728             GNAT_Pragma;
8729             Check_Valid_Configuration_Pragma;
8730             Check_Arg_Count (1);
8731             Check_Optional_Identifier (Arg1, Name_Name);
8732             Check_Arg_Is_Identifier (Arg1);
8733
8734             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
8735
8736             if Name_Len > 4
8737               and then Name_Buffer (1 .. 4) = "aux_"
8738             then
8739                if Present (System_Extend_Pragma_Arg) then
8740                   if Chars (Get_Pragma_Arg (Arg1)) =
8741                      Chars (Expression (System_Extend_Pragma_Arg))
8742                   then
8743                      null;
8744                   else
8745                      Error_Msg_Sloc := Sloc (System_Extend_Pragma_Arg);
8746                      Error_Pragma ("pragma% conflicts with that #");
8747                   end if;
8748
8749                else
8750                   System_Extend_Pragma_Arg := Arg1;
8751
8752                   if not GNAT_Mode then
8753                      System_Extend_Unit := Arg1;
8754                   end if;
8755                end if;
8756             else
8757                Error_Pragma ("incorrect name for pragma%, must be Aux_xxx");
8758             end if;
8759          end Extend_System;
8760
8761          ------------------------
8762          -- Extensions_Allowed --
8763          ------------------------
8764
8765          --  pragma Extensions_Allowed (ON | OFF);
8766
8767          when Pragma_Extensions_Allowed =>
8768             GNAT_Pragma;
8769             Check_Arg_Count (1);
8770             Check_No_Identifiers;
8771             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
8772
8773             if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
8774                Extensions_Allowed := True;
8775                Ada_Version := Ada_Version_Type'Last;
8776
8777             else
8778                Extensions_Allowed := False;
8779                Ada_Version := Ada_Version_Explicit;
8780             end if;
8781
8782          --------------
8783          -- External --
8784          --------------
8785
8786          --  pragma External (
8787          --    [   Convention    =>] convention_IDENTIFIER,
8788          --    [   Entity        =>] local_NAME
8789          --    [, [External_Name =>] static_string_EXPRESSION ]
8790          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
8791
8792          when Pragma_External => External : declare
8793                Def_Id : Entity_Id;
8794
8795                C : Convention_Id;
8796                pragma Warnings (Off, C);
8797
8798          begin
8799             GNAT_Pragma;
8800             Check_Arg_Order
8801               ((Name_Convention,
8802                 Name_Entity,
8803                 Name_External_Name,
8804                 Name_Link_Name));
8805             Check_At_Least_N_Arguments (2);
8806             Check_At_Most_N_Arguments  (4);
8807             Process_Convention (C, Def_Id);
8808             Note_Possible_Modification
8809               (Get_Pragma_Arg (Arg2), Sure => False);
8810             Process_Interface_Name (Def_Id, Arg3, Arg4);
8811             Set_Exported (Def_Id, Arg2);
8812          end External;
8813
8814          --------------------------
8815          -- External_Name_Casing --
8816          --------------------------
8817
8818          --  pragma External_Name_Casing (
8819          --    UPPERCASE | LOWERCASE
8820          --    [, AS_IS | UPPERCASE | LOWERCASE]);
8821
8822          when Pragma_External_Name_Casing => External_Name_Casing : declare
8823          begin
8824             GNAT_Pragma;
8825             Check_No_Identifiers;
8826
8827             if Arg_Count = 2 then
8828                Check_Arg_Is_One_Of
8829                  (Arg2, Name_As_Is, Name_Uppercase, Name_Lowercase);
8830
8831                case Chars (Get_Pragma_Arg (Arg2)) is
8832                   when Name_As_Is     =>
8833                      Opt.External_Name_Exp_Casing := As_Is;
8834
8835                   when Name_Uppercase =>
8836                      Opt.External_Name_Exp_Casing := Uppercase;
8837
8838                   when Name_Lowercase =>
8839                      Opt.External_Name_Exp_Casing := Lowercase;
8840
8841                   when others =>
8842                      null;
8843                end case;
8844
8845             else
8846                Check_Arg_Count (1);
8847             end if;
8848
8849             Check_Arg_Is_One_Of (Arg1, Name_Uppercase, Name_Lowercase);
8850
8851             case Chars (Get_Pragma_Arg (Arg1)) is
8852                when Name_Uppercase =>
8853                   Opt.External_Name_Imp_Casing := Uppercase;
8854
8855                when Name_Lowercase =>
8856                   Opt.External_Name_Imp_Casing := Lowercase;
8857
8858                when others =>
8859                   null;
8860             end case;
8861          end External_Name_Casing;
8862
8863          --------------------------
8864          -- Favor_Top_Level --
8865          --------------------------
8866
8867          --  pragma Favor_Top_Level (type_NAME);
8868
8869          when Pragma_Favor_Top_Level => Favor_Top_Level : declare
8870                Named_Entity : Entity_Id;
8871
8872          begin
8873             GNAT_Pragma;
8874             Check_No_Identifiers;
8875             Check_Arg_Count (1);
8876             Check_Arg_Is_Local_Name (Arg1);
8877             Named_Entity := Entity (Get_Pragma_Arg (Arg1));
8878
8879             --  If it's an access-to-subprogram type (in particular, not a
8880             --  subtype), set the flag on that type.
8881
8882             if Is_Access_Subprogram_Type (Named_Entity) then
8883                Set_Can_Use_Internal_Rep (Named_Entity, False);
8884
8885             --  Otherwise it's an error (name denotes the wrong sort of entity)
8886
8887             else
8888                Error_Pragma_Arg
8889                  ("access-to-subprogram type expected",
8890                   Get_Pragma_Arg (Arg1));
8891             end if;
8892          end Favor_Top_Level;
8893
8894          ---------------
8895          -- Fast_Math --
8896          ---------------
8897
8898          --  pragma Fast_Math;
8899
8900          when Pragma_Fast_Math =>
8901             GNAT_Pragma;
8902             Check_No_Identifiers;
8903             Check_Valid_Configuration_Pragma;
8904             Fast_Math := True;
8905
8906          ---------------------------
8907          -- Finalize_Storage_Only --
8908          ---------------------------
8909
8910          --  pragma Finalize_Storage_Only (first_subtype_LOCAL_NAME);
8911
8912          when Pragma_Finalize_Storage_Only => Finalize_Storage : declare
8913             Assoc   : constant Node_Id := Arg1;
8914             Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
8915             Typ     : Entity_Id;
8916
8917          begin
8918             GNAT_Pragma;
8919             Check_No_Identifiers;
8920             Check_Arg_Count (1);
8921             Check_Arg_Is_Local_Name (Arg1);
8922
8923             Find_Type (Type_Id);
8924             Typ := Entity (Type_Id);
8925
8926             if Typ = Any_Type
8927               or else Rep_Item_Too_Early (Typ, N)
8928             then
8929                return;
8930             else
8931                Typ := Underlying_Type (Typ);
8932             end if;
8933
8934             if not Is_Controlled (Typ) then
8935                Error_Pragma ("pragma% must specify controlled type");
8936             end if;
8937
8938             Check_First_Subtype (Arg1);
8939
8940             if Finalize_Storage_Only (Typ) then
8941                Error_Pragma ("duplicate pragma%, only one allowed");
8942
8943             elsif not Rep_Item_Too_Late (Typ, N) then
8944                Set_Finalize_Storage_Only (Base_Type (Typ), True);
8945             end if;
8946          end Finalize_Storage;
8947
8948          --------------------------
8949          -- Float_Representation --
8950          --------------------------
8951
8952          --  pragma Float_Representation (FLOAT_REP[, float_type_LOCAL_NAME]);
8953
8954          --  FLOAT_REP ::= VAX_Float | IEEE_Float
8955
8956          when Pragma_Float_Representation => Float_Representation : declare
8957             Argx : Node_Id;
8958             Digs : Nat;
8959             Ent  : Entity_Id;
8960
8961          begin
8962             GNAT_Pragma;
8963
8964             if Arg_Count = 1 then
8965                Check_Valid_Configuration_Pragma;
8966             else
8967                Check_Arg_Count (2);
8968                Check_Optional_Identifier (Arg2, Name_Entity);
8969                Check_Arg_Is_Local_Name (Arg2);
8970             end if;
8971
8972             Check_No_Identifier (Arg1);
8973             Check_Arg_Is_One_Of (Arg1, Name_VAX_Float, Name_IEEE_Float);
8974
8975             if not OpenVMS_On_Target then
8976                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
8977                   Error_Pragma
8978                     ("?pragma% ignored (applies only to Open'V'M'S)");
8979                end if;
8980
8981                return;
8982             end if;
8983
8984             --  One argument case
8985
8986             if Arg_Count = 1 then
8987                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
8988                   if Opt.Float_Format = 'I' then
8989                      Error_Pragma ("'I'E'E'E format previously specified");
8990                   end if;
8991
8992                   Opt.Float_Format := 'V';
8993
8994                else
8995                   if Opt.Float_Format = 'V' then
8996                      Error_Pragma ("'V'A'X format previously specified");
8997                   end if;
8998
8999                   Opt.Float_Format := 'I';
9000                end if;
9001
9002                Set_Standard_Fpt_Formats;
9003
9004             --  Two argument case
9005
9006             else
9007                Argx := Get_Pragma_Arg (Arg2);
9008
9009                if not Is_Entity_Name (Argx)
9010                  or else not Is_Floating_Point_Type (Entity (Argx))
9011                then
9012                   Error_Pragma_Arg
9013                     ("second argument of% pragma must be floating-point type",
9014                      Arg2);
9015                end if;
9016
9017                Ent  := Entity (Argx);
9018                Digs := UI_To_Int (Digits_Value (Ent));
9019
9020                --  Two arguments, VAX_Float case
9021
9022                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9023                   case Digs is
9024                      when  6 => Set_F_Float (Ent);
9025                      when  9 => Set_D_Float (Ent);
9026                      when 15 => Set_G_Float (Ent);
9027
9028                      when others =>
9029                         Error_Pragma_Arg
9030                           ("wrong digits value, must be 6,9 or 15", Arg2);
9031                   end case;
9032
9033                --  Two arguments, IEEE_Float case
9034
9035                else
9036                   case Digs is
9037                      when  6 => Set_IEEE_Short (Ent);
9038                      when 15 => Set_IEEE_Long  (Ent);
9039
9040                      when others =>
9041                         Error_Pragma_Arg
9042                           ("wrong digits value, must be 6 or 15", Arg2);
9043                   end case;
9044                end if;
9045             end if;
9046          end Float_Representation;
9047
9048          -----------
9049          -- Ident --
9050          -----------
9051
9052          --  pragma Ident (static_string_EXPRESSION)
9053
9054          --  Note: pragma Comment shares this processing. Pragma Comment is
9055          --  identical to Ident, except that the restriction of the argument to
9056          --  31 characters and the placement restrictions are not enforced for
9057          --  pragma Comment.
9058
9059          when Pragma_Ident | Pragma_Comment => Ident : declare
9060             Str : Node_Id;
9061
9062          begin
9063             GNAT_Pragma;
9064             Check_Arg_Count (1);
9065             Check_No_Identifiers;
9066             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
9067             Store_Note (N);
9068
9069             --  For pragma Ident, preserve DEC compatibility by requiring the
9070             --  pragma to appear in a declarative part or package spec.
9071
9072             if Prag_Id = Pragma_Ident then
9073                Check_Is_In_Decl_Part_Or_Package_Spec;
9074             end if;
9075
9076             Str := Expr_Value_S (Get_Pragma_Arg (Arg1));
9077
9078             declare
9079                CS : Node_Id;
9080                GP : Node_Id;
9081
9082             begin
9083                GP := Parent (Parent (N));
9084
9085                if Nkind_In (GP, N_Package_Declaration,
9086                                 N_Generic_Package_Declaration)
9087                then
9088                   GP := Parent (GP);
9089                end if;
9090
9091                --  If we have a compilation unit, then record the ident value,
9092                --  checking for improper duplication.
9093
9094                if Nkind (GP) = N_Compilation_Unit then
9095                   CS := Ident_String (Current_Sem_Unit);
9096
9097                   if Present (CS) then
9098
9099                      --  For Ident, we do not permit multiple instances
9100
9101                      if Prag_Id = Pragma_Ident then
9102                         Error_Pragma ("duplicate% pragma not permitted");
9103
9104                      --  For Comment, we concatenate the string, unless we want
9105                      --  to preserve the tree structure for ASIS.
9106
9107                      elsif not ASIS_Mode then
9108                         Start_String (Strval (CS));
9109                         Store_String_Char (' ');
9110                         Store_String_Chars (Strval (Str));
9111                         Set_Strval (CS, End_String);
9112                      end if;
9113
9114                   else
9115                      --  In VMS, the effect of IDENT is achieved by passing
9116                      --  --identification=name as a --for-linker switch.
9117
9118                      if OpenVMS_On_Target then
9119                         Start_String;
9120                         Store_String_Chars
9121                           ("--for-linker=--identification=");
9122                         String_To_Name_Buffer (Strval (Str));
9123                         Store_String_Chars (Name_Buffer (1 .. Name_Len));
9124
9125                         --  Only the last processed IDENT is saved. The main
9126                         --  purpose is so an IDENT associated with a main
9127                         --  procedure will be used in preference to an IDENT
9128                         --  associated with a with'd package.
9129
9130                         Replace_Linker_Option_String
9131                           (End_String, "--for-linker=--identification=");
9132                      end if;
9133
9134                      Set_Ident_String (Current_Sem_Unit, Str);
9135                   end if;
9136
9137                --  For subunits, we just ignore the Ident, since in GNAT these
9138                --  are not separate object files, and hence not separate units
9139                --  in the unit table.
9140
9141                elsif Nkind (GP) = N_Subunit then
9142                   null;
9143
9144                --  Otherwise we have a misplaced pragma Ident, but we ignore
9145                --  this if we are in an instantiation, since it comes from
9146                --  a generic, and has no relevance to the instantiation.
9147
9148                elsif Prag_Id = Pragma_Ident then
9149                   if Instantiation_Location (Loc) = No_Location then
9150                      Error_Pragma ("pragma% only allowed at outer level");
9151                   end if;
9152                end if;
9153             end;
9154          end Ident;
9155
9156          ----------------------------
9157          -- Implementation_Defined --
9158          ----------------------------
9159
9160          --  pragma Implementation_Defined (local_NAME);
9161
9162          --  Marks previously declared entity as implementation defined. For
9163          --  an overloaded entity, applies to the most recent homonym.
9164
9165          --  pragma Implementation_Defined;
9166
9167          --  The form with no arguments appears anywhere within a scope, most
9168          --  typically a package spec, and indicates that all entities that are
9169          --  defined within the package spec are Implementation_Defined.
9170
9171          when Pragma_Implementation_Defined => Implementation_Defined : declare
9172             Ent : Entity_Id;
9173
9174          begin
9175             Check_No_Identifiers;
9176
9177             --  Form with no arguments
9178
9179             if Arg_Count = 0 then
9180                Set_Is_Implementation_Defined (Current_Scope);
9181
9182             --  Form with one argument
9183
9184             else
9185                Check_Arg_Count (1);
9186                Check_Arg_Is_Local_Name (Arg1);
9187                Ent := Entity (Get_Pragma_Arg (Arg1));
9188                Set_Is_Implementation_Defined (Ent);
9189             end if;
9190          end Implementation_Defined;
9191
9192          -----------------
9193          -- Implemented --
9194          -----------------
9195
9196          --  pragma Implemented (procedure_LOCAL_NAME, implementation_kind);
9197          --  implementation_kind ::= By_Entry | By_Protected_Procedure | By_Any
9198
9199          when Pragma_Implemented => Implemented : declare
9200             Proc_Id : Entity_Id;
9201             Typ     : Entity_Id;
9202
9203          begin
9204             Ada_2012_Pragma;
9205             Check_Arg_Count (2);
9206             Check_No_Identifiers;
9207             Check_Arg_Is_Identifier (Arg1);
9208             Check_Arg_Is_Local_Name (Arg1);
9209             Check_Arg_Is_One_Of
9210               (Arg2, Name_By_Any, Name_By_Entry, Name_By_Protected_Procedure);
9211
9212             --  Extract the name of the local procedure
9213
9214             Proc_Id := Entity (Get_Pragma_Arg (Arg1));
9215
9216             --  Ada 2012 (AI05-0030): The procedure_LOCAL_NAME must denote a
9217             --  primitive procedure of a synchronized tagged type.
9218
9219             if Ekind (Proc_Id) = E_Procedure
9220               and then Is_Primitive (Proc_Id)
9221               and then Present (First_Formal (Proc_Id))
9222             then
9223                Typ := Etype (First_Formal (Proc_Id));
9224
9225                if Is_Tagged_Type (Typ)
9226                  and then
9227
9228                   --  Check for a protected, a synchronized or a task interface
9229
9230                    ((Is_Interface (Typ)
9231                        and then Is_Synchronized_Interface (Typ))
9232
9233                   --  Check for a protected type or a task type that implements
9234                   --  an interface.
9235
9236                    or else
9237                     (Is_Concurrent_Record_Type (Typ)
9238                        and then Present (Interfaces (Typ)))
9239
9240                   --  Check for a private record extension with keyword
9241                   --  "synchronized".
9242
9243                    or else
9244                     (Ekind_In (Typ, E_Record_Type_With_Private,
9245                                     E_Record_Subtype_With_Private)
9246                        and then Synchronized_Present (Parent (Typ))))
9247                then
9248                   null;
9249                else
9250                   Error_Pragma_Arg
9251                     ("controlling formal must be of synchronized " &
9252                      "tagged type", Arg1);
9253                   return;
9254                end if;
9255
9256             --  Procedures declared inside a protected type must be accepted
9257
9258             elsif Ekind (Proc_Id) = E_Procedure
9259               and then Is_Protected_Type (Scope (Proc_Id))
9260             then
9261                null;
9262
9263             --  The first argument is not a primitive procedure
9264
9265             else
9266                Error_Pragma_Arg
9267                  ("pragma % must be applied to a primitive procedure", Arg1);
9268                return;
9269             end if;
9270
9271             --  Ada 2012 (AI05-0030): Cannot apply the implementation_kind
9272             --  By_Protected_Procedure to the primitive procedure of a task
9273             --  interface.
9274
9275             if Chars (Arg2) = Name_By_Protected_Procedure
9276               and then Is_Interface (Typ)
9277               and then Is_Task_Interface (Typ)
9278             then
9279                Error_Pragma_Arg
9280                  ("implementation kind By_Protected_Procedure cannot be " &
9281                   "applied to a task interface primitive", Arg2);
9282                return;
9283             end if;
9284
9285             Record_Rep_Item (Proc_Id, N);
9286          end Implemented;
9287
9288          ----------------------
9289          -- Implicit_Packing --
9290          ----------------------
9291
9292          --  pragma Implicit_Packing;
9293
9294          when Pragma_Implicit_Packing =>
9295             GNAT_Pragma;
9296             Check_Arg_Count (0);
9297             Implicit_Packing := True;
9298
9299          ------------
9300          -- Import --
9301          ------------
9302
9303          --  pragma Import (
9304          --       [Convention    =>] convention_IDENTIFIER,
9305          --       [Entity        =>] local_NAME
9306          --    [, [External_Name =>] static_string_EXPRESSION ]
9307          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
9308
9309          when Pragma_Import =>
9310             Check_Ada_83_Warning;
9311             Check_Arg_Order
9312               ((Name_Convention,
9313                 Name_Entity,
9314                 Name_External_Name,
9315                 Name_Link_Name));
9316             Check_At_Least_N_Arguments (2);
9317             Check_At_Most_N_Arguments  (4);
9318             Process_Import_Or_Interface;
9319
9320          ----------------------
9321          -- Import_Exception --
9322          ----------------------
9323
9324          --  pragma Import_Exception (
9325          --        [Internal         =>] LOCAL_NAME
9326          --     [, [External         =>] EXTERNAL_SYMBOL]
9327          --     [, [Form     =>] Ada | VMS]
9328          --     [, [Code     =>] static_integer_EXPRESSION]);
9329
9330          when Pragma_Import_Exception => Import_Exception : declare
9331             Args  : Args_List (1 .. 4);
9332             Names : constant Name_List (1 .. 4) := (
9333                       Name_Internal,
9334                       Name_External,
9335                       Name_Form,
9336                       Name_Code);
9337
9338             Internal : Node_Id renames Args (1);
9339             External : Node_Id renames Args (2);
9340             Form     : Node_Id renames Args (3);
9341             Code     : Node_Id renames Args (4);
9342
9343          begin
9344             GNAT_Pragma;
9345             Gather_Associations (Names, Args);
9346
9347             if Present (External) and then Present (Code) then
9348                Error_Pragma
9349                  ("cannot give both External and Code options for pragma%");
9350             end if;
9351
9352             Process_Extended_Import_Export_Exception_Pragma (
9353               Arg_Internal => Internal,
9354               Arg_External => External,
9355               Arg_Form     => Form,
9356               Arg_Code     => Code);
9357
9358             if not Is_VMS_Exception (Entity (Internal)) then
9359                Set_Imported (Entity (Internal));
9360             end if;
9361          end Import_Exception;
9362
9363          ---------------------
9364          -- Import_Function --
9365          ---------------------
9366
9367          --  pragma Import_Function (
9368          --        [Internal                 =>] LOCAL_NAME,
9369          --     [, [External                 =>] EXTERNAL_SYMBOL]
9370          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9371          --     [, [Result_Type              =>] SUBTYPE_MARK]
9372          --     [, [Mechanism                =>] MECHANISM]
9373          --     [, [Result_Mechanism         =>] MECHANISM_NAME]
9374          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9375
9376          --  EXTERNAL_SYMBOL ::=
9377          --    IDENTIFIER
9378          --  | static_string_EXPRESSION
9379
9380          --  PARAMETER_TYPES ::=
9381          --    null
9382          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9383
9384          --  TYPE_DESIGNATOR ::=
9385          --    subtype_NAME
9386          --  | subtype_Name ' Access
9387
9388          --  MECHANISM ::=
9389          --    MECHANISM_NAME
9390          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9391
9392          --  MECHANISM_ASSOCIATION ::=
9393          --    [formal_parameter_NAME =>] MECHANISM_NAME
9394
9395          --  MECHANISM_NAME ::=
9396          --    Value
9397          --  | Reference
9398          --  | Descriptor [([Class =>] CLASS_NAME)]
9399
9400          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9401
9402          when Pragma_Import_Function => Import_Function : declare
9403             Args  : Args_List (1 .. 7);
9404             Names : constant Name_List (1 .. 7) := (
9405                       Name_Internal,
9406                       Name_External,
9407                       Name_Parameter_Types,
9408                       Name_Result_Type,
9409                       Name_Mechanism,
9410                       Name_Result_Mechanism,
9411                       Name_First_Optional_Parameter);
9412
9413             Internal                 : Node_Id renames Args (1);
9414             External                 : Node_Id renames Args (2);
9415             Parameter_Types          : Node_Id renames Args (3);
9416             Result_Type              : Node_Id renames Args (4);
9417             Mechanism                : Node_Id renames Args (5);
9418             Result_Mechanism         : Node_Id renames Args (6);
9419             First_Optional_Parameter : Node_Id renames Args (7);
9420
9421          begin
9422             GNAT_Pragma;
9423             Gather_Associations (Names, Args);
9424             Process_Extended_Import_Export_Subprogram_Pragma (
9425               Arg_Internal                 => Internal,
9426               Arg_External                 => External,
9427               Arg_Parameter_Types          => Parameter_Types,
9428               Arg_Result_Type              => Result_Type,
9429               Arg_Mechanism                => Mechanism,
9430               Arg_Result_Mechanism         => Result_Mechanism,
9431               Arg_First_Optional_Parameter => First_Optional_Parameter);
9432          end Import_Function;
9433
9434          -------------------
9435          -- Import_Object --
9436          -------------------
9437
9438          --  pragma Import_Object (
9439          --        [Internal =>] LOCAL_NAME
9440          --     [, [External =>] EXTERNAL_SYMBOL]
9441          --     [, [Size     =>] EXTERNAL_SYMBOL]);
9442
9443          --  EXTERNAL_SYMBOL ::=
9444          --    IDENTIFIER
9445          --  | static_string_EXPRESSION
9446
9447          when Pragma_Import_Object => Import_Object : declare
9448             Args  : Args_List (1 .. 3);
9449             Names : constant Name_List (1 .. 3) := (
9450                       Name_Internal,
9451                       Name_External,
9452                       Name_Size);
9453
9454             Internal : Node_Id renames Args (1);
9455             External : Node_Id renames Args (2);
9456             Size     : Node_Id renames Args (3);
9457
9458          begin
9459             GNAT_Pragma;
9460             Gather_Associations (Names, Args);
9461             Process_Extended_Import_Export_Object_Pragma (
9462               Arg_Internal => Internal,
9463               Arg_External => External,
9464               Arg_Size     => Size);
9465          end Import_Object;
9466
9467          ----------------------
9468          -- Import_Procedure --
9469          ----------------------
9470
9471          --  pragma Import_Procedure (
9472          --        [Internal                 =>] LOCAL_NAME
9473          --     [, [External                 =>] EXTERNAL_SYMBOL]
9474          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9475          --     [, [Mechanism                =>] MECHANISM]
9476          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9477
9478          --  EXTERNAL_SYMBOL ::=
9479          --    IDENTIFIER
9480          --  | static_string_EXPRESSION
9481
9482          --  PARAMETER_TYPES ::=
9483          --    null
9484          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9485
9486          --  TYPE_DESIGNATOR ::=
9487          --    subtype_NAME
9488          --  | subtype_Name ' Access
9489
9490          --  MECHANISM ::=
9491          --    MECHANISM_NAME
9492          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9493
9494          --  MECHANISM_ASSOCIATION ::=
9495          --    [formal_parameter_NAME =>] MECHANISM_NAME
9496
9497          --  MECHANISM_NAME ::=
9498          --    Value
9499          --  | Reference
9500          --  | Descriptor [([Class =>] CLASS_NAME)]
9501
9502          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9503
9504          when Pragma_Import_Procedure => Import_Procedure : declare
9505             Args  : Args_List (1 .. 5);
9506             Names : constant Name_List (1 .. 5) := (
9507                       Name_Internal,
9508                       Name_External,
9509                       Name_Parameter_Types,
9510                       Name_Mechanism,
9511                       Name_First_Optional_Parameter);
9512
9513             Internal                 : Node_Id renames Args (1);
9514             External                 : Node_Id renames Args (2);
9515             Parameter_Types          : Node_Id renames Args (3);
9516             Mechanism                : Node_Id renames Args (4);
9517             First_Optional_Parameter : Node_Id renames Args (5);
9518
9519          begin
9520             GNAT_Pragma;
9521             Gather_Associations (Names, Args);
9522             Process_Extended_Import_Export_Subprogram_Pragma (
9523               Arg_Internal                 => Internal,
9524               Arg_External                 => External,
9525               Arg_Parameter_Types          => Parameter_Types,
9526               Arg_Mechanism                => Mechanism,
9527               Arg_First_Optional_Parameter => First_Optional_Parameter);
9528          end Import_Procedure;
9529
9530          -----------------------------
9531          -- Import_Valued_Procedure --
9532          -----------------------------
9533
9534          --  pragma Import_Valued_Procedure (
9535          --        [Internal                 =>] LOCAL_NAME
9536          --     [, [External                 =>] EXTERNAL_SYMBOL]
9537          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9538          --     [, [Mechanism                =>] MECHANISM]
9539          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9540
9541          --  EXTERNAL_SYMBOL ::=
9542          --    IDENTIFIER
9543          --  | static_string_EXPRESSION
9544
9545          --  PARAMETER_TYPES ::=
9546          --    null
9547          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9548
9549          --  TYPE_DESIGNATOR ::=
9550          --    subtype_NAME
9551          --  | subtype_Name ' Access
9552
9553          --  MECHANISM ::=
9554          --    MECHANISM_NAME
9555          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9556
9557          --  MECHANISM_ASSOCIATION ::=
9558          --    [formal_parameter_NAME =>] MECHANISM_NAME
9559
9560          --  MECHANISM_NAME ::=
9561          --    Value
9562          --  | Reference
9563          --  | Descriptor [([Class =>] CLASS_NAME)]
9564
9565          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9566
9567          when Pragma_Import_Valued_Procedure =>
9568          Import_Valued_Procedure : declare
9569             Args  : Args_List (1 .. 5);
9570             Names : constant Name_List (1 .. 5) := (
9571                       Name_Internal,
9572                       Name_External,
9573                       Name_Parameter_Types,
9574                       Name_Mechanism,
9575                       Name_First_Optional_Parameter);
9576
9577             Internal                 : Node_Id renames Args (1);
9578             External                 : Node_Id renames Args (2);
9579             Parameter_Types          : Node_Id renames Args (3);
9580             Mechanism                : Node_Id renames Args (4);
9581             First_Optional_Parameter : Node_Id renames Args (5);
9582
9583          begin
9584             GNAT_Pragma;
9585             Gather_Associations (Names, Args);
9586             Process_Extended_Import_Export_Subprogram_Pragma (
9587               Arg_Internal                 => Internal,
9588               Arg_External                 => External,
9589               Arg_Parameter_Types          => Parameter_Types,
9590               Arg_Mechanism                => Mechanism,
9591               Arg_First_Optional_Parameter => First_Optional_Parameter);
9592          end Import_Valued_Procedure;
9593
9594          -----------------
9595          -- Independent --
9596          -----------------
9597
9598          --  pragma Independent (LOCAL_NAME);
9599
9600          when Pragma_Independent => Independent : declare
9601             E_Id : Node_Id;
9602             E    : Entity_Id;
9603             D    : Node_Id;
9604             K    : Node_Kind;
9605
9606          begin
9607             Check_Ada_83_Warning;
9608             Ada_2012_Pragma;
9609             Check_No_Identifiers;
9610             Check_Arg_Count (1);
9611             Check_Arg_Is_Local_Name (Arg1);
9612             E_Id := Get_Pragma_Arg (Arg1);
9613
9614             if Etype (E_Id) = Any_Type then
9615                return;
9616             end if;
9617
9618             E := Entity (E_Id);
9619             D := Declaration_Node (E);
9620             K := Nkind (D);
9621
9622             --  Check duplicate before we chain ourselves!
9623
9624             Check_Duplicate_Pragma (E);
9625
9626             --  Check appropriate entity
9627
9628             if Is_Type (E) then
9629                if Rep_Item_Too_Early (E, N)
9630                     or else
9631                   Rep_Item_Too_Late (E, N)
9632                then
9633                   return;
9634                else
9635                   Check_First_Subtype (Arg1);
9636                end if;
9637
9638             elsif K = N_Object_Declaration
9639               or else (K = N_Component_Declaration
9640                        and then Original_Record_Component (E) = E)
9641             then
9642                if Rep_Item_Too_Late (E, N) then
9643                   return;
9644                end if;
9645
9646             else
9647                Error_Pragma_Arg
9648                  ("inappropriate entity for pragma%", Arg1);
9649             end if;
9650
9651             Independence_Checks.Append ((N, E));
9652          end Independent;
9653
9654          ----------------------------
9655          -- Independent_Components --
9656          ----------------------------
9657
9658          --  pragma Atomic_Components (array_LOCAL_NAME);
9659
9660          --  This processing is shared by Volatile_Components
9661
9662          when Pragma_Independent_Components => Independent_Components : declare
9663             E_Id : Node_Id;
9664             E    : Entity_Id;
9665             D    : Node_Id;
9666             K    : Node_Kind;
9667
9668          begin
9669             Check_Ada_83_Warning;
9670             Ada_2012_Pragma;
9671             Check_No_Identifiers;
9672             Check_Arg_Count (1);
9673             Check_Arg_Is_Local_Name (Arg1);
9674             E_Id := Get_Pragma_Arg (Arg1);
9675
9676             if Etype (E_Id) = Any_Type then
9677                return;
9678             end if;
9679
9680             E := Entity (E_Id);
9681
9682             --  Check duplicate before we chain ourselves!
9683
9684             Check_Duplicate_Pragma (E);
9685
9686             --  Check appropriate entity
9687
9688             if Rep_Item_Too_Early (E, N)
9689                  or else
9690                Rep_Item_Too_Late (E, N)
9691             then
9692                return;
9693             end if;
9694
9695             D := Declaration_Node (E);
9696             K := Nkind (D);
9697
9698             if (K = N_Full_Type_Declaration
9699                  and then (Is_Array_Type (E) or else Is_Record_Type (E)))
9700               or else
9701                 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
9702                    and then Nkind (D) = N_Object_Declaration
9703                    and then Nkind (Object_Definition (D)) =
9704                                        N_Constrained_Array_Definition)
9705             then
9706                Independence_Checks.Append ((N, E));
9707
9708             else
9709                Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
9710             end if;
9711          end Independent_Components;
9712
9713          ------------------------
9714          -- Initialize_Scalars --
9715          ------------------------
9716
9717          --  pragma Initialize_Scalars;
9718
9719          when Pragma_Initialize_Scalars =>
9720             GNAT_Pragma;
9721             Check_Arg_Count (0);
9722             Check_Valid_Configuration_Pragma;
9723             Check_Restriction (No_Initialize_Scalars, N);
9724
9725             --  Initialize_Scalars creates false positives in CodePeer, and
9726             --  incorrect negative results in Alfa mode, so ignore this pragma
9727             --  in these modes.
9728
9729             if not Restriction_Active (No_Initialize_Scalars)
9730               and then not (CodePeer_Mode or Alfa_Mode)
9731             then
9732                Init_Or_Norm_Scalars := True;
9733                Initialize_Scalars := True;
9734             end if;
9735
9736          ------------
9737          -- Inline --
9738          ------------
9739
9740          --  pragma Inline ( NAME {, NAME} );
9741
9742          when Pragma_Inline =>
9743
9744             --  Pragma is active if inlining option is active
9745
9746             Process_Inline (Inline_Active);
9747
9748          -------------------
9749          -- Inline_Always --
9750          -------------------
9751
9752          --  pragma Inline_Always ( NAME {, NAME} );
9753
9754          when Pragma_Inline_Always =>
9755             GNAT_Pragma;
9756
9757             --  Pragma always active unless in CodePeer or Alfa mode, since
9758             --  this causes walk order issues.
9759
9760             if not (CodePeer_Mode or Alfa_Mode) then
9761                Process_Inline (True);
9762             end if;
9763
9764          --------------------
9765          -- Inline_Generic --
9766          --------------------
9767
9768          --  pragma Inline_Generic (NAME {, NAME});
9769
9770          when Pragma_Inline_Generic =>
9771             GNAT_Pragma;
9772             Process_Generic_List;
9773
9774          ----------------------
9775          -- Inspection_Point --
9776          ----------------------
9777
9778          --  pragma Inspection_Point [(object_NAME {, object_NAME})];
9779
9780          when Pragma_Inspection_Point => Inspection_Point : declare
9781             Arg : Node_Id;
9782             Exp : Node_Id;
9783
9784          begin
9785             if Arg_Count > 0 then
9786                Arg := Arg1;
9787                loop
9788                   Exp := Get_Pragma_Arg (Arg);
9789                   Analyze (Exp);
9790
9791                   if not Is_Entity_Name (Exp)
9792                     or else not Is_Object (Entity (Exp))
9793                   then
9794                      Error_Pragma_Arg ("object name required", Arg);
9795                   end if;
9796
9797                   Next (Arg);
9798                   exit when No (Arg);
9799                end loop;
9800             end if;
9801          end Inspection_Point;
9802
9803          ---------------
9804          -- Interface --
9805          ---------------
9806
9807          --  pragma Interface (
9808          --    [   Convention    =>] convention_IDENTIFIER,
9809          --    [   Entity        =>] local_NAME
9810          --    [, [External_Name =>] static_string_EXPRESSION ]
9811          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
9812
9813          when Pragma_Interface =>
9814             GNAT_Pragma;
9815             Check_Arg_Order
9816               ((Name_Convention,
9817                 Name_Entity,
9818                 Name_External_Name,
9819                 Name_Link_Name));
9820             Check_At_Least_N_Arguments (2);
9821             Check_At_Most_N_Arguments  (4);
9822             Process_Import_Or_Interface;
9823
9824             --  In Ada 2005, the permission to use Interface (a reserved word)
9825             --  as a pragma name is considered an obsolescent feature.
9826
9827             if Ada_Version >= Ada_2005 then
9828                Check_Restriction
9829                  (No_Obsolescent_Features, Pragma_Identifier (N));
9830             end if;
9831
9832          --------------------
9833          -- Interface_Name --
9834          --------------------
9835
9836          --  pragma Interface_Name (
9837          --    [  Entity        =>] local_NAME
9838          --    [,[External_Name =>] static_string_EXPRESSION ]
9839          --    [,[Link_Name     =>] static_string_EXPRESSION ]);
9840
9841          when Pragma_Interface_Name => Interface_Name : declare
9842             Id     : Node_Id;
9843             Def_Id : Entity_Id;
9844             Hom_Id : Entity_Id;
9845             Found  : Boolean;
9846
9847          begin
9848             GNAT_Pragma;
9849             Check_Arg_Order
9850               ((Name_Entity, Name_External_Name, Name_Link_Name));
9851             Check_At_Least_N_Arguments (2);
9852             Check_At_Most_N_Arguments  (3);
9853             Id := Get_Pragma_Arg (Arg1);
9854             Analyze (Id);
9855
9856             if not Is_Entity_Name (Id) then
9857                Error_Pragma_Arg
9858                  ("first argument for pragma% must be entity name", Arg1);
9859             elsif Etype (Id) = Any_Type then
9860                return;
9861             else
9862                Def_Id := Entity (Id);
9863             end if;
9864
9865             --  Special DEC-compatible processing for the object case, forces
9866             --  object to be imported.
9867
9868             if Ekind (Def_Id) = E_Variable then
9869                Kill_Size_Check_Code (Def_Id);
9870                Note_Possible_Modification (Id, Sure => False);
9871
9872                --  Initialization is not allowed for imported variable
9873
9874                if Present (Expression (Parent (Def_Id)))
9875                  and then Comes_From_Source (Expression (Parent (Def_Id)))
9876                then
9877                   Error_Msg_Sloc := Sloc (Def_Id);
9878                   Error_Pragma_Arg
9879                     ("no initialization allowed for declaration of& #",
9880                      Arg2);
9881
9882                else
9883                   --  For compatibility, support VADS usage of providing both
9884                   --  pragmas Interface and Interface_Name to obtain the effect
9885                   --  of a single Import pragma.
9886
9887                   if Is_Imported (Def_Id)
9888                     and then Present (First_Rep_Item (Def_Id))
9889                     and then Nkind (First_Rep_Item (Def_Id)) = N_Pragma
9890                     and then
9891                       Pragma_Name (First_Rep_Item (Def_Id)) = Name_Interface
9892                   then
9893                      null;
9894                   else
9895                      Set_Imported (Def_Id);
9896                   end if;
9897
9898                   Set_Is_Public (Def_Id);
9899                   Process_Interface_Name (Def_Id, Arg2, Arg3);
9900                end if;
9901
9902             --  Otherwise must be subprogram
9903
9904             elsif not Is_Subprogram (Def_Id) then
9905                Error_Pragma_Arg
9906                  ("argument of pragma% is not subprogram", Arg1);
9907
9908             else
9909                Check_At_Most_N_Arguments (3);
9910                Hom_Id := Def_Id;
9911                Found := False;
9912
9913                --  Loop through homonyms
9914
9915                loop
9916                   Def_Id := Get_Base_Subprogram (Hom_Id);
9917
9918                   if Is_Imported (Def_Id) then
9919                      Process_Interface_Name (Def_Id, Arg2, Arg3);
9920                      Found := True;
9921                   end if;
9922
9923                   exit when From_Aspect_Specification (N);
9924                   Hom_Id := Homonym (Hom_Id);
9925
9926                   exit when No (Hom_Id)
9927                     or else Scope (Hom_Id) /= Current_Scope;
9928                end loop;
9929
9930                if not Found then
9931                   Error_Pragma_Arg
9932                     ("argument of pragma% is not imported subprogram",
9933                      Arg1);
9934                end if;
9935             end if;
9936          end Interface_Name;
9937
9938          -----------------------
9939          -- Interrupt_Handler --
9940          -----------------------
9941
9942          --  pragma Interrupt_Handler (handler_NAME);
9943
9944          when Pragma_Interrupt_Handler =>
9945             Check_Ada_83_Warning;
9946             Check_Arg_Count (1);
9947             Check_No_Identifiers;
9948
9949             if No_Run_Time_Mode then
9950                Error_Msg_CRT ("Interrupt_Handler pragma", N);
9951             else
9952                Check_Interrupt_Or_Attach_Handler;
9953                Process_Interrupt_Or_Attach_Handler;
9954             end if;
9955
9956          ------------------------
9957          -- Interrupt_Priority --
9958          ------------------------
9959
9960          --  pragma Interrupt_Priority [(EXPRESSION)];
9961
9962          when Pragma_Interrupt_Priority => Interrupt_Priority : declare
9963             P   : constant Node_Id := Parent (N);
9964             Arg : Node_Id;
9965
9966          begin
9967             Check_Ada_83_Warning;
9968
9969             if Arg_Count /= 0 then
9970                Arg := Get_Pragma_Arg (Arg1);
9971                Check_Arg_Count (1);
9972                Check_No_Identifiers;
9973
9974                --  The expression must be analyzed in the special manner
9975                --  described in "Handling of Default and Per-Object
9976                --  Expressions" in sem.ads.
9977
9978                Preanalyze_Spec_Expression (Arg, RTE (RE_Interrupt_Priority));
9979             end if;
9980
9981             if not Nkind_In (P, N_Task_Definition, N_Protected_Definition) then
9982                Pragma_Misplaced;
9983                return;
9984
9985             elsif Has_Pragma_Priority (P) then
9986                Error_Pragma ("duplicate pragma% not allowed");
9987
9988             else
9989                Set_Has_Pragma_Priority (P, True);
9990                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
9991             end if;
9992          end Interrupt_Priority;
9993
9994          ---------------------
9995          -- Interrupt_State --
9996          ---------------------
9997
9998          --  pragma Interrupt_State (
9999          --    [Name  =>] INTERRUPT_ID,
10000          --    [State =>] INTERRUPT_STATE);
10001
10002          --  INTERRUPT_ID => IDENTIFIER | static_integer_EXPRESSION
10003          --  INTERRUPT_STATE => System | Runtime | User
10004
10005          --  Note: if the interrupt id is given as an identifier, then it must
10006          --  be one of the identifiers in Ada.Interrupts.Names. Otherwise it is
10007          --  given as a static integer expression which must be in the range of
10008          --  Ada.Interrupts.Interrupt_ID.
10009
10010          when Pragma_Interrupt_State => Interrupt_State : declare
10011
10012             Int_Id : constant Entity_Id := RTE (RE_Interrupt_ID);
10013             --  This is the entity Ada.Interrupts.Interrupt_ID;
10014
10015             State_Type : Character;
10016             --  Set to 's'/'r'/'u' for System/Runtime/User
10017
10018             IST_Num : Pos;
10019             --  Index to entry in Interrupt_States table
10020
10021             Int_Val : Uint;
10022             --  Value of interrupt
10023
10024             Arg1X : constant Node_Id := Get_Pragma_Arg (Arg1);
10025             --  The first argument to the pragma
10026
10027             Int_Ent : Entity_Id;
10028             --  Interrupt entity in Ada.Interrupts.Names
10029
10030          begin
10031             GNAT_Pragma;
10032             Check_Arg_Order ((Name_Name, Name_State));
10033             Check_Arg_Count (2);
10034
10035             Check_Optional_Identifier (Arg1, Name_Name);
10036             Check_Optional_Identifier (Arg2, Name_State);
10037             Check_Arg_Is_Identifier (Arg2);
10038
10039             --  First argument is identifier
10040
10041             if Nkind (Arg1X) = N_Identifier then
10042
10043                --  Search list of names in Ada.Interrupts.Names
10044
10045                Int_Ent := First_Entity (RTE (RE_Names));
10046                loop
10047                   if No (Int_Ent) then
10048                      Error_Pragma_Arg ("invalid interrupt name", Arg1);
10049
10050                   elsif Chars (Int_Ent) = Chars (Arg1X) then
10051                      Int_Val := Expr_Value (Constant_Value (Int_Ent));
10052                      exit;
10053                   end if;
10054
10055                   Next_Entity (Int_Ent);
10056                end loop;
10057
10058             --  First argument is not an identifier, so it must be a static
10059             --  expression of type Ada.Interrupts.Interrupt_ID.
10060
10061             else
10062                Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
10063                Int_Val := Expr_Value (Arg1X);
10064
10065                if Int_Val < Expr_Value (Type_Low_Bound (Int_Id))
10066                     or else
10067                   Int_Val > Expr_Value (Type_High_Bound (Int_Id))
10068                then
10069                   Error_Pragma_Arg
10070                     ("value not in range of type " &
10071                      """Ada.Interrupts.Interrupt_'I'D""", Arg1);
10072                end if;
10073             end if;
10074
10075             --  Check OK state
10076
10077             case Chars (Get_Pragma_Arg (Arg2)) is
10078                when Name_Runtime => State_Type := 'r';
10079                when Name_System  => State_Type := 's';
10080                when Name_User    => State_Type := 'u';
10081
10082                when others =>
10083                   Error_Pragma_Arg ("invalid interrupt state", Arg2);
10084             end case;
10085
10086             --  Check if entry is already stored
10087
10088             IST_Num := Interrupt_States.First;
10089             loop
10090                --  If entry not found, add it
10091
10092                if IST_Num > Interrupt_States.Last then
10093                   Interrupt_States.Append
10094                     ((Interrupt_Number => UI_To_Int (Int_Val),
10095                       Interrupt_State  => State_Type,
10096                       Pragma_Loc       => Loc));
10097                   exit;
10098
10099                --  Case of entry for the same entry
10100
10101                elsif Int_Val = Interrupt_States.Table (IST_Num).
10102                                                            Interrupt_Number
10103                then
10104                   --  If state matches, done, no need to make redundant entry
10105
10106                   exit when
10107                     State_Type = Interrupt_States.Table (IST_Num).
10108                                                            Interrupt_State;
10109
10110                   --  Otherwise if state does not match, error
10111
10112                   Error_Msg_Sloc :=
10113                     Interrupt_States.Table (IST_Num).Pragma_Loc;
10114                   Error_Pragma_Arg
10115                     ("state conflicts with that given #", Arg2);
10116                   exit;
10117                end if;
10118
10119                IST_Num := IST_Num + 1;
10120             end loop;
10121          end Interrupt_State;
10122
10123          ---------------
10124          -- Invariant --
10125          ---------------
10126
10127          --  pragma Invariant
10128          --    ([Entity =>]    type_LOCAL_NAME,
10129          --     [Check  =>]    EXPRESSION
10130          --     [,[Message =>] String_Expression]);
10131
10132          when Pragma_Invariant => Invariant : declare
10133             Type_Id : Node_Id;
10134             Typ     : Entity_Id;
10135
10136             Discard : Boolean;
10137             pragma Unreferenced (Discard);
10138
10139          begin
10140             GNAT_Pragma;
10141             Check_At_Least_N_Arguments (2);
10142             Check_At_Most_N_Arguments (3);
10143             Check_Optional_Identifier (Arg1, Name_Entity);
10144             Check_Optional_Identifier (Arg2, Name_Check);
10145
10146             if Arg_Count = 3 then
10147                Check_Optional_Identifier (Arg3, Name_Message);
10148                Check_Arg_Is_Static_Expression (Arg3, Standard_String);
10149             end if;
10150
10151             Check_Arg_Is_Local_Name (Arg1);
10152
10153             Type_Id := Get_Pragma_Arg (Arg1);
10154             Find_Type (Type_Id);
10155             Typ := Entity (Type_Id);
10156
10157             if Typ = Any_Type then
10158                return;
10159
10160             --  An invariant must apply to a private type, or appear in the
10161             --  private part of a package spec and apply to a completion.
10162
10163             elsif Ekind_In (Typ, E_Private_Type,
10164                                  E_Record_Type_With_Private,
10165                                  E_Limited_Private_Type)
10166             then
10167                null;
10168
10169             elsif In_Private_Part (Current_Scope)
10170               and then Has_Private_Declaration (Typ)
10171             then
10172                null;
10173
10174             elsif In_Private_Part (Current_Scope) then
10175                Error_Pragma_Arg
10176                  ("pragma% only allowed for private type " &
10177                   "declared in visible part", Arg1);
10178
10179             else
10180                Error_Pragma_Arg
10181                  ("pragma% only allowed for private type", Arg1);
10182             end if;
10183
10184             --  Note that the type has at least one invariant, and also that
10185             --  it has inheritable invariants if we have Invariant'Class.
10186
10187             Set_Has_Invariants (Typ);
10188
10189             if Class_Present (N) then
10190                Set_Has_Inheritable_Invariants (Typ);
10191             end if;
10192
10193             --  The remaining processing is simply to link the pragma on to
10194             --  the rep item chain, for processing when the type is frozen.
10195             --  This is accomplished by a call to Rep_Item_Too_Late.
10196
10197             Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
10198          end Invariant;
10199
10200          ----------------------
10201          -- Java_Constructor --
10202          ----------------------
10203
10204          --  pragma Java_Constructor ([Entity =>] LOCAL_NAME);
10205
10206          --  Also handles pragma CIL_Constructor
10207
10208          when Pragma_CIL_Constructor | Pragma_Java_Constructor =>
10209          Java_Constructor : declare
10210             Convention  : Convention_Id;
10211             Def_Id      : Entity_Id;
10212             Hom_Id      : Entity_Id;
10213             Id          : Entity_Id;
10214             This_Formal : Entity_Id;
10215
10216          begin
10217             GNAT_Pragma;
10218             Check_Arg_Count (1);
10219             Check_Optional_Identifier (Arg1, Name_Entity);
10220             Check_Arg_Is_Local_Name (Arg1);
10221
10222             Id := Get_Pragma_Arg (Arg1);
10223             Find_Program_Unit_Name (Id);
10224
10225             --  If we did not find the name, we are done
10226
10227             if Etype (Id) = Any_Type then
10228                return;
10229             end if;
10230
10231             --  Check wrong use of pragma in wrong VM target
10232
10233             if VM_Target = No_VM then
10234                return;
10235
10236             elsif VM_Target = CLI_Target
10237               and then Prag_Id = Pragma_Java_Constructor
10238             then
10239                Error_Pragma ("must use pragma 'C'I'L_'Constructor");
10240
10241             elsif VM_Target = JVM_Target
10242               and then Prag_Id = Pragma_CIL_Constructor
10243             then
10244                Error_Pragma ("must use pragma 'Java_'Constructor");
10245             end if;
10246
10247             case Prag_Id is
10248                when Pragma_CIL_Constructor  => Convention := Convention_CIL;
10249                when Pragma_Java_Constructor => Convention := Convention_Java;
10250                when others                  => null;
10251             end case;
10252
10253             Hom_Id := Entity (Id);
10254
10255             --  Loop through homonyms
10256
10257             loop
10258                Def_Id := Get_Base_Subprogram (Hom_Id);
10259
10260                --  The constructor is required to be a function
10261
10262                if Ekind (Def_Id) /= E_Function then
10263                   if VM_Target = JVM_Target then
10264                      Error_Pragma_Arg
10265                        ("pragma% requires function returning a " &
10266                         "'Java access type", Def_Id);
10267                   else
10268                      Error_Pragma_Arg
10269                        ("pragma% requires function returning a " &
10270                         "'C'I'L access type", Def_Id);
10271                   end if;
10272                end if;
10273
10274                --  Check arguments: For tagged type the first formal must be
10275                --  named "this" and its type must be a named access type
10276                --  designating a class-wide tagged type that has convention
10277                --  CIL/Java. The first formal must also have a null default
10278                --  value. For example:
10279
10280                --      type Typ is tagged ...
10281                --      type Ref is access all Typ;
10282                --      pragma Convention (CIL, Typ);
10283
10284                --      function New_Typ (This : Ref) return Ref;
10285                --      function New_Typ (This : Ref; I : Integer) return Ref;
10286                --      pragma Cil_Constructor (New_Typ);
10287
10288                --  Reason: The first formal must NOT be a primitive of the
10289                --  tagged type.
10290
10291                --  This rule also applies to constructors of delegates used
10292                --  to interface with standard target libraries. For example:
10293
10294                --      type Delegate is access procedure ...
10295                --      pragma Import (CIL, Delegate, ...);
10296
10297                --      function new_Delegate
10298                --        (This : Delegate := null; ... ) return Delegate;
10299
10300                --  For value-types this rule does not apply.
10301
10302                if not Is_Value_Type (Etype (Def_Id)) then
10303                   if No (First_Formal (Def_Id)) then
10304                      Error_Msg_Name_1 := Pname;
10305                      Error_Msg_N ("% function must have parameters", Def_Id);
10306                      return;
10307                   end if;
10308
10309                   --  In the JRE library we have several occurrences in which
10310                   --  the "this" parameter is not the first formal.
10311
10312                   This_Formal := First_Formal (Def_Id);
10313
10314                   --  In the JRE library we have several occurrences in which
10315                   --  the "this" parameter is not the first formal. Search for
10316                   --  it.
10317
10318                   if VM_Target = JVM_Target then
10319                      while Present (This_Formal)
10320                        and then Get_Name_String (Chars (This_Formal)) /= "this"
10321                      loop
10322                         Next_Formal (This_Formal);
10323                      end loop;
10324
10325                      if No (This_Formal) then
10326                         This_Formal := First_Formal (Def_Id);
10327                      end if;
10328                   end if;
10329
10330                   --  Warning: The first parameter should be named "this".
10331                   --  We temporarily allow it because we have the following
10332                   --  case in the Java runtime (file s-osinte.ads) ???
10333
10334                   --    function new_Thread
10335                   --      (Self_Id : System.Address) return Thread_Id;
10336                   --    pragma Java_Constructor (new_Thread);
10337
10338                   if VM_Target = JVM_Target
10339                     and then Get_Name_String (Chars (First_Formal (Def_Id)))
10340                                = "self_id"
10341                     and then Etype (First_Formal (Def_Id)) = RTE (RE_Address)
10342                   then
10343                      null;
10344
10345                   elsif Get_Name_String (Chars (This_Formal)) /= "this" then
10346                      Error_Msg_Name_1 := Pname;
10347                      Error_Msg_N
10348                        ("first formal of % function must be named `this`",
10349                         Parent (This_Formal));
10350
10351                   elsif not Is_Access_Type (Etype (This_Formal)) then
10352                      Error_Msg_Name_1 := Pname;
10353                      Error_Msg_N
10354                        ("first formal of % function must be an access type",
10355                         Parameter_Type (Parent (This_Formal)));
10356
10357                   --  For delegates the type of the first formal must be a
10358                   --  named access-to-subprogram type (see previous example)
10359
10360                   elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type
10361                     and then Ekind (Etype (This_Formal))
10362                                /= E_Access_Subprogram_Type
10363                   then
10364                      Error_Msg_Name_1 := Pname;
10365                      Error_Msg_N
10366                        ("first formal of % function must be a named access" &
10367                         " to subprogram type",
10368                         Parameter_Type (Parent (This_Formal)));
10369
10370                   --  Warning: We should reject anonymous access types because
10371                   --  the constructor must not be handled as a primitive of the
10372                   --  tagged type. We temporarily allow it because this profile
10373                   --  is currently generated by cil2ada???
10374
10375                   elsif Ekind (Etype (Def_Id)) /= E_Access_Subprogram_Type
10376                     and then not Ekind_In (Etype (This_Formal),
10377                                              E_Access_Type,
10378                                              E_General_Access_Type,
10379                                              E_Anonymous_Access_Type)
10380                   then
10381                      Error_Msg_Name_1 := Pname;
10382                      Error_Msg_N
10383                        ("first formal of % function must be a named access" &
10384                         " type",
10385                         Parameter_Type (Parent (This_Formal)));
10386
10387                   elsif Atree.Convention
10388                          (Designated_Type (Etype (This_Formal))) /= Convention
10389                   then
10390                      Error_Msg_Name_1 := Pname;
10391
10392                      if Convention = Convention_Java then
10393                         Error_Msg_N
10394                           ("pragma% requires convention 'Cil in designated" &
10395                            " type",
10396                            Parameter_Type (Parent (This_Formal)));
10397                      else
10398                         Error_Msg_N
10399                           ("pragma% requires convention 'Java in designated" &
10400                            " type",
10401                            Parameter_Type (Parent (This_Formal)));
10402                      end if;
10403
10404                   elsif No (Expression (Parent (This_Formal)))
10405                     or else Nkind (Expression (Parent (This_Formal))) /= N_Null
10406                   then
10407                      Error_Msg_Name_1 := Pname;
10408                      Error_Msg_N
10409                        ("pragma% requires first formal with default `null`",
10410                         Parameter_Type (Parent (This_Formal)));
10411                   end if;
10412                end if;
10413
10414                --  Check result type: the constructor must be a function
10415                --  returning:
10416                --   * a value type (only allowed in the CIL compiler)
10417                --   * an access-to-subprogram type with convention Java/CIL
10418                --   * an access-type designating a type that has convention
10419                --     Java/CIL.
10420
10421                if Is_Value_Type (Etype (Def_Id)) then
10422                   null;
10423
10424                --  Access-to-subprogram type with convention Java/CIL
10425
10426                elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type then
10427                   if Atree.Convention (Etype (Def_Id)) /= Convention then
10428                      if Convention = Convention_Java then
10429                         Error_Pragma_Arg
10430                           ("pragma% requires function returning a " &
10431                            "'Java access type", Arg1);
10432                      else
10433                         pragma Assert (Convention = Convention_CIL);
10434                         Error_Pragma_Arg
10435                           ("pragma% requires function returning a " &
10436                            "'C'I'L access type", Arg1);
10437                      end if;
10438                   end if;
10439
10440                elsif Ekind (Etype (Def_Id)) in Access_Kind then
10441                   if not Ekind_In (Etype (Def_Id), E_Access_Type,
10442                                                    E_General_Access_Type)
10443                     or else
10444                       Atree.Convention
10445                         (Designated_Type (Etype (Def_Id))) /= Convention
10446                   then
10447                      Error_Msg_Name_1 := Pname;
10448
10449                      if Convention = Convention_Java then
10450                         Error_Pragma_Arg
10451                           ("pragma% requires function returning a named" &
10452                            "'Java access type", Arg1);
10453                      else
10454                         Error_Pragma_Arg
10455                           ("pragma% requires function returning a named" &
10456                            "'C'I'L access type", Arg1);
10457                      end if;
10458                   end if;
10459                end if;
10460
10461                Set_Is_Constructor (Def_Id);
10462                Set_Convention     (Def_Id, Convention);
10463                Set_Is_Imported    (Def_Id);
10464
10465                exit when From_Aspect_Specification (N);
10466                Hom_Id := Homonym (Hom_Id);
10467
10468                exit when No (Hom_Id) or else Scope (Hom_Id) /= Current_Scope;
10469             end loop;
10470          end Java_Constructor;
10471
10472          ----------------------
10473          -- Java_Interface --
10474          ----------------------
10475
10476          --  pragma Java_Interface ([Entity =>] LOCAL_NAME);
10477
10478          when Pragma_Java_Interface => Java_Interface : declare
10479             Arg : Node_Id;
10480             Typ : Entity_Id;
10481
10482          begin
10483             GNAT_Pragma;
10484             Check_Arg_Count (1);
10485             Check_Optional_Identifier (Arg1, Name_Entity);
10486             Check_Arg_Is_Local_Name (Arg1);
10487
10488             Arg := Get_Pragma_Arg (Arg1);
10489             Analyze (Arg);
10490
10491             if Etype (Arg) = Any_Type then
10492                return;
10493             end if;
10494
10495             if not Is_Entity_Name (Arg)
10496               or else not Is_Type (Entity (Arg))
10497             then
10498                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
10499             end if;
10500
10501             Typ := Underlying_Type (Entity (Arg));
10502
10503             --  For now simply check some of the semantic constraints on the
10504             --  type. This currently leaves out some restrictions on interface
10505             --  types, namely that the parent type must be java.lang.Object.Typ
10506             --  and that all primitives of the type should be declared
10507             --  abstract. ???
10508
10509             if not Is_Tagged_Type (Typ) or else not Is_Abstract_Type (Typ) then
10510                Error_Pragma_Arg ("pragma% requires an abstract "
10511                  & "tagged type", Arg1);
10512
10513             elsif not Has_Discriminants (Typ)
10514               or else Ekind (Etype (First_Discriminant (Typ)))
10515                         /= E_Anonymous_Access_Type
10516               or else
10517                 not Is_Class_Wide_Type
10518                       (Designated_Type (Etype (First_Discriminant (Typ))))
10519             then
10520                Error_Pragma_Arg
10521                  ("type must have a class-wide access discriminant", Arg1);
10522             end if;
10523          end Java_Interface;
10524
10525          ----------------
10526          -- Keep_Names --
10527          ----------------
10528
10529          --  pragma Keep_Names ([On => ] local_NAME);
10530
10531          when Pragma_Keep_Names => Keep_Names : declare
10532             Arg : Node_Id;
10533
10534          begin
10535             GNAT_Pragma;
10536             Check_Arg_Count (1);
10537             Check_Optional_Identifier (Arg1, Name_On);
10538             Check_Arg_Is_Local_Name (Arg1);
10539
10540             Arg := Get_Pragma_Arg (Arg1);
10541             Analyze (Arg);
10542
10543             if Etype (Arg) = Any_Type then
10544                return;
10545             end if;
10546
10547             if not Is_Entity_Name (Arg)
10548               or else Ekind (Entity (Arg)) /= E_Enumeration_Type
10549             then
10550                Error_Pragma_Arg
10551                  ("pragma% requires a local enumeration type", Arg1);
10552             end if;
10553
10554             Set_Discard_Names (Entity (Arg), False);
10555          end Keep_Names;
10556
10557          -------------
10558          -- License --
10559          -------------
10560
10561          --  pragma License (RESTRICTED | UNRESTRICTED | GPL | MODIFIED_GPL);
10562
10563          when Pragma_License =>
10564             GNAT_Pragma;
10565             Check_Arg_Count (1);
10566             Check_No_Identifiers;
10567             Check_Valid_Configuration_Pragma;
10568             Check_Arg_Is_Identifier (Arg1);
10569
10570             declare
10571                Sind : constant Source_File_Index :=
10572                         Source_Index (Current_Sem_Unit);
10573
10574             begin
10575                case Chars (Get_Pragma_Arg (Arg1)) is
10576                   when Name_GPL =>
10577                      Set_License (Sind, GPL);
10578
10579                   when Name_Modified_GPL =>
10580                      Set_License (Sind, Modified_GPL);
10581
10582                   when Name_Restricted =>
10583                      Set_License (Sind, Restricted);
10584
10585                   when Name_Unrestricted =>
10586                      Set_License (Sind, Unrestricted);
10587
10588                   when others =>
10589                      Error_Pragma_Arg ("invalid license name", Arg1);
10590                end case;
10591             end;
10592
10593          ---------------
10594          -- Link_With --
10595          ---------------
10596
10597          --  pragma Link_With (string_EXPRESSION {, string_EXPRESSION});
10598
10599          when Pragma_Link_With => Link_With : declare
10600             Arg : Node_Id;
10601
10602          begin
10603             GNAT_Pragma;
10604
10605             if Operating_Mode = Generate_Code
10606               and then In_Extended_Main_Source_Unit (N)
10607             then
10608                Check_At_Least_N_Arguments (1);
10609                Check_No_Identifiers;
10610                Check_Is_In_Decl_Part_Or_Package_Spec;
10611                Check_Arg_Is_Static_Expression (Arg1, Standard_String);
10612                Start_String;
10613
10614                Arg := Arg1;
10615                while Present (Arg) loop
10616                   Check_Arg_Is_Static_Expression (Arg, Standard_String);
10617
10618                   --  Store argument, converting sequences of spaces to a
10619                   --  single null character (this is one of the differences
10620                   --  in processing between Link_With and Linker_Options).
10621
10622                   Arg_Store : declare
10623                      C : constant Char_Code := Get_Char_Code (' ');
10624                      S : constant String_Id :=
10625                            Strval (Expr_Value_S (Get_Pragma_Arg (Arg)));
10626                      L : constant Nat := String_Length (S);
10627                      F : Nat := 1;
10628
10629                      procedure Skip_Spaces;
10630                      --  Advance F past any spaces
10631
10632                      -----------------
10633                      -- Skip_Spaces --
10634                      -----------------
10635
10636                      procedure Skip_Spaces is
10637                      begin
10638                         while F <= L and then Get_String_Char (S, F) = C loop
10639                            F := F + 1;
10640                         end loop;
10641                      end Skip_Spaces;
10642
10643                   --  Start of processing for Arg_Store
10644
10645                   begin
10646                      Skip_Spaces; -- skip leading spaces
10647
10648                      --  Loop through characters, changing any embedded
10649                      --  sequence of spaces to a single null character (this
10650                      --  is how Link_With/Linker_Options differ)
10651
10652                      while F <= L loop
10653                         if Get_String_Char (S, F) = C then
10654                            Skip_Spaces;
10655                            exit when F > L;
10656                            Store_String_Char (ASCII.NUL);
10657
10658                         else
10659                            Store_String_Char (Get_String_Char (S, F));
10660                            F := F + 1;
10661                         end if;
10662                      end loop;
10663                   end Arg_Store;
10664
10665                   Arg := Next (Arg);
10666
10667                   if Present (Arg) then
10668                      Store_String_Char (ASCII.NUL);
10669                   end if;
10670                end loop;
10671
10672                Store_Linker_Option_String (End_String);
10673             end if;
10674          end Link_With;
10675
10676          ------------------
10677          -- Linker_Alias --
10678          ------------------
10679
10680          --  pragma Linker_Alias (
10681          --      [Entity =>]  LOCAL_NAME
10682          --      [Target =>]  static_string_EXPRESSION);
10683
10684          when Pragma_Linker_Alias =>
10685             GNAT_Pragma;
10686             Check_Arg_Order ((Name_Entity, Name_Target));
10687             Check_Arg_Count (2);
10688             Check_Optional_Identifier (Arg1, Name_Entity);
10689             Check_Optional_Identifier (Arg2, Name_Target);
10690             Check_Arg_Is_Library_Level_Local_Name (Arg1);
10691             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10692
10693             --  The only processing required is to link this item on to the
10694             --  list of rep items for the given entity. This is accomplished
10695             --  by the call to Rep_Item_Too_Late (when no error is detected
10696             --  and False is returned).
10697
10698             if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
10699                return;
10700             else
10701                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10702             end if;
10703
10704          ------------------------
10705          -- Linker_Constructor --
10706          ------------------------
10707
10708          --  pragma Linker_Constructor (procedure_LOCAL_NAME);
10709
10710          --  Code is shared with Linker_Destructor
10711
10712          -----------------------
10713          -- Linker_Destructor --
10714          -----------------------
10715
10716          --  pragma Linker_Destructor (procedure_LOCAL_NAME);
10717
10718          when Pragma_Linker_Constructor |
10719               Pragma_Linker_Destructor =>
10720          Linker_Constructor : declare
10721             Arg1_X : Node_Id;
10722             Proc   : Entity_Id;
10723
10724          begin
10725             GNAT_Pragma;
10726             Check_Arg_Count (1);
10727             Check_No_Identifiers;
10728             Check_Arg_Is_Local_Name (Arg1);
10729             Arg1_X := Get_Pragma_Arg (Arg1);
10730             Analyze (Arg1_X);
10731             Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
10732
10733             if not Is_Library_Level_Entity (Proc) then
10734                Error_Pragma_Arg
10735                 ("argument for pragma% must be library level entity", Arg1);
10736             end if;
10737
10738             --  The only processing required is to link this item on to the
10739             --  list of rep items for the given entity. This is accomplished
10740             --  by the call to Rep_Item_Too_Late (when no error is detected
10741             --  and False is returned).
10742
10743             if Rep_Item_Too_Late (Proc, N) then
10744                return;
10745             else
10746                Set_Has_Gigi_Rep_Item (Proc);
10747             end if;
10748          end Linker_Constructor;
10749
10750          --------------------
10751          -- Linker_Options --
10752          --------------------
10753
10754          --  pragma Linker_Options (string_EXPRESSION {, string_EXPRESSION});
10755
10756          when Pragma_Linker_Options => Linker_Options : declare
10757             Arg : Node_Id;
10758
10759          begin
10760             Check_Ada_83_Warning;
10761             Check_No_Identifiers;
10762             Check_Arg_Count (1);
10763             Check_Is_In_Decl_Part_Or_Package_Spec;
10764             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
10765             Start_String (Strval (Expr_Value_S (Get_Pragma_Arg (Arg1))));
10766
10767             Arg := Arg2;
10768             while Present (Arg) loop
10769                Check_Arg_Is_Static_Expression (Arg, Standard_String);
10770                Store_String_Char (ASCII.NUL);
10771                Store_String_Chars
10772                  (Strval (Expr_Value_S (Get_Pragma_Arg (Arg))));
10773                Arg := Next (Arg);
10774             end loop;
10775
10776             if Operating_Mode = Generate_Code
10777               and then In_Extended_Main_Source_Unit (N)
10778             then
10779                Store_Linker_Option_String (End_String);
10780             end if;
10781          end Linker_Options;
10782
10783          --------------------
10784          -- Linker_Section --
10785          --------------------
10786
10787          --  pragma Linker_Section (
10788          --      [Entity  =>]  LOCAL_NAME
10789          --      [Section =>]  static_string_EXPRESSION);
10790
10791          when Pragma_Linker_Section =>
10792             GNAT_Pragma;
10793             Check_Arg_Order ((Name_Entity, Name_Section));
10794             Check_Arg_Count (2);
10795             Check_Optional_Identifier (Arg1, Name_Entity);
10796             Check_Optional_Identifier (Arg2, Name_Section);
10797             Check_Arg_Is_Library_Level_Local_Name (Arg1);
10798             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10799
10800             --  This pragma applies only to objects
10801
10802             if not Is_Object (Entity (Get_Pragma_Arg (Arg1))) then
10803                Error_Pragma_Arg ("pragma% applies only to objects", Arg1);
10804             end if;
10805
10806             --  The only processing required is to link this item on to the
10807             --  list of rep items for the given entity. This is accomplished
10808             --  by the call to Rep_Item_Too_Late (when no error is detected
10809             --  and False is returned).
10810
10811             if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
10812                return;
10813             else
10814                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10815             end if;
10816
10817          ----------
10818          -- List --
10819          ----------
10820
10821          --  pragma List (On | Off)
10822
10823          --  There is nothing to do here, since we did all the processing for
10824          --  this pragma in Par.Prag (so that it works properly even in syntax
10825          --  only mode).
10826
10827          when Pragma_List =>
10828             null;
10829
10830          --------------------
10831          -- Locking_Policy --
10832          --------------------
10833
10834          --  pragma Locking_Policy (policy_IDENTIFIER);
10835
10836          when Pragma_Locking_Policy => declare
10837             subtype LP_Range is Name_Id
10838               range First_Locking_Policy_Name .. Last_Locking_Policy_Name;
10839             LP_Val : LP_Range;
10840             LP     : Character;
10841          begin
10842             Check_Ada_83_Warning;
10843             Check_Arg_Count (1);
10844             Check_No_Identifiers;
10845             Check_Arg_Is_Locking_Policy (Arg1);
10846             Check_Valid_Configuration_Pragma;
10847             LP_Val := Chars (Get_Pragma_Arg (Arg1));
10848
10849             case LP_Val is
10850                when Name_Ceiling_Locking            => LP := 'C';
10851                when Name_Inheritance_Locking        => LP := 'I';
10852                when Name_Concurrent_Readers_Locking => LP := 'R';
10853             end case;
10854
10855             if Locking_Policy /= ' '
10856               and then Locking_Policy /= LP
10857             then
10858                Error_Msg_Sloc := Locking_Policy_Sloc;
10859                Error_Pragma ("locking policy incompatible with policy#");
10860
10861             --  Set new policy, but always preserve System_Location since we
10862             --  like the error message with the run time name.
10863
10864             else
10865                Locking_Policy := LP;
10866
10867                if Locking_Policy_Sloc /= System_Location then
10868                   Locking_Policy_Sloc := Loc;
10869                end if;
10870             end if;
10871          end;
10872
10873          ----------------
10874          -- Long_Float --
10875          ----------------
10876
10877          --  pragma Long_Float (D_Float | G_Float);
10878
10879          when Pragma_Long_Float =>
10880             GNAT_Pragma;
10881             Check_Valid_Configuration_Pragma;
10882             Check_Arg_Count (1);
10883             Check_No_Identifier (Arg1);
10884             Check_Arg_Is_One_Of (Arg1, Name_D_Float, Name_G_Float);
10885
10886             if not OpenVMS_On_Target then
10887                Error_Pragma ("?pragma% ignored (applies only to Open'V'M'S)");
10888             end if;
10889
10890             --  D_Float case
10891
10892             if Chars (Get_Pragma_Arg (Arg1)) = Name_D_Float then
10893                if Opt.Float_Format_Long = 'G' then
10894                   Error_Pragma ("G_Float previously specified");
10895                end if;
10896
10897                Opt.Float_Format_Long := 'D';
10898
10899             --  G_Float case (this is the default, does not need overriding)
10900
10901             else
10902                if Opt.Float_Format_Long = 'D' then
10903                   Error_Pragma ("D_Float previously specified");
10904                end if;
10905
10906                Opt.Float_Format_Long := 'G';
10907             end if;
10908
10909             Set_Standard_Fpt_Formats;
10910
10911          -----------------------
10912          -- Machine_Attribute --
10913          -----------------------
10914
10915          --  pragma Machine_Attribute (
10916          --       [Entity         =>] LOCAL_NAME,
10917          --       [Attribute_Name =>] static_string_EXPRESSION
10918          --    [, [Info           =>] static_EXPRESSION] );
10919
10920          when Pragma_Machine_Attribute => Machine_Attribute : declare
10921             Def_Id : Entity_Id;
10922
10923          begin
10924             GNAT_Pragma;
10925             Check_Arg_Order ((Name_Entity, Name_Attribute_Name, Name_Info));
10926
10927             if Arg_Count = 3 then
10928                Check_Optional_Identifier (Arg3, Name_Info);
10929                Check_Arg_Is_Static_Expression (Arg3);
10930             else
10931                Check_Arg_Count (2);
10932             end if;
10933
10934             Check_Optional_Identifier (Arg1, Name_Entity);
10935             Check_Optional_Identifier (Arg2, Name_Attribute_Name);
10936             Check_Arg_Is_Local_Name (Arg1);
10937             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10938             Def_Id := Entity (Get_Pragma_Arg (Arg1));
10939
10940             if Is_Access_Type (Def_Id) then
10941                Def_Id := Designated_Type (Def_Id);
10942             end if;
10943
10944             if Rep_Item_Too_Early (Def_Id, N) then
10945                return;
10946             end if;
10947
10948             Def_Id := Underlying_Type (Def_Id);
10949
10950             --  The only processing required is to link this item on to the
10951             --  list of rep items for the given entity. This is accomplished
10952             --  by the call to Rep_Item_Too_Late (when no error is detected
10953             --  and False is returned).
10954
10955             if Rep_Item_Too_Late (Def_Id, N) then
10956                return;
10957             else
10958                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10959             end if;
10960          end Machine_Attribute;
10961
10962          ----------
10963          -- Main --
10964          ----------
10965
10966          --  pragma Main
10967          --   (MAIN_OPTION [, MAIN_OPTION]);
10968
10969          --  MAIN_OPTION ::=
10970          --    [STACK_SIZE              =>] static_integer_EXPRESSION
10971          --  | [TASK_STACK_SIZE_DEFAULT =>] static_integer_EXPRESSION
10972          --  | [TIME_SLICING_ENABLED    =>] static_boolean_EXPRESSION
10973
10974          when Pragma_Main => Main : declare
10975             Args  : Args_List (1 .. 3);
10976             Names : constant Name_List (1 .. 3) := (
10977                       Name_Stack_Size,
10978                       Name_Task_Stack_Size_Default,
10979                       Name_Time_Slicing_Enabled);
10980
10981             Nod : Node_Id;
10982
10983          begin
10984             GNAT_Pragma;
10985             Gather_Associations (Names, Args);
10986
10987             for J in 1 .. 2 loop
10988                if Present (Args (J)) then
10989                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
10990                end if;
10991             end loop;
10992
10993             if Present (Args (3)) then
10994                Check_Arg_Is_Static_Expression (Args (3), Standard_Boolean);
10995             end if;
10996
10997             Nod := Next (N);
10998             while Present (Nod) loop
10999                if Nkind (Nod) = N_Pragma
11000                  and then Pragma_Name (Nod) = Name_Main
11001                then
11002                   Error_Msg_Name_1 := Pname;
11003                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
11004                end if;
11005
11006                Next (Nod);
11007             end loop;
11008          end Main;
11009
11010          ------------------
11011          -- Main_Storage --
11012          ------------------
11013
11014          --  pragma Main_Storage
11015          --   (MAIN_STORAGE_OPTION [, MAIN_STORAGE_OPTION]);
11016
11017          --  MAIN_STORAGE_OPTION ::=
11018          --    [WORKING_STORAGE =>] static_SIMPLE_EXPRESSION
11019          --  | [TOP_GUARD =>] static_SIMPLE_EXPRESSION
11020
11021          when Pragma_Main_Storage => Main_Storage : declare
11022             Args  : Args_List (1 .. 2);
11023             Names : constant Name_List (1 .. 2) := (
11024                       Name_Working_Storage,
11025                       Name_Top_Guard);
11026
11027             Nod : Node_Id;
11028
11029          begin
11030             GNAT_Pragma;
11031             Gather_Associations (Names, Args);
11032
11033             for J in 1 .. 2 loop
11034                if Present (Args (J)) then
11035                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
11036                end if;
11037             end loop;
11038
11039             Check_In_Main_Program;
11040
11041             Nod := Next (N);
11042             while Present (Nod) loop
11043                if Nkind (Nod) = N_Pragma
11044                  and then Pragma_Name (Nod) = Name_Main_Storage
11045                then
11046                   Error_Msg_Name_1 := Pname;
11047                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
11048                end if;
11049
11050                Next (Nod);
11051             end loop;
11052          end Main_Storage;
11053
11054          -----------------
11055          -- Memory_Size --
11056          -----------------
11057
11058          --  pragma Memory_Size (NUMERIC_LITERAL)
11059
11060          when Pragma_Memory_Size =>
11061             GNAT_Pragma;
11062
11063             --  Memory size is simply ignored
11064
11065             Check_No_Identifiers;
11066             Check_Arg_Count (1);
11067             Check_Arg_Is_Integer_Literal (Arg1);
11068
11069          -------------
11070          -- No_Body --
11071          -------------
11072
11073          --  pragma No_Body;
11074
11075          --  The only correct use of this pragma is on its own in a file, in
11076          --  which case it is specially processed (see Gnat1drv.Check_Bad_Body
11077          --  and Frontend, which use Sinput.L.Source_File_Is_Pragma_No_Body to
11078          --  check for a file containing nothing but a No_Body pragma). If we
11079          --  attempt to process it during normal semantics processing, it means
11080          --  it was misplaced.
11081
11082          when Pragma_No_Body =>
11083             GNAT_Pragma;
11084             Pragma_Misplaced;
11085
11086          ---------------
11087          -- No_Return --
11088          ---------------
11089
11090          --  pragma No_Return (procedure_LOCAL_NAME {, procedure_Local_Name});
11091
11092          when Pragma_No_Return => No_Return : declare
11093             Id    : Node_Id;
11094             E     : Entity_Id;
11095             Found : Boolean;
11096             Arg   : Node_Id;
11097
11098          begin
11099             Ada_2005_Pragma;
11100             Check_At_Least_N_Arguments (1);
11101
11102             --  Loop through arguments of pragma
11103
11104             Arg := Arg1;
11105             while Present (Arg) loop
11106                Check_Arg_Is_Local_Name (Arg);
11107                Id := Get_Pragma_Arg (Arg);
11108                Analyze (Id);
11109
11110                if not Is_Entity_Name (Id) then
11111                   Error_Pragma_Arg ("entity name required", Arg);
11112                end if;
11113
11114                if Etype (Id) = Any_Type then
11115                   raise Pragma_Exit;
11116                end if;
11117
11118                --  Loop to find matching procedures
11119
11120                E := Entity (Id);
11121                Found := False;
11122                while Present (E)
11123                  and then Scope (E) = Current_Scope
11124                loop
11125                   if Ekind_In (E, E_Procedure, E_Generic_Procedure) then
11126                      Set_No_Return (E);
11127
11128                      --  Set flag on any alias as well
11129
11130                      if Is_Overloadable (E) and then Present (Alias (E)) then
11131                         Set_No_Return (Alias (E));
11132                      end if;
11133
11134                      Found := True;
11135                   end if;
11136
11137                   exit when From_Aspect_Specification (N);
11138                   E := Homonym (E);
11139                end loop;
11140
11141                if not Found then
11142                   Error_Pragma_Arg ("no procedure & found for pragma%", Arg);
11143                end if;
11144
11145                Next (Arg);
11146             end loop;
11147          end No_Return;
11148
11149          -----------------
11150          -- No_Run_Time --
11151          -----------------
11152
11153          --  pragma No_Run_Time;
11154
11155          --  Note: this pragma is retained for backwards compatibility. See
11156          --  body of Rtsfind for full details on its handling.
11157
11158          when Pragma_No_Run_Time =>
11159             GNAT_Pragma;
11160             Check_Valid_Configuration_Pragma;
11161             Check_Arg_Count (0);
11162
11163             No_Run_Time_Mode           := True;
11164             Configurable_Run_Time_Mode := True;
11165
11166             --  Set Duration to 32 bits if word size is 32
11167
11168             if Ttypes.System_Word_Size = 32 then
11169                Duration_32_Bits_On_Target := True;
11170             end if;
11171
11172             --  Set appropriate restrictions
11173
11174             Set_Restriction (No_Finalization, N);
11175             Set_Restriction (No_Exception_Handlers, N);
11176             Set_Restriction (Max_Tasks, N, 0);
11177             Set_Restriction (No_Tasking, N);
11178
11179          ------------------------
11180          -- No_Strict_Aliasing --
11181          ------------------------
11182
11183          --  pragma No_Strict_Aliasing [([Entity =>] type_LOCAL_NAME)];
11184
11185          when Pragma_No_Strict_Aliasing => No_Strict_Aliasing : declare
11186             E_Id : Entity_Id;
11187
11188          begin
11189             GNAT_Pragma;
11190             Check_At_Most_N_Arguments (1);
11191
11192             if Arg_Count = 0 then
11193                Check_Valid_Configuration_Pragma;
11194                Opt.No_Strict_Aliasing := True;
11195
11196             else
11197                Check_Optional_Identifier (Arg2, Name_Entity);
11198                Check_Arg_Is_Local_Name (Arg1);
11199                E_Id := Entity (Get_Pragma_Arg (Arg1));
11200
11201                if E_Id = Any_Type then
11202                   return;
11203                elsif No (E_Id) or else not Is_Access_Type (E_Id) then
11204                   Error_Pragma_Arg ("pragma% requires access type", Arg1);
11205                end if;
11206
11207                Set_No_Strict_Aliasing (Implementation_Base_Type (E_Id));
11208             end if;
11209          end No_Strict_Aliasing;
11210
11211          -----------------------
11212          -- Normalize_Scalars --
11213          -----------------------
11214
11215          --  pragma Normalize_Scalars;
11216
11217          when Pragma_Normalize_Scalars =>
11218             Check_Ada_83_Warning;
11219             Check_Arg_Count (0);
11220             Check_Valid_Configuration_Pragma;
11221
11222             --  Normalize_Scalars creates false positives in CodePeer, and
11223             --  incorrect negative results in Alfa mode, so ignore this pragma
11224             --  in these modes.
11225
11226             if not (CodePeer_Mode or Alfa_Mode) then
11227                Normalize_Scalars := True;
11228                Init_Or_Norm_Scalars := True;
11229             end if;
11230
11231          -----------------
11232          -- Obsolescent --
11233          -----------------
11234
11235          --  pragma Obsolescent;
11236
11237          --  pragma Obsolescent (
11238          --    [Message =>] static_string_EXPRESSION
11239          --  [,[Version =>] Ada_05]]);
11240
11241          --  pragma Obsolescent (
11242          --    [Entity  =>] NAME
11243          --  [,[Message =>] static_string_EXPRESSION
11244          --  [,[Version =>] Ada_05]] );
11245
11246          when Pragma_Obsolescent => Obsolescent : declare
11247             Ename : Node_Id;
11248             Decl  : Node_Id;
11249
11250             procedure Set_Obsolescent (E : Entity_Id);
11251             --  Given an entity Ent, mark it as obsolescent if appropriate
11252
11253             ---------------------
11254             -- Set_Obsolescent --
11255             ---------------------
11256
11257             procedure Set_Obsolescent (E : Entity_Id) is
11258                Active : Boolean;
11259                Ent    : Entity_Id;
11260                S      : String_Id;
11261
11262             begin
11263                Active := True;
11264                Ent    := E;
11265
11266                --  Entity name was given
11267
11268                if Present (Ename) then
11269
11270                   --  If entity name matches, we are fine. Save entity in
11271                   --  pragma argument, for ASIS use.
11272
11273                   if Chars (Ename) = Chars (Ent) then
11274                      Set_Entity (Ename, Ent);
11275                      Generate_Reference (Ent, Ename);
11276
11277                   --  If entity name does not match, only possibility is an
11278                   --  enumeration literal from an enumeration type declaration.
11279
11280                   elsif Ekind (Ent) /= E_Enumeration_Type then
11281                      Error_Pragma
11282                        ("pragma % entity name does not match declaration");
11283
11284                   else
11285                      Ent := First_Literal (E);
11286                      loop
11287                         if No (Ent) then
11288                            Error_Pragma
11289                              ("pragma % entity name does not match any " &
11290                               "enumeration literal");
11291
11292                         elsif Chars (Ent) = Chars (Ename) then
11293                            Set_Entity (Ename, Ent);
11294                            Generate_Reference (Ent, Ename);
11295                            exit;
11296
11297                         else
11298                            Ent := Next_Literal (Ent);
11299                         end if;
11300                      end loop;
11301                   end if;
11302                end if;
11303
11304                --  Ent points to entity to be marked
11305
11306                if Arg_Count >= 1 then
11307
11308                   --  Deal with static string argument
11309
11310                   Check_Arg_Is_Static_Expression (Arg1, Standard_String);
11311                   S := Strval (Get_Pragma_Arg (Arg1));
11312
11313                   for J in 1 .. String_Length (S) loop
11314                      if not In_Character_Range (Get_String_Char (S, J)) then
11315                         Error_Pragma_Arg
11316                           ("pragma% argument does not allow wide characters",
11317                            Arg1);
11318                      end if;
11319                   end loop;
11320
11321                   Obsolescent_Warnings.Append
11322                     ((Ent => Ent, Msg => Strval (Get_Pragma_Arg (Arg1))));
11323
11324                   --  Check for Ada_05 parameter
11325
11326                   if Arg_Count /= 1 then
11327                      Check_Arg_Count (2);
11328
11329                      declare
11330                         Argx : constant Node_Id := Get_Pragma_Arg (Arg2);
11331
11332                      begin
11333                         Check_Arg_Is_Identifier (Argx);
11334
11335                         if Chars (Argx) /= Name_Ada_05 then
11336                            Error_Msg_Name_2 := Name_Ada_05;
11337                            Error_Pragma_Arg
11338                              ("only allowed argument for pragma% is %", Argx);
11339                         end if;
11340
11341                         if Ada_Version_Explicit < Ada_2005
11342                           or else not Warn_On_Ada_2005_Compatibility
11343                         then
11344                            Active := False;
11345                         end if;
11346                      end;
11347                   end if;
11348                end if;
11349
11350                --  Set flag if pragma active
11351
11352                if Active then
11353                   Set_Is_Obsolescent (Ent);
11354                end if;
11355
11356                return;
11357             end Set_Obsolescent;
11358
11359          --  Start of processing for pragma Obsolescent
11360
11361          begin
11362             GNAT_Pragma;
11363
11364             Check_At_Most_N_Arguments (3);
11365
11366             --  See if first argument specifies an entity name
11367
11368             if Arg_Count >= 1
11369               and then
11370                 (Chars (Arg1) = Name_Entity
11371                    or else
11372                      Nkind_In (Get_Pragma_Arg (Arg1), N_Character_Literal,
11373                                                       N_Identifier,
11374                                                       N_Operator_Symbol))
11375             then
11376                Ename := Get_Pragma_Arg (Arg1);
11377
11378                --  Eliminate first argument, so we can share processing
11379
11380                Arg1 := Arg2;
11381                Arg2 := Arg3;
11382                Arg_Count := Arg_Count - 1;
11383
11384             --  No Entity name argument given
11385
11386             else
11387                Ename := Empty;
11388             end if;
11389
11390             if Arg_Count >= 1 then
11391                Check_Optional_Identifier (Arg1, Name_Message);
11392
11393                if Arg_Count = 2 then
11394                   Check_Optional_Identifier (Arg2, Name_Version);
11395                end if;
11396             end if;
11397
11398             --  Get immediately preceding declaration
11399
11400             Decl := Prev (N);
11401             while Present (Decl) and then Nkind (Decl) = N_Pragma loop
11402                Prev (Decl);
11403             end loop;
11404
11405             --  Cases where we do not follow anything other than another pragma
11406
11407             if No (Decl) then
11408
11409                --  First case: library level compilation unit declaration with
11410                --  the pragma immediately following the declaration.
11411
11412                if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
11413                   Set_Obsolescent
11414                     (Defining_Entity (Unit (Parent (Parent (N)))));
11415                   return;
11416
11417                --  Case 2: library unit placement for package
11418
11419                else
11420                   declare
11421                      Ent : constant Entity_Id := Find_Lib_Unit_Name;
11422                   begin
11423                      if Is_Package_Or_Generic_Package (Ent) then
11424                         Set_Obsolescent (Ent);
11425                         return;
11426                      end if;
11427                   end;
11428                end if;
11429
11430             --  Cases where we must follow a declaration
11431
11432             else
11433                if         Nkind (Decl) not in N_Declaration
11434                  and then Nkind (Decl) not in N_Later_Decl_Item
11435                  and then Nkind (Decl) not in N_Generic_Declaration
11436                  and then Nkind (Decl) not in N_Renaming_Declaration
11437                then
11438                   Error_Pragma
11439                     ("pragma% misplaced, "
11440                      & "must immediately follow a declaration");
11441
11442                else
11443                   Set_Obsolescent (Defining_Entity (Decl));
11444                   return;
11445                end if;
11446             end if;
11447          end Obsolescent;
11448
11449          --------------
11450          -- Optimize --
11451          --------------
11452
11453          --  pragma Optimize (Time | Space | Off);
11454
11455          --  The actual check for optimize is done in Gigi. Note that this
11456          --  pragma does not actually change the optimization setting, it
11457          --  simply checks that it is consistent with the pragma.
11458
11459          when Pragma_Optimize =>
11460             Check_No_Identifiers;
11461             Check_Arg_Count (1);
11462             Check_Arg_Is_One_Of (Arg1, Name_Time, Name_Space, Name_Off);
11463
11464          ------------------------
11465          -- Optimize_Alignment --
11466          ------------------------
11467
11468          --  pragma Optimize_Alignment (Time | Space | Off);
11469
11470          when Pragma_Optimize_Alignment => Optimize_Alignment : begin
11471             GNAT_Pragma;
11472             Check_No_Identifiers;
11473             Check_Arg_Count (1);
11474             Check_Valid_Configuration_Pragma;
11475
11476             declare
11477                Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
11478             begin
11479                case Nam is
11480                   when Name_Time =>
11481                      Opt.Optimize_Alignment := 'T';
11482                   when Name_Space =>
11483                      Opt.Optimize_Alignment := 'S';
11484                   when Name_Off =>
11485                      Opt.Optimize_Alignment := 'O';
11486                   when others =>
11487                      Error_Pragma_Arg ("invalid argument for pragma%", Arg1);
11488                end case;
11489             end;
11490
11491             --  Set indication that mode is set locally. If we are in fact in a
11492             --  configuration pragma file, this setting is harmless since the
11493             --  switch will get reset anyway at the start of each unit.
11494
11495             Optimize_Alignment_Local := True;
11496          end Optimize_Alignment;
11497
11498          -------------
11499          -- Ordered --
11500          -------------
11501
11502          --  pragma Ordered (first_enumeration_subtype_LOCAL_NAME);
11503
11504          when Pragma_Ordered => Ordered : declare
11505             Assoc   : constant Node_Id := Arg1;
11506             Type_Id : Node_Id;
11507             Typ     : Entity_Id;
11508
11509          begin
11510             GNAT_Pragma;
11511             Check_No_Identifiers;
11512             Check_Arg_Count (1);
11513             Check_Arg_Is_Local_Name (Arg1);
11514
11515             Type_Id := Get_Pragma_Arg (Assoc);
11516             Find_Type (Type_Id);
11517             Typ := Entity (Type_Id);
11518
11519             if Typ = Any_Type then
11520                return;
11521             else
11522                Typ := Underlying_Type (Typ);
11523             end if;
11524
11525             if not Is_Enumeration_Type (Typ) then
11526                Error_Pragma ("pragma% must specify enumeration type");
11527             end if;
11528
11529             Check_First_Subtype (Arg1);
11530             Set_Has_Pragma_Ordered (Base_Type (Typ));
11531          end Ordered;
11532
11533          ----------
11534          -- Pack --
11535          ----------
11536
11537          --  pragma Pack (first_subtype_LOCAL_NAME);
11538
11539          when Pragma_Pack => Pack : declare
11540             Assoc   : constant Node_Id := Arg1;
11541             Type_Id : Node_Id;
11542             Typ     : Entity_Id;
11543             Ctyp    : Entity_Id;
11544             Ignore  : Boolean := False;
11545
11546          begin
11547             Check_No_Identifiers;
11548             Check_Arg_Count (1);
11549             Check_Arg_Is_Local_Name (Arg1);
11550
11551             Type_Id := Get_Pragma_Arg (Assoc);
11552             Find_Type (Type_Id);
11553             Typ := Entity (Type_Id);
11554
11555             if Typ = Any_Type
11556               or else Rep_Item_Too_Early (Typ, N)
11557             then
11558                return;
11559             else
11560                Typ := Underlying_Type (Typ);
11561             end if;
11562
11563             if not Is_Array_Type (Typ) and then not Is_Record_Type (Typ) then
11564                Error_Pragma ("pragma% must specify array or record type");
11565             end if;
11566
11567             Check_First_Subtype (Arg1);
11568             Check_Duplicate_Pragma (Typ);
11569
11570             --  Array type
11571
11572             if Is_Array_Type (Typ) then
11573                Ctyp := Component_Type (Typ);
11574
11575                --  Ignore pack that does nothing
11576
11577                if Known_Static_Esize (Ctyp)
11578                  and then Known_Static_RM_Size (Ctyp)
11579                  and then Esize (Ctyp) = RM_Size (Ctyp)
11580                  and then Addressable (Esize (Ctyp))
11581                then
11582                   Ignore := True;
11583                end if;
11584
11585                --  Process OK pragma Pack. Note that if there is a separate
11586                --  component clause present, the Pack will be cancelled. This
11587                --  processing is in Freeze.
11588
11589                if not Rep_Item_Too_Late (Typ, N) then
11590
11591                   --  In the context of static code analysis, we do not need
11592                   --  complex front-end expansions related to pragma Pack,
11593                   --  so disable handling of pragma Pack in these cases.
11594
11595                   if CodePeer_Mode or Alfa_Mode then
11596                      null;
11597
11598                   --  Don't attempt any packing for VM targets. We possibly
11599                   --  could deal with some cases of array bit-packing, but we
11600                   --  don't bother, since this is not a typical kind of
11601                   --  representation in the VM context anyway (and would not
11602                   --  for example work nicely with the debugger).
11603
11604                   elsif VM_Target /= No_VM then
11605                      if not GNAT_Mode then
11606                         Error_Pragma
11607                           ("?pragma% ignored in this configuration");
11608                      end if;
11609
11610                   --  Normal case where we do the pack action
11611
11612                   else
11613                      if not Ignore then
11614                         Set_Is_Packed            (Base_Type (Typ));
11615                         Set_Has_Non_Standard_Rep (Base_Type (Typ));
11616                      end if;
11617
11618                      Set_Has_Pragma_Pack (Base_Type (Typ));
11619                   end if;
11620                end if;
11621
11622             --  For record types, the pack is always effective
11623
11624             else pragma Assert (Is_Record_Type (Typ));
11625                if not Rep_Item_Too_Late (Typ, N) then
11626
11627                   --  Ignore pack request with warning in VM mode (skip warning
11628                   --  if we are compiling GNAT run time library).
11629
11630                   if VM_Target /= No_VM then
11631                      if not GNAT_Mode then
11632                         Error_Pragma
11633                           ("?pragma% ignored in this configuration");
11634                      end if;
11635
11636                   --  Normal case of pack request active
11637
11638                   else
11639                      Set_Is_Packed            (Base_Type (Typ));
11640                      Set_Has_Pragma_Pack      (Base_Type (Typ));
11641                      Set_Has_Non_Standard_Rep (Base_Type (Typ));
11642                   end if;
11643                end if;
11644             end if;
11645          end Pack;
11646
11647          ----------
11648          -- Page --
11649          ----------
11650
11651          --  pragma Page;
11652
11653          --  There is nothing to do here, since we did all the processing for
11654          --  this pragma in Par.Prag (so that it works properly even in syntax
11655          --  only mode).
11656
11657          when Pragma_Page =>
11658             null;
11659
11660          -------------
11661          -- Passive --
11662          -------------
11663
11664          --  pragma Passive [(PASSIVE_FORM)];
11665
11666          --  PASSIVE_FORM ::= Semaphore | No
11667
11668          when Pragma_Passive =>
11669             GNAT_Pragma;
11670
11671             if Nkind (Parent (N)) /= N_Task_Definition then
11672                Error_Pragma ("pragma% must be within task definition");
11673             end if;
11674
11675             if Arg_Count /= 0 then
11676                Check_Arg_Count (1);
11677                Check_Arg_Is_One_Of (Arg1, Name_Semaphore, Name_No);
11678             end if;
11679
11680          ----------------------------------
11681          -- Preelaborable_Initialization --
11682          ----------------------------------
11683
11684          --  pragma Preelaborable_Initialization (DIRECT_NAME);
11685
11686          when Pragma_Preelaborable_Initialization => Preelab_Init : declare
11687             Ent : Entity_Id;
11688
11689          begin
11690             Ada_2005_Pragma;
11691             Check_Arg_Count (1);
11692             Check_No_Identifiers;
11693             Check_Arg_Is_Identifier (Arg1);
11694             Check_Arg_Is_Local_Name (Arg1);
11695             Check_First_Subtype (Arg1);
11696             Ent := Entity (Get_Pragma_Arg (Arg1));
11697
11698             if not (Is_Private_Type (Ent)
11699                       or else
11700                     Is_Protected_Type (Ent)
11701                       or else
11702                     (Is_Generic_Type (Ent) and then Is_Derived_Type (Ent)))
11703             then
11704                Error_Pragma_Arg
11705                  ("pragma % can only be applied to private, formal derived or "
11706                   & "protected type",
11707                   Arg1);
11708             end if;
11709
11710             --  Give an error if the pragma is applied to a protected type that
11711             --  does not qualify (due to having entries, or due to components
11712             --  that do not qualify).
11713
11714             if Is_Protected_Type (Ent)
11715               and then not Has_Preelaborable_Initialization (Ent)
11716             then
11717                Error_Msg_N
11718                  ("protected type & does not have preelaborable " &
11719                   "initialization", Ent);
11720
11721             --  Otherwise mark the type as definitely having preelaborable
11722             --  initialization.
11723
11724             else
11725                Set_Known_To_Have_Preelab_Init (Ent);
11726             end if;
11727
11728             if Has_Pragma_Preelab_Init (Ent)
11729               and then Warn_On_Redundant_Constructs
11730             then
11731                Error_Pragma ("?duplicate pragma%!");
11732             else
11733                Set_Has_Pragma_Preelab_Init (Ent);
11734             end if;
11735          end Preelab_Init;
11736
11737          --------------------
11738          -- Persistent_BSS --
11739          --------------------
11740
11741          --  pragma Persistent_BSS [(object_NAME)];
11742
11743          when Pragma_Persistent_BSS => Persistent_BSS :  declare
11744             Decl : Node_Id;
11745             Ent  : Entity_Id;
11746             Prag : Node_Id;
11747
11748          begin
11749             GNAT_Pragma;
11750             Check_At_Most_N_Arguments (1);
11751
11752             --  Case of application to specific object (one argument)
11753
11754             if Arg_Count = 1 then
11755                Check_Arg_Is_Library_Level_Local_Name (Arg1);
11756
11757                if not Is_Entity_Name (Get_Pragma_Arg (Arg1))
11758                  or else not
11759                   Ekind_In (Entity (Get_Pragma_Arg (Arg1)), E_Variable,
11760                                                             E_Constant)
11761                then
11762                   Error_Pragma_Arg ("pragma% only applies to objects", Arg1);
11763                end if;
11764
11765                Ent := Entity (Get_Pragma_Arg (Arg1));
11766                Decl := Parent (Ent);
11767
11768                if Rep_Item_Too_Late (Ent, N) then
11769                   return;
11770                end if;
11771
11772                if Present (Expression (Decl)) then
11773                   Error_Pragma_Arg
11774                     ("object for pragma% cannot have initialization", Arg1);
11775                end if;
11776
11777                if not Is_Potentially_Persistent_Type (Etype (Ent)) then
11778                   Error_Pragma_Arg
11779                     ("object type for pragma% is not potentially persistent",
11780                      Arg1);
11781                end if;
11782
11783                Check_Duplicate_Pragma (Ent);
11784
11785                Prag :=
11786                  Make_Linker_Section_Pragma
11787                    (Ent, Sloc (N), ".persistent.bss");
11788                Insert_After (N, Prag);
11789                Analyze (Prag);
11790
11791             --  Case of use as configuration pragma with no arguments
11792
11793             else
11794                Check_Valid_Configuration_Pragma;
11795                Persistent_BSS_Mode := True;
11796             end if;
11797          end Persistent_BSS;
11798
11799          -------------
11800          -- Polling --
11801          -------------
11802
11803          --  pragma Polling (ON | OFF);
11804
11805          when Pragma_Polling =>
11806             GNAT_Pragma;
11807             Check_Arg_Count (1);
11808             Check_No_Identifiers;
11809             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
11810             Polling_Required := (Chars (Get_Pragma_Arg (Arg1)) = Name_On);
11811
11812          -------------------
11813          -- Postcondition --
11814          -------------------
11815
11816          --  pragma Postcondition ([Check   =>] Boolean_EXPRESSION
11817          --                      [,[Message =>] String_EXPRESSION]);
11818
11819          when Pragma_Postcondition => Postcondition : declare
11820             In_Body : Boolean;
11821             pragma Warnings (Off, In_Body);
11822
11823          begin
11824             GNAT_Pragma;
11825             Check_At_Least_N_Arguments (1);
11826             Check_At_Most_N_Arguments (2);
11827             Check_Optional_Identifier (Arg1, Name_Check);
11828
11829             --  All we need to do here is call the common check procedure,
11830             --  the remainder of the processing is found in Sem_Ch6/Sem_Ch7.
11831
11832             Check_Precondition_Postcondition (In_Body);
11833          end Postcondition;
11834
11835          ------------------
11836          -- Precondition --
11837          ------------------
11838
11839          --  pragma Precondition ([Check   =>] Boolean_EXPRESSION
11840          --                     [,[Message =>] String_EXPRESSION]);
11841
11842          when Pragma_Precondition => Precondition : declare
11843             In_Body : Boolean;
11844
11845          begin
11846             GNAT_Pragma;
11847             Check_At_Least_N_Arguments (1);
11848             Check_At_Most_N_Arguments (2);
11849             Check_Optional_Identifier (Arg1, Name_Check);
11850             Check_Precondition_Postcondition (In_Body);
11851
11852             --  If in spec, nothing more to do. If in body, then we convert the
11853             --  pragma to pragma Check (Precondition, cond [, msg]). Note we do
11854             --  this whether or not precondition checks are enabled. That works
11855             --  fine since pragma Check will do this check, and will also
11856             --  analyze the condition itself in the proper context.
11857
11858             if In_Body then
11859                Rewrite (N,
11860                  Make_Pragma (Loc,
11861                    Chars => Name_Check,
11862                    Pragma_Argument_Associations => New_List (
11863                      Make_Pragma_Argument_Association (Loc,
11864                        Expression => Make_Identifier (Loc, Name_Precondition)),
11865
11866                      Make_Pragma_Argument_Association (Sloc (Arg1),
11867                        Expression => Relocate_Node (Get_Pragma_Arg (Arg1))))));
11868
11869                if Arg_Count = 2 then
11870                   Append_To (Pragma_Argument_Associations (N),
11871                     Make_Pragma_Argument_Association (Sloc (Arg2),
11872                       Expression => Relocate_Node (Get_Pragma_Arg (Arg2))));
11873                end if;
11874
11875                Analyze (N);
11876             end if;
11877          end Precondition;
11878
11879          ---------------
11880          -- Predicate --
11881          ---------------
11882
11883          --  pragma Predicate
11884          --    ([Entity =>] type_LOCAL_NAME,
11885          --     [Check  =>] EXPRESSION);
11886
11887          when Pragma_Predicate => Predicate : declare
11888             Type_Id : Node_Id;
11889             Typ     : Entity_Id;
11890
11891             Discard : Boolean;
11892             pragma Unreferenced (Discard);
11893
11894          begin
11895             GNAT_Pragma;
11896             Check_Arg_Count (2);
11897             Check_Optional_Identifier (Arg1, Name_Entity);
11898             Check_Optional_Identifier (Arg2, Name_Check);
11899
11900             Check_Arg_Is_Local_Name (Arg1);
11901
11902             Type_Id := Get_Pragma_Arg (Arg1);
11903             Find_Type (Type_Id);
11904             Typ := Entity (Type_Id);
11905
11906             if Typ = Any_Type then
11907                return;
11908             end if;
11909
11910             --  The remaining processing is simply to link the pragma on to
11911             --  the rep item chain, for processing when the type is frozen.
11912             --  This is accomplished by a call to Rep_Item_Too_Late. We also
11913             --  mark the type as having predicates.
11914
11915             Set_Has_Predicates (Typ);
11916             Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
11917          end Predicate;
11918
11919          ------------------
11920          -- Preelaborate --
11921          ------------------
11922
11923          --  pragma Preelaborate [(library_unit_NAME)];
11924
11925          --  Set the flag Is_Preelaborated of program unit name entity
11926
11927          when Pragma_Preelaborate => Preelaborate : declare
11928             Pa  : constant Node_Id   := Parent (N);
11929             Pk  : constant Node_Kind := Nkind (Pa);
11930             Ent : Entity_Id;
11931
11932          begin
11933             Check_Ada_83_Warning;
11934             Check_Valid_Library_Unit_Pragma;
11935
11936             if Nkind (N) = N_Null_Statement then
11937                return;
11938             end if;
11939
11940             Ent := Find_Lib_Unit_Name;
11941             Check_Duplicate_Pragma (Ent);
11942
11943             --  This filters out pragmas inside generic parent then
11944             --  show up inside instantiation
11945
11946             if Present (Ent)
11947               and then not (Pk = N_Package_Specification
11948                              and then Present (Generic_Parent (Pa)))
11949             then
11950                if not Debug_Flag_U then
11951                   Set_Is_Preelaborated (Ent);
11952                   Set_Suppress_Elaboration_Warnings (Ent);
11953                end if;
11954             end if;
11955          end Preelaborate;
11956
11957          ---------------------
11958          -- Preelaborate_05 --
11959          ---------------------
11960
11961          --  pragma Preelaborate_05 [(library_unit_NAME)];
11962
11963          --  This pragma is useable only in GNAT_Mode, where it is used like
11964          --  pragma Preelaborate but it is only effective in Ada 2005 mode
11965          --  (otherwise it is ignored). This is used to implement AI-362 which
11966          --  recategorizes some run-time packages in Ada 2005 mode.
11967
11968          when Pragma_Preelaborate_05 => Preelaborate_05 : declare
11969             Ent : Entity_Id;
11970
11971          begin
11972             GNAT_Pragma;
11973             Check_Valid_Library_Unit_Pragma;
11974
11975             if not GNAT_Mode then
11976                Error_Pragma ("pragma% only available in GNAT mode");
11977             end if;
11978
11979             if Nkind (N) = N_Null_Statement then
11980                return;
11981             end if;
11982
11983             --  This is one of the few cases where we need to test the value of
11984             --  Ada_Version_Explicit rather than Ada_Version (which is always
11985             --  set to Ada_2012 in a predefined unit), we need to know the
11986             --  explicit version set to know if this pragma is active.
11987
11988             if Ada_Version_Explicit >= Ada_2005 then
11989                Ent := Find_Lib_Unit_Name;
11990                Set_Is_Preelaborated (Ent);
11991                Set_Suppress_Elaboration_Warnings (Ent);
11992             end if;
11993          end Preelaborate_05;
11994
11995          --------------
11996          -- Priority --
11997          --------------
11998
11999          --  pragma Priority (EXPRESSION);
12000
12001          when Pragma_Priority => Priority : declare
12002             P   : constant Node_Id := Parent (N);
12003             Arg : Node_Id;
12004
12005          begin
12006             Check_No_Identifiers;
12007             Check_Arg_Count (1);
12008
12009             --  Subprogram case
12010
12011             if Nkind (P) = N_Subprogram_Body then
12012                Check_In_Main_Program;
12013
12014                Arg := Get_Pragma_Arg (Arg1);
12015                Analyze_And_Resolve (Arg, Standard_Integer);
12016
12017                --  Must be static
12018
12019                if not Is_Static_Expression (Arg) then
12020                   Flag_Non_Static_Expr
12021                     ("main subprogram priority is not static!", Arg);
12022                   raise Pragma_Exit;
12023
12024                --  If constraint error, then we already signalled an error
12025
12026                elsif Raises_Constraint_Error (Arg) then
12027                   null;
12028
12029                --  Otherwise check in range
12030
12031                else
12032                   declare
12033                      Val : constant Uint := Expr_Value (Arg);
12034
12035                   begin
12036                      if Val < 0
12037                        or else Val > Expr_Value (Expression
12038                                        (Parent (RTE (RE_Max_Priority))))
12039                      then
12040                         Error_Pragma_Arg
12041                           ("main subprogram priority is out of range", Arg1);
12042                      end if;
12043                   end;
12044                end if;
12045
12046                Set_Main_Priority
12047                     (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
12048
12049                --  Load an arbitrary entity from System.Tasking to make sure
12050                --  this package is implicitly with'ed, since we need to have
12051                --  the tasking run-time active for the pragma Priority to have
12052                --  any effect.
12053
12054                declare
12055                   Discard : Entity_Id;
12056                   pragma Warnings (Off, Discard);
12057                begin
12058                   Discard := RTE (RE_Task_List);
12059                end;
12060
12061             --  Task or Protected, must be of type Integer
12062
12063             elsif Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
12064                Arg := Get_Pragma_Arg (Arg1);
12065
12066                --  The expression must be analyzed in the special manner
12067                --  described in "Handling of Default and Per-Object
12068                --  Expressions" in sem.ads.
12069
12070                Preanalyze_Spec_Expression (Arg, Standard_Integer);
12071
12072                if not Is_Static_Expression (Arg) then
12073                   Check_Restriction (Static_Priorities, Arg);
12074                end if;
12075
12076             --  Anything else is incorrect
12077
12078             else
12079                Pragma_Misplaced;
12080             end if;
12081
12082             if Has_Pragma_Priority (P) then
12083                Error_Pragma ("duplicate pragma% not allowed");
12084             else
12085                Set_Has_Pragma_Priority (P, True);
12086
12087                if Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
12088                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
12089                   --  exp_ch9 should use this ???
12090                end if;
12091             end if;
12092          end Priority;
12093
12094          -----------------------------------
12095          -- Priority_Specific_Dispatching --
12096          -----------------------------------
12097
12098          --  pragma Priority_Specific_Dispatching (
12099          --    policy_IDENTIFIER,
12100          --    first_priority_EXPRESSION,
12101          --    last_priority_EXPRESSION);
12102
12103          when Pragma_Priority_Specific_Dispatching =>
12104          Priority_Specific_Dispatching : declare
12105             Prio_Id : constant Entity_Id := RTE (RE_Any_Priority);
12106             --  This is the entity System.Any_Priority;
12107
12108             DP          : Character;
12109             Lower_Bound : Node_Id;
12110             Upper_Bound : Node_Id;
12111             Lower_Val   : Uint;
12112             Upper_Val   : Uint;
12113
12114          begin
12115             Ada_2005_Pragma;
12116             Check_Arg_Count (3);
12117             Check_No_Identifiers;
12118             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
12119             Check_Valid_Configuration_Pragma;
12120             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
12121             DP := Fold_Upper (Name_Buffer (1));
12122
12123             Lower_Bound := Get_Pragma_Arg (Arg2);
12124             Check_Arg_Is_Static_Expression (Lower_Bound, Standard_Integer);
12125             Lower_Val := Expr_Value (Lower_Bound);
12126
12127             Upper_Bound := Get_Pragma_Arg (Arg3);
12128             Check_Arg_Is_Static_Expression (Upper_Bound, Standard_Integer);
12129             Upper_Val := Expr_Value (Upper_Bound);
12130
12131             --  It is not allowed to use Task_Dispatching_Policy and
12132             --  Priority_Specific_Dispatching in the same partition.
12133
12134             if Task_Dispatching_Policy /= ' ' then
12135                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
12136                Error_Pragma
12137                  ("pragma% incompatible with Task_Dispatching_Policy#");
12138
12139             --  Check lower bound in range
12140
12141             elsif Lower_Val < Expr_Value (Type_Low_Bound (Prio_Id))
12142                     or else
12143                   Lower_Val > Expr_Value (Type_High_Bound (Prio_Id))
12144             then
12145                Error_Pragma_Arg
12146                  ("first_priority is out of range", Arg2);
12147
12148             --  Check upper bound in range
12149
12150             elsif Upper_Val < Expr_Value (Type_Low_Bound (Prio_Id))
12151                     or else
12152                   Upper_Val > Expr_Value (Type_High_Bound (Prio_Id))
12153             then
12154                Error_Pragma_Arg
12155                  ("last_priority is out of range", Arg3);
12156
12157             --  Check that the priority range is valid
12158
12159             elsif Lower_Val > Upper_Val then
12160                Error_Pragma
12161                  ("last_priority_expression must be greater than" &
12162                   " or equal to first_priority_expression");
12163
12164             --  Store the new policy, but always preserve System_Location since
12165             --  we like the error message with the run-time name.
12166
12167             else
12168                --  Check overlapping in the priority ranges specified in other
12169                --  Priority_Specific_Dispatching pragmas within the same
12170                --  partition. We can only check those we know about!
12171
12172                for J in
12173                   Specific_Dispatching.First .. Specific_Dispatching.Last
12174                loop
12175                   if Specific_Dispatching.Table (J).First_Priority in
12176                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
12177                   or else Specific_Dispatching.Table (J).Last_Priority in
12178                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
12179                   then
12180                      Error_Msg_Sloc :=
12181                        Specific_Dispatching.Table (J).Pragma_Loc;
12182                         Error_Pragma
12183                           ("priority range overlaps with "
12184                            & "Priority_Specific_Dispatching#");
12185                   end if;
12186                end loop;
12187
12188                --  The use of Priority_Specific_Dispatching is incompatible
12189                --  with Task_Dispatching_Policy.
12190
12191                if Task_Dispatching_Policy /= ' ' then
12192                   Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
12193                      Error_Pragma
12194                        ("Priority_Specific_Dispatching incompatible "
12195                         & "with Task_Dispatching_Policy#");
12196                end if;
12197
12198                --  The use of Priority_Specific_Dispatching forces ceiling
12199                --  locking policy.
12200
12201                if Locking_Policy /= ' ' and then Locking_Policy /= 'C' then
12202                   Error_Msg_Sloc := Locking_Policy_Sloc;
12203                      Error_Pragma
12204                        ("Priority_Specific_Dispatching incompatible "
12205                         & "with Locking_Policy#");
12206
12207                --  Set the Ceiling_Locking policy, but preserve System_Location
12208                --  since we like the error message with the run time name.
12209
12210                else
12211                   Locking_Policy := 'C';
12212
12213                   if Locking_Policy_Sloc /= System_Location then
12214                      Locking_Policy_Sloc := Loc;
12215                   end if;
12216                end if;
12217
12218                --  Add entry in the table
12219
12220                Specific_Dispatching.Append
12221                     ((Dispatching_Policy => DP,
12222                       First_Priority     => UI_To_Int (Lower_Val),
12223                       Last_Priority      => UI_To_Int (Upper_Val),
12224                       Pragma_Loc         => Loc));
12225             end if;
12226          end Priority_Specific_Dispatching;
12227
12228          -------------
12229          -- Profile --
12230          -------------
12231
12232          --  pragma Profile (profile_IDENTIFIER);
12233
12234          --  profile_IDENTIFIER => Restricted | Ravenscar
12235
12236          when Pragma_Profile =>
12237             Ada_2005_Pragma;
12238             Check_Arg_Count (1);
12239             Check_Valid_Configuration_Pragma;
12240             Check_No_Identifiers;
12241
12242             declare
12243                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
12244
12245             begin
12246                if Chars (Argx) = Name_Ravenscar then
12247                   Set_Ravenscar_Profile (N);
12248
12249                elsif Chars (Argx) = Name_Restricted then
12250                   Set_Profile_Restrictions
12251                     (Restricted,
12252                      N, Warn => Treat_Restrictions_As_Warnings);
12253
12254                elsif Chars (Argx) = Name_No_Implementation_Extensions then
12255                   Set_Profile_Restrictions
12256                     (No_Implementation_Extensions,
12257                      N, Warn => Treat_Restrictions_As_Warnings);
12258
12259                else
12260                   Error_Pragma_Arg ("& is not a valid profile", Argx);
12261                end if;
12262             end;
12263
12264          ----------------------
12265          -- Profile_Warnings --
12266          ----------------------
12267
12268          --  pragma Profile_Warnings (profile_IDENTIFIER);
12269
12270          --  profile_IDENTIFIER => Restricted | Ravenscar
12271
12272          when Pragma_Profile_Warnings =>
12273             GNAT_Pragma;
12274             Check_Arg_Count (1);
12275             Check_Valid_Configuration_Pragma;
12276             Check_No_Identifiers;
12277
12278             declare
12279                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
12280
12281             begin
12282                if Chars (Argx) = Name_Ravenscar then
12283                   Set_Profile_Restrictions (Ravenscar, N, Warn => True);
12284
12285                elsif Chars (Argx) = Name_Restricted then
12286                   Set_Profile_Restrictions (Restricted, N, Warn => True);
12287
12288                elsif Chars (Argx) = Name_No_Implementation_Extensions then
12289                   Set_Profile_Restrictions
12290                     (No_Implementation_Extensions, N, Warn => True);
12291
12292                else
12293                   Error_Pragma_Arg ("& is not a valid profile", Argx);
12294                end if;
12295             end;
12296
12297          --------------------------
12298          -- Propagate_Exceptions --
12299          --------------------------
12300
12301          --  pragma Propagate_Exceptions;
12302
12303          --  Note: this pragma is obsolete and has no effect
12304
12305          when Pragma_Propagate_Exceptions =>
12306             GNAT_Pragma;
12307             Check_Arg_Count (0);
12308
12309             if In_Extended_Main_Source_Unit (N) then
12310                Propagate_Exceptions := True;
12311             end if;
12312
12313          ------------------
12314          -- Psect_Object --
12315          ------------------
12316
12317          --  pragma Psect_Object (
12318          --        [Internal =>] LOCAL_NAME,
12319          --     [, [External =>] EXTERNAL_SYMBOL]
12320          --     [, [Size     =>] EXTERNAL_SYMBOL]);
12321
12322          when Pragma_Psect_Object | Pragma_Common_Object =>
12323          Psect_Object : declare
12324             Args  : Args_List (1 .. 3);
12325             Names : constant Name_List (1 .. 3) := (
12326                       Name_Internal,
12327                       Name_External,
12328                       Name_Size);
12329
12330             Internal : Node_Id renames Args (1);
12331             External : Node_Id renames Args (2);
12332             Size     : Node_Id renames Args (3);
12333
12334             Def_Id : Entity_Id;
12335
12336             procedure Check_Too_Long (Arg : Node_Id);
12337             --  Posts message if the argument is an identifier with more
12338             --  than 31 characters, or a string literal with more than
12339             --  31 characters, and we are operating under VMS
12340
12341             --------------------
12342             -- Check_Too_Long --
12343             --------------------
12344
12345             procedure Check_Too_Long (Arg : Node_Id) is
12346                X : constant Node_Id := Original_Node (Arg);
12347
12348             begin
12349                if not Nkind_In (X, N_String_Literal, N_Identifier) then
12350                   Error_Pragma_Arg
12351                     ("inappropriate argument for pragma %", Arg);
12352                end if;
12353
12354                if OpenVMS_On_Target then
12355                   if (Nkind (X) = N_String_Literal
12356                        and then String_Length (Strval (X)) > 31)
12357                     or else
12358                      (Nkind (X) = N_Identifier
12359                        and then Length_Of_Name (Chars (X)) > 31)
12360                   then
12361                      Error_Pragma_Arg
12362                        ("argument for pragma % is longer than 31 characters",
12363                         Arg);
12364                   end if;
12365                end if;
12366             end Check_Too_Long;
12367
12368          --  Start of processing for Common_Object/Psect_Object
12369
12370          begin
12371             GNAT_Pragma;
12372             Gather_Associations (Names, Args);
12373             Process_Extended_Import_Export_Internal_Arg (Internal);
12374
12375             Def_Id := Entity (Internal);
12376
12377             if not Ekind_In (Def_Id, E_Constant, E_Variable) then
12378                Error_Pragma_Arg
12379                  ("pragma% must designate an object", Internal);
12380             end if;
12381
12382             Check_Too_Long (Internal);
12383
12384             if Is_Imported (Def_Id) or else Is_Exported (Def_Id) then
12385                Error_Pragma_Arg
12386                  ("cannot use pragma% for imported/exported object",
12387                   Internal);
12388             end if;
12389
12390             if Is_Concurrent_Type (Etype (Internal)) then
12391                Error_Pragma_Arg
12392                  ("cannot specify pragma % for task/protected object",
12393                   Internal);
12394             end if;
12395
12396             if Has_Rep_Pragma (Def_Id, Name_Common_Object)
12397                  or else
12398                Has_Rep_Pragma (Def_Id, Name_Psect_Object)
12399             then
12400                Error_Msg_N ("?duplicate Common/Psect_Object pragma", N);
12401             end if;
12402
12403             if Ekind (Def_Id) = E_Constant then
12404                Error_Pragma_Arg
12405                  ("cannot specify pragma % for a constant", Internal);
12406             end if;
12407
12408             if Is_Record_Type (Etype (Internal)) then
12409                declare
12410                   Ent  : Entity_Id;
12411                   Decl : Entity_Id;
12412
12413                begin
12414                   Ent := First_Entity (Etype (Internal));
12415                   while Present (Ent) loop
12416                      Decl := Declaration_Node (Ent);
12417
12418                      if Ekind (Ent) = E_Component
12419                        and then Nkind (Decl) = N_Component_Declaration
12420                        and then Present (Expression (Decl))
12421                        and then Warn_On_Export_Import
12422                      then
12423                         Error_Msg_N
12424                           ("?object for pragma % has defaults", Internal);
12425                         exit;
12426
12427                      else
12428                         Next_Entity (Ent);
12429                      end if;
12430                   end loop;
12431                end;
12432             end if;
12433
12434             if Present (Size) then
12435                Check_Too_Long (Size);
12436             end if;
12437
12438             if Present (External) then
12439                Check_Arg_Is_External_Name (External);
12440                Check_Too_Long (External);
12441             end if;
12442
12443             --  If all error tests pass, link pragma on to the rep item chain
12444
12445             Record_Rep_Item (Def_Id, N);
12446          end Psect_Object;
12447
12448          ----------
12449          -- Pure --
12450          ----------
12451
12452          --  pragma Pure [(library_unit_NAME)];
12453
12454          when Pragma_Pure => Pure : declare
12455             Ent : Entity_Id;
12456
12457          begin
12458             Check_Ada_83_Warning;
12459             Check_Valid_Library_Unit_Pragma;
12460
12461             if Nkind (N) = N_Null_Statement then
12462                return;
12463             end if;
12464
12465             Ent := Find_Lib_Unit_Name;
12466             Set_Is_Pure (Ent);
12467             Set_Has_Pragma_Pure (Ent);
12468             Set_Suppress_Elaboration_Warnings (Ent);
12469          end Pure;
12470
12471          -------------
12472          -- Pure_05 --
12473          -------------
12474
12475          --  pragma Pure_05 [(library_unit_NAME)];
12476
12477          --  This pragma is useable only in GNAT_Mode, where it is used like
12478          --  pragma Pure but it is only effective in Ada 2005 mode (otherwise
12479          --  it is ignored). It may be used after a pragma Preelaborate, in
12480          --  which case it overrides the effect of the pragma Preelaborate.
12481          --  This is used to implement AI-362 which recategorizes some run-time
12482          --  packages in Ada 2005 mode.
12483
12484          when Pragma_Pure_05 => Pure_05 : declare
12485             Ent : Entity_Id;
12486
12487          begin
12488             GNAT_Pragma;
12489             Check_Valid_Library_Unit_Pragma;
12490
12491             if not GNAT_Mode then
12492                Error_Pragma ("pragma% only available in GNAT mode");
12493             end if;
12494
12495             if Nkind (N) = N_Null_Statement then
12496                return;
12497             end if;
12498
12499             --  This is one of the few cases where we need to test the value of
12500             --  Ada_Version_Explicit rather than Ada_Version (which is always
12501             --  set to Ada_2012 in a predefined unit), we need to know the
12502             --  explicit version set to know if this pragma is active.
12503
12504             if Ada_Version_Explicit >= Ada_2005 then
12505                Ent := Find_Lib_Unit_Name;
12506                Set_Is_Preelaborated (Ent, False);
12507                Set_Is_Pure (Ent);
12508                Set_Suppress_Elaboration_Warnings (Ent);
12509             end if;
12510          end Pure_05;
12511
12512          -------------------
12513          -- Pure_Function --
12514          -------------------
12515
12516          --  pragma Pure_Function ([Entity =>] function_LOCAL_NAME);
12517
12518          when Pragma_Pure_Function => Pure_Function : declare
12519             E_Id      : Node_Id;
12520             E         : Entity_Id;
12521             Def_Id    : Entity_Id;
12522             Effective : Boolean := False;
12523
12524          begin
12525             GNAT_Pragma;
12526             Check_Arg_Count (1);
12527             Check_Optional_Identifier (Arg1, Name_Entity);
12528             Check_Arg_Is_Local_Name (Arg1);
12529             E_Id := Get_Pragma_Arg (Arg1);
12530
12531             if Error_Posted (E_Id) then
12532                return;
12533             end if;
12534
12535             --  Loop through homonyms (overloadings) of referenced entity
12536
12537             E := Entity (E_Id);
12538
12539             if Present (E) then
12540                loop
12541                   Def_Id := Get_Base_Subprogram (E);
12542
12543                   if not Ekind_In (Def_Id, E_Function,
12544                                            E_Generic_Function,
12545                                            E_Operator)
12546                   then
12547                      Error_Pragma_Arg
12548                        ("pragma% requires a function name", Arg1);
12549                   end if;
12550
12551                   Set_Is_Pure (Def_Id);
12552
12553                   if not Has_Pragma_Pure_Function (Def_Id) then
12554                      Set_Has_Pragma_Pure_Function (Def_Id);
12555                      Effective := True;
12556                   end if;
12557
12558                   exit when From_Aspect_Specification (N);
12559                   E := Homonym (E);
12560                   exit when No (E) or else Scope (E) /= Current_Scope;
12561                end loop;
12562
12563                if not Effective
12564                  and then Warn_On_Redundant_Constructs
12565                then
12566                   Error_Msg_NE
12567                     ("pragma Pure_Function on& is redundant?",
12568                      N, Entity (E_Id));
12569                end if;
12570             end if;
12571          end Pure_Function;
12572
12573          --------------------
12574          -- Queuing_Policy --
12575          --------------------
12576
12577          --  pragma Queuing_Policy (policy_IDENTIFIER);
12578
12579          when Pragma_Queuing_Policy => declare
12580             QP : Character;
12581
12582          begin
12583             Check_Ada_83_Warning;
12584             Check_Arg_Count (1);
12585             Check_No_Identifiers;
12586             Check_Arg_Is_Queuing_Policy (Arg1);
12587             Check_Valid_Configuration_Pragma;
12588             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
12589             QP := Fold_Upper (Name_Buffer (1));
12590
12591             if Queuing_Policy /= ' '
12592               and then Queuing_Policy /= QP
12593             then
12594                Error_Msg_Sloc := Queuing_Policy_Sloc;
12595                Error_Pragma ("queuing policy incompatible with policy#");
12596
12597             --  Set new policy, but always preserve System_Location since we
12598             --  like the error message with the run time name.
12599
12600             else
12601                Queuing_Policy := QP;
12602
12603                if Queuing_Policy_Sloc /= System_Location then
12604                   Queuing_Policy_Sloc := Loc;
12605                end if;
12606             end if;
12607          end;
12608
12609          -----------------------
12610          -- Relative_Deadline --
12611          -----------------------
12612
12613          --  pragma Relative_Deadline (time_span_EXPRESSION);
12614
12615          when Pragma_Relative_Deadline => Relative_Deadline : declare
12616             P   : constant Node_Id := Parent (N);
12617             Arg : Node_Id;
12618
12619          begin
12620             Ada_2005_Pragma;
12621             Check_No_Identifiers;
12622             Check_Arg_Count (1);
12623
12624             Arg := Get_Pragma_Arg (Arg1);
12625
12626             --  The expression must be analyzed in the special manner described
12627             --  in "Handling of Default and Per-Object Expressions" in sem.ads.
12628
12629             Preanalyze_Spec_Expression (Arg, RTE (RE_Time_Span));
12630
12631             --  Subprogram case
12632
12633             if Nkind (P) = N_Subprogram_Body then
12634                Check_In_Main_Program;
12635
12636             --  Tasks
12637
12638             elsif Nkind (P) = N_Task_Definition then
12639                null;
12640
12641             --  Anything else is incorrect
12642
12643             else
12644                Pragma_Misplaced;
12645             end if;
12646
12647             if Has_Relative_Deadline_Pragma (P) then
12648                Error_Pragma ("duplicate pragma% not allowed");
12649             else
12650                Set_Has_Relative_Deadline_Pragma (P, True);
12651
12652                if Nkind (P) = N_Task_Definition then
12653                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
12654                end if;
12655             end if;
12656          end Relative_Deadline;
12657
12658          ---------------------------
12659          -- Remote_Call_Interface --
12660          ---------------------------
12661
12662          --  pragma Remote_Call_Interface [(library_unit_NAME)];
12663
12664          when Pragma_Remote_Call_Interface => Remote_Call_Interface : declare
12665             Cunit_Node : Node_Id;
12666             Cunit_Ent  : Entity_Id;
12667             K          : Node_Kind;
12668
12669          begin
12670             Check_Ada_83_Warning;
12671             Check_Valid_Library_Unit_Pragma;
12672
12673             if Nkind (N) = N_Null_Statement then
12674                return;
12675             end if;
12676
12677             Cunit_Node := Cunit (Current_Sem_Unit);
12678             K          := Nkind (Unit (Cunit_Node));
12679             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12680
12681             if K = N_Package_Declaration
12682               or else K = N_Generic_Package_Declaration
12683               or else K = N_Subprogram_Declaration
12684               or else K = N_Generic_Subprogram_Declaration
12685               or else (K = N_Subprogram_Body
12686                          and then Acts_As_Spec (Unit (Cunit_Node)))
12687             then
12688                null;
12689             else
12690                Error_Pragma (
12691                  "pragma% must apply to package or subprogram declaration");
12692             end if;
12693
12694             Set_Is_Remote_Call_Interface (Cunit_Ent);
12695          end Remote_Call_Interface;
12696
12697          ------------------
12698          -- Remote_Types --
12699          ------------------
12700
12701          --  pragma Remote_Types [(library_unit_NAME)];
12702
12703          when Pragma_Remote_Types => Remote_Types : declare
12704             Cunit_Node : Node_Id;
12705             Cunit_Ent  : Entity_Id;
12706
12707          begin
12708             Check_Ada_83_Warning;
12709             Check_Valid_Library_Unit_Pragma;
12710
12711             if Nkind (N) = N_Null_Statement then
12712                return;
12713             end if;
12714
12715             Cunit_Node := Cunit (Current_Sem_Unit);
12716             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12717
12718             if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
12719                                                 N_Generic_Package_Declaration)
12720             then
12721                Error_Pragma
12722                  ("pragma% can only apply to a package declaration");
12723             end if;
12724
12725             Set_Is_Remote_Types (Cunit_Ent);
12726          end Remote_Types;
12727
12728          ---------------
12729          -- Ravenscar --
12730          ---------------
12731
12732          --  pragma Ravenscar;
12733
12734          when Pragma_Ravenscar =>
12735             GNAT_Pragma;
12736             Check_Arg_Count (0);
12737             Check_Valid_Configuration_Pragma;
12738             Set_Ravenscar_Profile (N);
12739
12740             if Warn_On_Obsolescent_Feature then
12741                Error_Msg_N ("pragma Ravenscar is an obsolescent feature?", N);
12742                Error_Msg_N ("|use pragma Profile (Ravenscar) instead", N);
12743             end if;
12744
12745          -------------------------
12746          -- Restricted_Run_Time --
12747          -------------------------
12748
12749          --  pragma Restricted_Run_Time;
12750
12751          when Pragma_Restricted_Run_Time =>
12752             GNAT_Pragma;
12753             Check_Arg_Count (0);
12754             Check_Valid_Configuration_Pragma;
12755             Set_Profile_Restrictions
12756               (Restricted, N, Warn => Treat_Restrictions_As_Warnings);
12757
12758             if Warn_On_Obsolescent_Feature then
12759                Error_Msg_N
12760                  ("pragma Restricted_Run_Time is an obsolescent feature?", N);
12761                Error_Msg_N ("|use pragma Profile (Restricted) instead", N);
12762             end if;
12763
12764          ------------------
12765          -- Restrictions --
12766          ------------------
12767
12768          --  pragma Restrictions (RESTRICTION {, RESTRICTION});
12769
12770          --  RESTRICTION ::=
12771          --    restriction_IDENTIFIER
12772          --  | restriction_parameter_IDENTIFIER => EXPRESSION
12773
12774          when Pragma_Restrictions =>
12775             Process_Restrictions_Or_Restriction_Warnings
12776               (Warn => Treat_Restrictions_As_Warnings);
12777
12778          --------------------------
12779          -- Restriction_Warnings --
12780          --------------------------
12781
12782          --  pragma Restriction_Warnings (RESTRICTION {, RESTRICTION});
12783
12784          --  RESTRICTION ::=
12785          --    restriction_IDENTIFIER
12786          --  | restriction_parameter_IDENTIFIER => EXPRESSION
12787
12788          when Pragma_Restriction_Warnings =>
12789             GNAT_Pragma;
12790             Process_Restrictions_Or_Restriction_Warnings (Warn => True);
12791
12792          ----------------
12793          -- Reviewable --
12794          ----------------
12795
12796          --  pragma Reviewable;
12797
12798          when Pragma_Reviewable =>
12799             Check_Ada_83_Warning;
12800             Check_Arg_Count (0);
12801
12802             --  Call dummy debugging function rv. This is done to assist front
12803             --  end debugging. By placing a Reviewable pragma in the source
12804             --  program, a breakpoint on rv catches this place in the source,
12805             --  allowing convenient stepping to the point of interest.
12806
12807             rv;
12808
12809          --------------------------
12810          -- Short_Circuit_And_Or --
12811          --------------------------
12812
12813          when Pragma_Short_Circuit_And_Or =>
12814             GNAT_Pragma;
12815             Check_Arg_Count (0);
12816             Check_Valid_Configuration_Pragma;
12817             Short_Circuit_And_Or := True;
12818
12819          -------------------
12820          -- Share_Generic --
12821          -------------------
12822
12823          --  pragma Share_Generic (NAME {, NAME});
12824
12825          when Pragma_Share_Generic =>
12826             GNAT_Pragma;
12827             Process_Generic_List;
12828
12829          ------------
12830          -- Shared --
12831          ------------
12832
12833          --  pragma Shared (LOCAL_NAME);
12834
12835          when Pragma_Shared =>
12836             GNAT_Pragma;
12837             Process_Atomic_Shared_Volatile;
12838
12839          --------------------
12840          -- Shared_Passive --
12841          --------------------
12842
12843          --  pragma Shared_Passive [(library_unit_NAME)];
12844
12845          --  Set the flag Is_Shared_Passive of program unit name entity
12846
12847          when Pragma_Shared_Passive => Shared_Passive : declare
12848             Cunit_Node : Node_Id;
12849             Cunit_Ent  : Entity_Id;
12850
12851          begin
12852             Check_Ada_83_Warning;
12853             Check_Valid_Library_Unit_Pragma;
12854
12855             if Nkind (N) = N_Null_Statement then
12856                return;
12857             end if;
12858
12859             Cunit_Node := Cunit (Current_Sem_Unit);
12860             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12861
12862             if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
12863                                                 N_Generic_Package_Declaration)
12864             then
12865                Error_Pragma
12866                  ("pragma% can only apply to a package declaration");
12867             end if;
12868
12869             Set_Is_Shared_Passive (Cunit_Ent);
12870          end Shared_Passive;
12871
12872          -----------------------
12873          -- Short_Descriptors --
12874          -----------------------
12875
12876          --  pragma Short_Descriptors;
12877
12878          when Pragma_Short_Descriptors =>
12879             GNAT_Pragma;
12880             Check_Arg_Count (0);
12881             Check_Valid_Configuration_Pragma;
12882             Short_Descriptors := True;
12883
12884          ----------------------
12885          -- Source_File_Name --
12886          ----------------------
12887
12888          --  There are five forms for this pragma:
12889
12890          --  pragma Source_File_Name (
12891          --    [UNIT_NAME      =>] unit_NAME,
12892          --     BODY_FILE_NAME =>  STRING_LITERAL
12893          --    [, [INDEX =>] INTEGER_LITERAL]);
12894
12895          --  pragma Source_File_Name (
12896          --    [UNIT_NAME      =>] unit_NAME,
12897          --     SPEC_FILE_NAME =>  STRING_LITERAL
12898          --    [, [INDEX =>] INTEGER_LITERAL]);
12899
12900          --  pragma Source_File_Name (
12901          --     BODY_FILE_NAME  => STRING_LITERAL
12902          --  [, DOT_REPLACEMENT => STRING_LITERAL]
12903          --  [, CASING          => CASING_SPEC]);
12904
12905          --  pragma Source_File_Name (
12906          --     SPEC_FILE_NAME  => STRING_LITERAL
12907          --  [, DOT_REPLACEMENT => STRING_LITERAL]
12908          --  [, CASING          => CASING_SPEC]);
12909
12910          --  pragma Source_File_Name (
12911          --     SUBUNIT_FILE_NAME  => STRING_LITERAL
12912          --  [, DOT_REPLACEMENT    => STRING_LITERAL]
12913          --  [, CASING             => CASING_SPEC]);
12914
12915          --  CASING_SPEC ::= Uppercase | Lowercase | Mixedcase
12916
12917          --  Pragma Source_File_Name_Project (SFNP) is equivalent to pragma
12918          --  Source_File_Name (SFN), however their usage is exclusive: SFN can
12919          --  only be used when no project file is used, while SFNP can only be
12920          --  used when a project file is used.
12921
12922          --  No processing here. Processing was completed during parsing, since
12923          --  we need to have file names set as early as possible. Units are
12924          --  loaded well before semantic processing starts.
12925
12926          --  The only processing we defer to this point is the check for
12927          --  correct placement.
12928
12929          when Pragma_Source_File_Name =>
12930             GNAT_Pragma;
12931             Check_Valid_Configuration_Pragma;
12932
12933          ------------------------------
12934          -- Source_File_Name_Project --
12935          ------------------------------
12936
12937          --  See Source_File_Name for syntax
12938
12939          --  No processing here. Processing was completed during parsing, since
12940          --  we need to have file names set as early as possible. Units are
12941          --  loaded well before semantic processing starts.
12942
12943          --  The only processing we defer to this point is the check for
12944          --  correct placement.
12945
12946          when Pragma_Source_File_Name_Project =>
12947             GNAT_Pragma;
12948             Check_Valid_Configuration_Pragma;
12949
12950             --  Check that a pragma Source_File_Name_Project is used only in a
12951             --  configuration pragmas file.
12952
12953             --  Pragmas Source_File_Name_Project should only be generated by
12954             --  the Project Manager in configuration pragmas files.
12955
12956             --  This is really an ugly test. It seems to depend on some
12957             --  accidental and undocumented property. At the very least it
12958             --  needs to be documented, but it would be better to have a
12959             --  clean way of testing if we are in a configuration file???
12960
12961             if Present (Parent (N)) then
12962                Error_Pragma
12963                  ("pragma% can only appear in a configuration pragmas file");
12964             end if;
12965
12966          ----------------------
12967          -- Source_Reference --
12968          ----------------------
12969
12970          --  pragma Source_Reference (INTEGER_LITERAL [, STRING_LITERAL]);
12971
12972          --  Nothing to do, all processing completed in Par.Prag, since we need
12973          --  the information for possible parser messages that are output.
12974
12975          when Pragma_Source_Reference =>
12976             GNAT_Pragma;
12977
12978          --------------------------------
12979          -- Static_Elaboration_Desired --
12980          --------------------------------
12981
12982          --  pragma Static_Elaboration_Desired (DIRECT_NAME);
12983
12984          when Pragma_Static_Elaboration_Desired =>
12985             GNAT_Pragma;
12986             Check_At_Most_N_Arguments (1);
12987
12988             if Is_Compilation_Unit (Current_Scope)
12989               and then Ekind (Current_Scope) = E_Package
12990             then
12991                Set_Static_Elaboration_Desired (Current_Scope, True);
12992             else
12993                Error_Pragma ("pragma% must apply to a library-level package");
12994             end if;
12995
12996          ------------------
12997          -- Storage_Size --
12998          ------------------
12999
13000          --  pragma Storage_Size (EXPRESSION);
13001
13002          when Pragma_Storage_Size => Storage_Size : declare
13003             P   : constant Node_Id := Parent (N);
13004             Arg : Node_Id;
13005
13006          begin
13007             Check_No_Identifiers;
13008             Check_Arg_Count (1);
13009
13010             --  The expression must be analyzed in the special manner described
13011             --  in "Handling of Default Expressions" in sem.ads.
13012
13013             Arg := Get_Pragma_Arg (Arg1);
13014             Preanalyze_Spec_Expression (Arg, Any_Integer);
13015
13016             if not Is_Static_Expression (Arg) then
13017                Check_Restriction (Static_Storage_Size, Arg);
13018             end if;
13019
13020             if Nkind (P) /= N_Task_Definition then
13021                Pragma_Misplaced;
13022                return;
13023
13024             else
13025                if Has_Storage_Size_Pragma (P) then
13026                   Error_Pragma ("duplicate pragma% not allowed");
13027                else
13028                   Set_Has_Storage_Size_Pragma (P, True);
13029                end if;
13030
13031                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
13032                --  ???  exp_ch9 should use this!
13033             end if;
13034          end Storage_Size;
13035
13036          ------------------
13037          -- Storage_Unit --
13038          ------------------
13039
13040          --  pragma Storage_Unit (NUMERIC_LITERAL);
13041
13042          --  Only permitted argument is System'Storage_Unit value
13043
13044          when Pragma_Storage_Unit =>
13045             Check_No_Identifiers;
13046             Check_Arg_Count (1);
13047             Check_Arg_Is_Integer_Literal (Arg1);
13048
13049             if Intval (Get_Pragma_Arg (Arg1)) /=
13050               UI_From_Int (Ttypes.System_Storage_Unit)
13051             then
13052                Error_Msg_Uint_1 := UI_From_Int (Ttypes.System_Storage_Unit);
13053                Error_Pragma_Arg
13054                  ("the only allowed argument for pragma% is ^", Arg1);
13055             end if;
13056
13057          --------------------
13058          -- Stream_Convert --
13059          --------------------
13060
13061          --  pragma Stream_Convert (
13062          --    [Entity =>] type_LOCAL_NAME,
13063          --    [Read   =>] function_NAME,
13064          --    [Write  =>] function NAME);
13065
13066          when Pragma_Stream_Convert => Stream_Convert : declare
13067
13068             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id);
13069             --  Check that the given argument is the name of a local function
13070             --  of one argument that is not overloaded earlier in the current
13071             --  local scope. A check is also made that the argument is a
13072             --  function with one parameter.
13073
13074             --------------------------------------
13075             -- Check_OK_Stream_Convert_Function --
13076             --------------------------------------
13077
13078             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id) is
13079                Ent : Entity_Id;
13080
13081             begin
13082                Check_Arg_Is_Local_Name (Arg);
13083                Ent := Entity (Get_Pragma_Arg (Arg));
13084
13085                if Has_Homonym (Ent) then
13086                   Error_Pragma_Arg
13087                     ("argument for pragma% may not be overloaded", Arg);
13088                end if;
13089
13090                if Ekind (Ent) /= E_Function
13091                  or else No (First_Formal (Ent))
13092                  or else Present (Next_Formal (First_Formal (Ent)))
13093                then
13094                   Error_Pragma_Arg
13095                     ("argument for pragma% must be" &
13096                      " function of one argument", Arg);
13097                end if;
13098             end Check_OK_Stream_Convert_Function;
13099
13100          --  Start of processing for Stream_Convert
13101
13102          begin
13103             GNAT_Pragma;
13104             Check_Arg_Order ((Name_Entity, Name_Read, Name_Write));
13105             Check_Arg_Count (3);
13106             Check_Optional_Identifier (Arg1, Name_Entity);
13107             Check_Optional_Identifier (Arg2, Name_Read);
13108             Check_Optional_Identifier (Arg3, Name_Write);
13109             Check_Arg_Is_Local_Name (Arg1);
13110             Check_OK_Stream_Convert_Function (Arg2);
13111             Check_OK_Stream_Convert_Function (Arg3);
13112
13113             declare
13114                Typ   : constant Entity_Id :=
13115                          Underlying_Type (Entity (Get_Pragma_Arg (Arg1)));
13116                Read  : constant Entity_Id := Entity (Get_Pragma_Arg (Arg2));
13117                Write : constant Entity_Id := Entity (Get_Pragma_Arg (Arg3));
13118
13119             begin
13120                Check_First_Subtype (Arg1);
13121
13122                --  Check for too early or too late. Note that we don't enforce
13123                --  the rule about primitive operations in this case, since, as
13124                --  is the case for explicit stream attributes themselves, these
13125                --  restrictions are not appropriate. Note that the chaining of
13126                --  the pragma by Rep_Item_Too_Late is actually the critical
13127                --  processing done for this pragma.
13128
13129                if Rep_Item_Too_Early (Typ, N)
13130                     or else
13131                   Rep_Item_Too_Late (Typ, N, FOnly => True)
13132                then
13133                   return;
13134                end if;
13135
13136                --  Return if previous error
13137
13138                if Etype (Typ) = Any_Type
13139                     or else
13140                   Etype (Read) = Any_Type
13141                     or else
13142                   Etype (Write) = Any_Type
13143                then
13144                   return;
13145                end if;
13146
13147                --  Error checks
13148
13149                if Underlying_Type (Etype (Read)) /= Typ then
13150                   Error_Pragma_Arg
13151                     ("incorrect return type for function&", Arg2);
13152                end if;
13153
13154                if Underlying_Type (Etype (First_Formal (Write))) /= Typ then
13155                   Error_Pragma_Arg
13156                     ("incorrect parameter type for function&", Arg3);
13157                end if;
13158
13159                if Underlying_Type (Etype (First_Formal (Read))) /=
13160                   Underlying_Type (Etype (Write))
13161                then
13162                   Error_Pragma_Arg
13163                     ("result type of & does not match Read parameter type",
13164                      Arg3);
13165                end if;
13166             end;
13167          end Stream_Convert;
13168
13169          -------------------------
13170          -- Style_Checks (GNAT) --
13171          -------------------------
13172
13173          --  pragma Style_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
13174
13175          --  This is processed by the parser since some of the style checks
13176          --  take place during source scanning and parsing. This means that
13177          --  we don't need to issue error messages here.
13178
13179          when Pragma_Style_Checks => Style_Checks : declare
13180             A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
13181             S  : String_Id;
13182             C  : Char_Code;
13183
13184          begin
13185             GNAT_Pragma;
13186             Check_No_Identifiers;
13187
13188             --  Two argument form
13189
13190             if Arg_Count = 2 then
13191                Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
13192
13193                declare
13194                   E_Id : Node_Id;
13195                   E    : Entity_Id;
13196
13197                begin
13198                   E_Id := Get_Pragma_Arg (Arg2);
13199                   Analyze (E_Id);
13200
13201                   if not Is_Entity_Name (E_Id) then
13202                      Error_Pragma_Arg
13203                        ("second argument of pragma% must be entity name",
13204                         Arg2);
13205                   end if;
13206
13207                   E := Entity (E_Id);
13208
13209                   if E = Any_Id then
13210                      return;
13211                   else
13212                      loop
13213                         Set_Suppress_Style_Checks (E,
13214                           (Chars (Get_Pragma_Arg (Arg1)) = Name_Off));
13215                         exit when No (Homonym (E));
13216                         E := Homonym (E);
13217                      end loop;
13218                   end if;
13219                end;
13220
13221             --  One argument form
13222
13223             else
13224                Check_Arg_Count (1);
13225
13226                if Nkind (A) = N_String_Literal then
13227                   S   := Strval (A);
13228
13229                   declare
13230                      Slen    : constant Natural := Natural (String_Length (S));
13231                      Options : String (1 .. Slen);
13232                      J       : Natural;
13233
13234                   begin
13235                      J := 1;
13236                      loop
13237                         C := Get_String_Char (S, Int (J));
13238                         exit when not In_Character_Range (C);
13239                         Options (J) := Get_Character (C);
13240
13241                         --  If at end of string, set options. As per discussion
13242                         --  above, no need to check for errors, since we issued
13243                         --  them in the parser.
13244
13245                         if J = Slen then
13246                            Set_Style_Check_Options (Options);
13247                            exit;
13248                         end if;
13249
13250                         J := J + 1;
13251                      end loop;
13252                   end;
13253
13254                elsif Nkind (A) = N_Identifier then
13255                   if Chars (A) = Name_All_Checks then
13256                      if GNAT_Mode then
13257                         Set_GNAT_Style_Check_Options;
13258                      else
13259                         Set_Default_Style_Check_Options;
13260                      end if;
13261
13262                   elsif Chars (A) = Name_On then
13263                      Style_Check := True;
13264
13265                   elsif Chars (A) = Name_Off then
13266                      Style_Check := False;
13267                   end if;
13268                end if;
13269             end if;
13270          end Style_Checks;
13271
13272          --------------
13273          -- Subtitle --
13274          --------------
13275
13276          --  pragma Subtitle ([Subtitle =>] STRING_LITERAL);
13277
13278          when Pragma_Subtitle =>
13279             GNAT_Pragma;
13280             Check_Arg_Count (1);
13281             Check_Optional_Identifier (Arg1, Name_Subtitle);
13282             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
13283             Store_Note (N);
13284
13285          --------------
13286          -- Suppress --
13287          --------------
13288
13289          --  pragma Suppress (IDENTIFIER [, [On =>] NAME]);
13290
13291          when Pragma_Suppress =>
13292             Process_Suppress_Unsuppress (True);
13293
13294          ------------------
13295          -- Suppress_All --
13296          ------------------
13297
13298          --  pragma Suppress_All;
13299
13300          --  The only check made here is that the pragma has no arguments.
13301          --  There are no placement rules, and the processing required (setting
13302          --  the Has_Pragma_Suppress_All flag in the compilation unit node was
13303          --  taken care of by the parser). Process_Compilation_Unit_Pragmas
13304          --  then creates and inserts a pragma Suppress (All_Checks).
13305
13306          when Pragma_Suppress_All =>
13307             GNAT_Pragma;
13308             Check_Arg_Count (0);
13309
13310          -------------------------
13311          -- Suppress_Debug_Info --
13312          -------------------------
13313
13314          --  pragma Suppress_Debug_Info ([Entity =>] LOCAL_NAME);
13315
13316          when Pragma_Suppress_Debug_Info =>
13317             GNAT_Pragma;
13318             Check_Arg_Count (1);
13319             Check_Optional_Identifier (Arg1, Name_Entity);
13320             Check_Arg_Is_Local_Name (Arg1);
13321             Set_Debug_Info_Off (Entity (Get_Pragma_Arg (Arg1)));
13322
13323          ----------------------------------
13324          -- Suppress_Exception_Locations --
13325          ----------------------------------
13326
13327          --  pragma Suppress_Exception_Locations;
13328
13329          when Pragma_Suppress_Exception_Locations =>
13330             GNAT_Pragma;
13331             Check_Arg_Count (0);
13332             Check_Valid_Configuration_Pragma;
13333             Exception_Locations_Suppressed := True;
13334
13335          -----------------------------
13336          -- Suppress_Initialization --
13337          -----------------------------
13338
13339          --  pragma Suppress_Initialization ([Entity =>] type_Name);
13340
13341          when Pragma_Suppress_Initialization => Suppress_Init : declare
13342             E_Id : Node_Id;
13343             E    : Entity_Id;
13344
13345          begin
13346             GNAT_Pragma;
13347             Check_Arg_Count (1);
13348             Check_Optional_Identifier (Arg1, Name_Entity);
13349             Check_Arg_Is_Local_Name (Arg1);
13350
13351             E_Id := Get_Pragma_Arg (Arg1);
13352
13353             if Etype (E_Id) = Any_Type then
13354                return;
13355             end if;
13356
13357             E := Entity (E_Id);
13358
13359             if not Is_Type (E) then
13360                Error_Pragma_Arg ("pragma% requires type or subtype", Arg1);
13361             end if;
13362
13363             if Rep_Item_Too_Early (E, N)
13364                  or else
13365                Rep_Item_Too_Late (E, N, FOnly => True)
13366             then
13367                return;
13368             end if;
13369
13370             --  For incomplete/private type, set flag on full view
13371
13372             if Is_Incomplete_Or_Private_Type (E) then
13373                if No (Full_View (Base_Type (E))) then
13374                   Error_Pragma_Arg
13375                     ("argument of pragma% cannot be an incomplete type", Arg1);
13376                else
13377                   Set_Suppress_Initialization (Full_View (Base_Type (E)));
13378                end if;
13379
13380             --  For first subtype, set flag on base type
13381
13382             elsif Is_First_Subtype (E) then
13383                Set_Suppress_Initialization (Base_Type (E));
13384
13385             --  For other than first subtype, set flag on subtype itself
13386
13387             else
13388                Set_Suppress_Initialization (E);
13389             end if;
13390          end Suppress_Init;
13391
13392          -----------------
13393          -- System_Name --
13394          -----------------
13395
13396          --  pragma System_Name (DIRECT_NAME);
13397
13398          --  Syntax check: one argument, which must be the identifier GNAT or
13399          --  the identifier GCC, no other identifiers are acceptable.
13400
13401          when Pragma_System_Name =>
13402             GNAT_Pragma;
13403             Check_No_Identifiers;
13404             Check_Arg_Count (1);
13405             Check_Arg_Is_One_Of (Arg1, Name_Gcc, Name_Gnat);
13406
13407          -----------------------------
13408          -- Task_Dispatching_Policy --
13409          -----------------------------
13410
13411          --  pragma Task_Dispatching_Policy (policy_IDENTIFIER);
13412
13413          when Pragma_Task_Dispatching_Policy => declare
13414             DP : Character;
13415
13416          begin
13417             Check_Ada_83_Warning;
13418             Check_Arg_Count (1);
13419             Check_No_Identifiers;
13420             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
13421             Check_Valid_Configuration_Pragma;
13422             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
13423             DP := Fold_Upper (Name_Buffer (1));
13424
13425             if Task_Dispatching_Policy /= ' '
13426               and then Task_Dispatching_Policy /= DP
13427             then
13428                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
13429                Error_Pragma
13430                  ("task dispatching policy incompatible with policy#");
13431
13432             --  Set new policy, but always preserve System_Location since we
13433             --  like the error message with the run time name.
13434
13435             else
13436                Task_Dispatching_Policy := DP;
13437
13438                if Task_Dispatching_Policy_Sloc /= System_Location then
13439                   Task_Dispatching_Policy_Sloc := Loc;
13440                end if;
13441             end if;
13442          end;
13443
13444          ---------------
13445          -- Task_Info --
13446          ---------------
13447
13448          --  pragma Task_Info (EXPRESSION);
13449
13450          when Pragma_Task_Info => Task_Info : declare
13451             P : constant Node_Id := Parent (N);
13452
13453          begin
13454             GNAT_Pragma;
13455
13456             if Nkind (P) /= N_Task_Definition then
13457                Error_Pragma ("pragma% must appear in task definition");
13458             end if;
13459
13460             Check_No_Identifiers;
13461             Check_Arg_Count (1);
13462
13463             Analyze_And_Resolve
13464               (Get_Pragma_Arg (Arg1), RTE (RE_Task_Info_Type));
13465
13466             if Etype (Get_Pragma_Arg (Arg1)) = Any_Type then
13467                return;
13468             end if;
13469
13470             if Has_Task_Info_Pragma (P) then
13471                Error_Pragma ("duplicate pragma% not allowed");
13472             else
13473                Set_Has_Task_Info_Pragma (P, True);
13474             end if;
13475          end Task_Info;
13476
13477          ---------------
13478          -- Task_Name --
13479          ---------------
13480
13481          --  pragma Task_Name (string_EXPRESSION);
13482
13483          when Pragma_Task_Name => Task_Name : declare
13484             P   : constant Node_Id := Parent (N);
13485             Arg : Node_Id;
13486
13487          begin
13488             Check_No_Identifiers;
13489             Check_Arg_Count (1);
13490
13491             Arg := Get_Pragma_Arg (Arg1);
13492
13493             --  The expression is used in the call to Create_Task, and must be
13494             --  expanded there, not in the context of the current spec. It must
13495             --  however be analyzed to capture global references, in case it
13496             --  appears in a generic context.
13497
13498             Preanalyze_And_Resolve (Arg, Standard_String);
13499
13500             if Nkind (P) /= N_Task_Definition then
13501                Pragma_Misplaced;
13502             end if;
13503
13504             if Has_Task_Name_Pragma (P) then
13505                Error_Pragma ("duplicate pragma% not allowed");
13506             else
13507                Set_Has_Task_Name_Pragma (P, True);
13508                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
13509             end if;
13510          end Task_Name;
13511
13512          ------------------
13513          -- Task_Storage --
13514          ------------------
13515
13516          --  pragma Task_Storage (
13517          --     [Task_Type =>] LOCAL_NAME,
13518          --     [Top_Guard =>] static_integer_EXPRESSION);
13519
13520          when Pragma_Task_Storage => Task_Storage : declare
13521             Args  : Args_List (1 .. 2);
13522             Names : constant Name_List (1 .. 2) := (
13523                       Name_Task_Type,
13524                       Name_Top_Guard);
13525
13526             Task_Type : Node_Id renames Args (1);
13527             Top_Guard : Node_Id renames Args (2);
13528
13529             Ent : Entity_Id;
13530
13531          begin
13532             GNAT_Pragma;
13533             Gather_Associations (Names, Args);
13534
13535             if No (Task_Type) then
13536                Error_Pragma
13537                  ("missing task_type argument for pragma%");
13538             end if;
13539
13540             Check_Arg_Is_Local_Name (Task_Type);
13541
13542             Ent := Entity (Task_Type);
13543
13544             if not Is_Task_Type (Ent) then
13545                Error_Pragma_Arg
13546                  ("argument for pragma% must be task type", Task_Type);
13547             end if;
13548
13549             if No (Top_Guard) then
13550                Error_Pragma_Arg
13551                  ("pragma% takes two arguments", Task_Type);
13552             else
13553                Check_Arg_Is_Static_Expression (Top_Guard, Any_Integer);
13554             end if;
13555
13556             Check_First_Subtype (Task_Type);
13557
13558             if Rep_Item_Too_Late (Ent, N) then
13559                raise Pragma_Exit;
13560             end if;
13561          end Task_Storage;
13562
13563          ---------------
13564          -- Test_Case --
13565          ---------------
13566
13567          --  pragma Test_Case ([Name     =>] Static_String_EXPRESSION
13568          --                   ,[Mode     =>] MODE_TYPE
13569          --                  [, Requires =>  Boolean_EXPRESSION]
13570          --                  [, Ensures  =>  Boolean_EXPRESSION]);
13571
13572          --  MODE_TYPE ::= Nominal | Robustness
13573
13574          when Pragma_Test_Case => Test_Case : declare
13575          begin
13576             GNAT_Pragma;
13577             Check_At_Least_N_Arguments (2);
13578             Check_At_Most_N_Arguments (4);
13579             Check_Arg_Order
13580                  ((Name_Name, Name_Mode, Name_Requires, Name_Ensures));
13581
13582             Check_Optional_Identifier (Arg1, Name_Name);
13583             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
13584             Check_Optional_Identifier (Arg2, Name_Mode);
13585             Check_Arg_Is_One_Of (Arg2, Name_Nominal, Name_Robustness);
13586
13587             if Arg_Count = 4 then
13588                Check_Identifier (Arg3, Name_Requires);
13589                Check_Identifier (Arg4, Name_Ensures);
13590
13591             elsif Arg_Count = 3 then
13592                Check_Identifier_Is_One_Of (Arg3, Name_Requires, Name_Ensures);
13593             end if;
13594
13595             Check_Test_Case;
13596          end Test_Case;
13597
13598          --------------------------
13599          -- Thread_Local_Storage --
13600          --------------------------
13601
13602          --  pragma Thread_Local_Storage ([Entity =>] LOCAL_NAME);
13603
13604          when Pragma_Thread_Local_Storage => Thread_Local_Storage : declare
13605             Id : Node_Id;
13606             E  : Entity_Id;
13607
13608          begin
13609             GNAT_Pragma;
13610             Check_Arg_Count (1);
13611             Check_Optional_Identifier (Arg1, Name_Entity);
13612             Check_Arg_Is_Library_Level_Local_Name (Arg1);
13613
13614             Id := Get_Pragma_Arg (Arg1);
13615             Analyze (Id);
13616
13617             if not Is_Entity_Name (Id)
13618               or else Ekind (Entity (Id)) /= E_Variable
13619             then
13620                Error_Pragma_Arg ("local variable name required", Arg1);
13621             end if;
13622
13623             E := Entity (Id);
13624
13625             if Rep_Item_Too_Early (E, N)
13626               or else Rep_Item_Too_Late (E, N)
13627             then
13628                raise Pragma_Exit;
13629             end if;
13630
13631             Set_Has_Pragma_Thread_Local_Storage (E);
13632             Set_Has_Gigi_Rep_Item (E);
13633          end Thread_Local_Storage;
13634
13635          ----------------
13636          -- Time_Slice --
13637          ----------------
13638
13639          --  pragma Time_Slice (static_duration_EXPRESSION);
13640
13641          when Pragma_Time_Slice => Time_Slice : declare
13642             Val : Ureal;
13643             Nod : Node_Id;
13644
13645          begin
13646             GNAT_Pragma;
13647             Check_Arg_Count (1);
13648             Check_No_Identifiers;
13649             Check_In_Main_Program;
13650             Check_Arg_Is_Static_Expression (Arg1, Standard_Duration);
13651
13652             if not Error_Posted (Arg1) then
13653                Nod := Next (N);
13654                while Present (Nod) loop
13655                   if Nkind (Nod) = N_Pragma
13656                     and then Pragma_Name (Nod) = Name_Time_Slice
13657                   then
13658                      Error_Msg_Name_1 := Pname;
13659                      Error_Msg_N ("duplicate pragma% not permitted", Nod);
13660                   end if;
13661
13662                   Next (Nod);
13663                end loop;
13664             end if;
13665
13666             --  Process only if in main unit
13667
13668             if Get_Source_Unit (Loc) = Main_Unit then
13669                Opt.Time_Slice_Set := True;
13670                Val := Expr_Value_R (Get_Pragma_Arg (Arg1));
13671
13672                if Val <= Ureal_0 then
13673                   Opt.Time_Slice_Value := 0;
13674
13675                elsif Val > UR_From_Uint (UI_From_Int (1000)) then
13676                   Opt.Time_Slice_Value := 1_000_000_000;
13677
13678                else
13679                   Opt.Time_Slice_Value :=
13680                     UI_To_Int (UR_To_Uint (Val * UI_From_Int (1_000_000)));
13681                end if;
13682             end if;
13683          end Time_Slice;
13684
13685          -----------
13686          -- Title --
13687          -----------
13688
13689          --  pragma Title (TITLING_OPTION [, TITLING OPTION]);
13690
13691          --   TITLING_OPTION ::=
13692          --     [Title =>] STRING_LITERAL
13693          --   | [Subtitle =>] STRING_LITERAL
13694
13695          when Pragma_Title => Title : declare
13696             Args  : Args_List (1 .. 2);
13697             Names : constant Name_List (1 .. 2) := (
13698                       Name_Title,
13699                       Name_Subtitle);
13700
13701          begin
13702             GNAT_Pragma;
13703             Gather_Associations (Names, Args);
13704             Store_Note (N);
13705
13706             for J in 1 .. 2 loop
13707                if Present (Args (J)) then
13708                   Check_Arg_Is_Static_Expression (Args (J), Standard_String);
13709                end if;
13710             end loop;
13711          end Title;
13712
13713          ---------------------
13714          -- Unchecked_Union --
13715          ---------------------
13716
13717          --  pragma Unchecked_Union (first_subtype_LOCAL_NAME)
13718
13719          when Pragma_Unchecked_Union => Unchecked_Union : declare
13720             Assoc   : constant Node_Id := Arg1;
13721             Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
13722             Typ     : Entity_Id;
13723             Discr   : Entity_Id;
13724             Tdef    : Node_Id;
13725             Clist   : Node_Id;
13726             Vpart   : Node_Id;
13727             Comp    : Node_Id;
13728             Variant : Node_Id;
13729
13730          begin
13731             Ada_2005_Pragma;
13732             Check_No_Identifiers;
13733             Check_Arg_Count (1);
13734             Check_Arg_Is_Local_Name (Arg1);
13735
13736             Find_Type (Type_Id);
13737             Typ := Entity (Type_Id);
13738
13739             if Typ = Any_Type
13740               or else Rep_Item_Too_Early (Typ, N)
13741             then
13742                return;
13743             else
13744                Typ := Underlying_Type (Typ);
13745             end if;
13746
13747             if Rep_Item_Too_Late (Typ, N) then
13748                return;
13749             end if;
13750
13751             Check_First_Subtype (Arg1);
13752
13753             --  Note remaining cases are references to a type in the current
13754             --  declarative part. If we find an error, we post the error on
13755             --  the relevant type declaration at an appropriate point.
13756
13757             if not Is_Record_Type (Typ) then
13758                Error_Msg_N ("Unchecked_Union must be record type", Typ);
13759                return;
13760
13761             elsif Is_Tagged_Type (Typ) then
13762                Error_Msg_N ("Unchecked_Union must not be tagged", Typ);
13763                return;
13764
13765             elsif Is_Limited_Type (Typ) then
13766                Error_Msg_N
13767                  ("Unchecked_Union must not be limited record type", Typ);
13768                Explain_Limited_Type (Typ, Typ);
13769                return;
13770
13771             else
13772                if not Has_Discriminants (Typ) then
13773                   Error_Msg_N
13774                     ("Unchecked_Union must have one discriminant", Typ);
13775                   return;
13776                end if;
13777
13778                Discr := First_Discriminant (Typ);
13779                while Present (Discr) loop
13780                   if No (Discriminant_Default_Value (Discr)) then
13781                      Error_Msg_N
13782                        ("Unchecked_Union discriminant must have default value",
13783                         Discr);
13784                   end if;
13785
13786                   Next_Discriminant (Discr);
13787                end loop;
13788
13789                Tdef  := Type_Definition (Declaration_Node (Typ));
13790                Clist := Component_List (Tdef);
13791
13792                Comp := First (Component_Items (Clist));
13793                while Present (Comp) loop
13794                   Check_Component (Comp, Typ);
13795                   Next (Comp);
13796                end loop;
13797
13798                if No (Clist) or else No (Variant_Part (Clist)) then
13799                   Error_Msg_N
13800                     ("Unchecked_Union must have variant part",
13801                      Tdef);
13802                   return;
13803                end if;
13804
13805                Vpart := Variant_Part (Clist);
13806
13807                Variant := First (Variants (Vpart));
13808                while Present (Variant) loop
13809                   Check_Variant (Variant, Typ);
13810                   Next (Variant);
13811                end loop;
13812             end if;
13813
13814             Set_Is_Unchecked_Union  (Typ);
13815             Set_Convention (Typ, Convention_C);
13816             Set_Has_Unchecked_Union (Base_Type (Typ));
13817             Set_Is_Unchecked_Union  (Base_Type (Typ));
13818          end Unchecked_Union;
13819
13820          ------------------------
13821          -- Unimplemented_Unit --
13822          ------------------------
13823
13824          --  pragma Unimplemented_Unit;
13825
13826          --  Note: this only gives an error if we are generating code, or if
13827          --  we are in a generic library unit (where the pragma appears in the
13828          --  body, not in the spec).
13829
13830          when Pragma_Unimplemented_Unit => Unimplemented_Unit : declare
13831             Cunitent : constant Entity_Id :=
13832                          Cunit_Entity (Get_Source_Unit (Loc));
13833             Ent_Kind : constant Entity_Kind :=
13834                          Ekind (Cunitent);
13835
13836          begin
13837             GNAT_Pragma;
13838             Check_Arg_Count (0);
13839
13840             if Operating_Mode = Generate_Code
13841               or else Ent_Kind = E_Generic_Function
13842               or else Ent_Kind = E_Generic_Procedure
13843               or else Ent_Kind = E_Generic_Package
13844             then
13845                Get_Name_String (Chars (Cunitent));
13846                Set_Casing (Mixed_Case);
13847                Write_Str (Name_Buffer (1 .. Name_Len));
13848                Write_Str (" is not supported in this configuration");
13849                Write_Eol;
13850                raise Unrecoverable_Error;
13851             end if;
13852          end Unimplemented_Unit;
13853
13854          ------------------------
13855          -- Universal_Aliasing --
13856          ------------------------
13857
13858          --  pragma Universal_Aliasing [([Entity =>] type_LOCAL_NAME)];
13859
13860          when Pragma_Universal_Aliasing => Universal_Alias : declare
13861             E_Id : Entity_Id;
13862
13863          begin
13864             GNAT_Pragma;
13865             Check_Arg_Count (1);
13866             Check_Optional_Identifier (Arg2, Name_Entity);
13867             Check_Arg_Is_Local_Name (Arg1);
13868             E_Id := Entity (Get_Pragma_Arg (Arg1));
13869
13870             if E_Id = Any_Type then
13871                return;
13872             elsif No (E_Id) or else not Is_Type (E_Id) then
13873                Error_Pragma_Arg ("pragma% requires type", Arg1);
13874             end if;
13875
13876             Set_Universal_Aliasing (Implementation_Base_Type (E_Id));
13877          end Universal_Alias;
13878
13879          --------------------
13880          -- Universal_Data --
13881          --------------------
13882
13883          --  pragma Universal_Data [(library_unit_NAME)];
13884
13885          when Pragma_Universal_Data =>
13886             GNAT_Pragma;
13887
13888             --  If this is a configuration pragma, then set the universal
13889             --  addressing option, otherwise confirm that the pragma satisfies
13890             --  the requirements of library unit pragma placement and leave it
13891             --  to the GNAAMP back end to detect the pragma (avoids transitive
13892             --  setting of the option due to withed units).
13893
13894             if Is_Configuration_Pragma then
13895                Universal_Addressing_On_AAMP := True;
13896             else
13897                Check_Valid_Library_Unit_Pragma;
13898             end if;
13899
13900             if not AAMP_On_Target then
13901                Error_Pragma ("?pragma% ignored (applies only to AAMP)");
13902             end if;
13903
13904          ----------------
13905          -- Unmodified --
13906          ----------------
13907
13908          --  pragma Unmodified (local_Name {, local_Name});
13909
13910          when Pragma_Unmodified => Unmodified : declare
13911             Arg_Node : Node_Id;
13912             Arg_Expr : Node_Id;
13913             Arg_Ent  : Entity_Id;
13914
13915          begin
13916             GNAT_Pragma;
13917             Check_At_Least_N_Arguments (1);
13918
13919             --  Loop through arguments
13920
13921             Arg_Node := Arg1;
13922             while Present (Arg_Node) loop
13923                Check_No_Identifier (Arg_Node);
13924
13925                --  Note: the analyze call done by Check_Arg_Is_Local_Name will
13926                --  in fact generate reference, so that the entity will have a
13927                --  reference, which will inhibit any warnings about it not
13928                --  being referenced, and also properly show up in the ali file
13929                --  as a reference. But this reference is recorded before the
13930                --  Has_Pragma_Unreferenced flag is set, so that no warning is
13931                --  generated for this reference.
13932
13933                Check_Arg_Is_Local_Name (Arg_Node);
13934                Arg_Expr := Get_Pragma_Arg (Arg_Node);
13935
13936                if Is_Entity_Name (Arg_Expr) then
13937                   Arg_Ent := Entity (Arg_Expr);
13938
13939                   if not Is_Assignable (Arg_Ent) then
13940                      Error_Pragma_Arg
13941                        ("pragma% can only be applied to a variable",
13942                         Arg_Expr);
13943                   else
13944                      Set_Has_Pragma_Unmodified (Arg_Ent);
13945                   end if;
13946                end if;
13947
13948                Next (Arg_Node);
13949             end loop;
13950          end Unmodified;
13951
13952          ------------------
13953          -- Unreferenced --
13954          ------------------
13955
13956          --  pragma Unreferenced (local_Name {, local_Name});
13957
13958          --    or when used in a context clause:
13959
13960          --  pragma Unreferenced (library_unit_NAME {, library_unit_NAME}
13961
13962          when Pragma_Unreferenced => Unreferenced : declare
13963             Arg_Node : Node_Id;
13964             Arg_Expr : Node_Id;
13965             Arg_Ent  : Entity_Id;
13966             Citem    : Node_Id;
13967
13968          begin
13969             GNAT_Pragma;
13970             Check_At_Least_N_Arguments (1);
13971
13972             --  Check case of appearing within context clause
13973
13974             if Is_In_Context_Clause then
13975
13976                --  The arguments must all be units mentioned in a with clause
13977                --  in the same context clause. Note we already checked (in
13978                --  Par.Prag) that the arguments are either identifiers or
13979                --  selected components.
13980
13981                Arg_Node := Arg1;
13982                while Present (Arg_Node) loop
13983                   Citem := First (List_Containing (N));
13984                   while Citem /= N loop
13985                      if Nkind (Citem) = N_With_Clause
13986                        and then
13987                          Same_Name (Name (Citem), Get_Pragma_Arg (Arg_Node))
13988                      then
13989                         Set_Has_Pragma_Unreferenced
13990                           (Cunit_Entity
13991                              (Get_Source_Unit
13992                                 (Library_Unit (Citem))));
13993                         Set_Unit_Name
13994                           (Get_Pragma_Arg (Arg_Node), Name (Citem));
13995                         exit;
13996                      end if;
13997
13998                      Next (Citem);
13999                   end loop;
14000
14001                   if Citem = N then
14002                      Error_Pragma_Arg
14003                        ("argument of pragma% is not with'ed unit", Arg_Node);
14004                   end if;
14005
14006                   Next (Arg_Node);
14007                end loop;
14008
14009             --  Case of not in list of context items
14010
14011             else
14012                Arg_Node := Arg1;
14013                while Present (Arg_Node) loop
14014                   Check_No_Identifier (Arg_Node);
14015
14016                   --  Note: the analyze call done by Check_Arg_Is_Local_Name
14017                   --  will in fact generate reference, so that the entity will
14018                   --  have a reference, which will inhibit any warnings about
14019                   --  it not being referenced, and also properly show up in the
14020                   --  ali file as a reference. But this reference is recorded
14021                   --  before the Has_Pragma_Unreferenced flag is set, so that
14022                   --  no warning is generated for this reference.
14023
14024                   Check_Arg_Is_Local_Name (Arg_Node);
14025                   Arg_Expr := Get_Pragma_Arg (Arg_Node);
14026
14027                   if Is_Entity_Name (Arg_Expr) then
14028                      Arg_Ent := Entity (Arg_Expr);
14029
14030                      --  If the entity is overloaded, the pragma applies to the
14031                      --  most recent overloading, as documented. In this case,
14032                      --  name resolution does not generate a reference, so it
14033                      --  must be done here explicitly.
14034
14035                      if Is_Overloaded (Arg_Expr) then
14036                         Generate_Reference (Arg_Ent, N);
14037                      end if;
14038
14039                      Set_Has_Pragma_Unreferenced (Arg_Ent);
14040                   end if;
14041
14042                   Next (Arg_Node);
14043                end loop;
14044             end if;
14045          end Unreferenced;
14046
14047          --------------------------
14048          -- Unreferenced_Objects --
14049          --------------------------
14050
14051          --  pragma Unreferenced_Objects (local_Name {, local_Name});
14052
14053          when Pragma_Unreferenced_Objects => Unreferenced_Objects : declare
14054             Arg_Node : Node_Id;
14055             Arg_Expr : Node_Id;
14056
14057          begin
14058             GNAT_Pragma;
14059             Check_At_Least_N_Arguments (1);
14060
14061             Arg_Node := Arg1;
14062             while Present (Arg_Node) loop
14063                Check_No_Identifier (Arg_Node);
14064                Check_Arg_Is_Local_Name (Arg_Node);
14065                Arg_Expr := Get_Pragma_Arg (Arg_Node);
14066
14067                if not Is_Entity_Name (Arg_Expr)
14068                  or else not Is_Type (Entity (Arg_Expr))
14069                then
14070                   Error_Pragma_Arg
14071                     ("argument for pragma% must be type or subtype", Arg_Node);
14072                end if;
14073
14074                Set_Has_Pragma_Unreferenced_Objects (Entity (Arg_Expr));
14075                Next (Arg_Node);
14076             end loop;
14077          end Unreferenced_Objects;
14078
14079          ------------------------------
14080          -- Unreserve_All_Interrupts --
14081          ------------------------------
14082
14083          --  pragma Unreserve_All_Interrupts;
14084
14085          when Pragma_Unreserve_All_Interrupts =>
14086             GNAT_Pragma;
14087             Check_Arg_Count (0);
14088
14089             if In_Extended_Main_Code_Unit (Main_Unit_Entity) then
14090                Unreserve_All_Interrupts := True;
14091             end if;
14092
14093          ----------------
14094          -- Unsuppress --
14095          ----------------
14096
14097          --  pragma Unsuppress (IDENTIFIER [, [On =>] NAME]);
14098
14099          when Pragma_Unsuppress =>
14100             Ada_2005_Pragma;
14101             Process_Suppress_Unsuppress (False);
14102
14103          -------------------
14104          -- Use_VADS_Size --
14105          -------------------
14106
14107          --  pragma Use_VADS_Size;
14108
14109          when Pragma_Use_VADS_Size =>
14110             GNAT_Pragma;
14111             Check_Arg_Count (0);
14112             Check_Valid_Configuration_Pragma;
14113             Use_VADS_Size := True;
14114
14115          ---------------------
14116          -- Validity_Checks --
14117          ---------------------
14118
14119          --  pragma Validity_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
14120
14121          when Pragma_Validity_Checks => Validity_Checks : declare
14122             A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
14123             S  : String_Id;
14124             C  : Char_Code;
14125
14126          begin
14127             GNAT_Pragma;
14128             Check_Arg_Count (1);
14129             Check_No_Identifiers;
14130
14131             if Nkind (A) = N_String_Literal then
14132                S   := Strval (A);
14133
14134                declare
14135                   Slen    : constant Natural := Natural (String_Length (S));
14136                   Options : String (1 .. Slen);
14137                   J       : Natural;
14138
14139                begin
14140                   J := 1;
14141                   loop
14142                      C := Get_String_Char (S, Int (J));
14143                      exit when not In_Character_Range (C);
14144                      Options (J) := Get_Character (C);
14145
14146                      if J = Slen then
14147                         Set_Validity_Check_Options (Options);
14148                         exit;
14149                      else
14150                         J := J + 1;
14151                      end if;
14152                   end loop;
14153                end;
14154
14155             elsif Nkind (A) = N_Identifier then
14156
14157                if Chars (A) = Name_All_Checks then
14158                   Set_Validity_Check_Options ("a");
14159
14160                elsif Chars (A) = Name_On then
14161                   Validity_Checks_On := True;
14162
14163                elsif Chars (A) = Name_Off then
14164                   Validity_Checks_On := False;
14165
14166                end if;
14167             end if;
14168          end Validity_Checks;
14169
14170          --------------
14171          -- Volatile --
14172          --------------
14173
14174          --  pragma Volatile (LOCAL_NAME);
14175
14176          when Pragma_Volatile =>
14177             Process_Atomic_Shared_Volatile;
14178
14179          -------------------------
14180          -- Volatile_Components --
14181          -------------------------
14182
14183          --  pragma Volatile_Components (array_LOCAL_NAME);
14184
14185          --  Volatile is handled by the same circuit as Atomic_Components
14186
14187          --------------
14188          -- Warnings --
14189          --------------
14190
14191          --  pragma Warnings (On | Off);
14192          --  pragma Warnings (On | Off, LOCAL_NAME);
14193          --  pragma Warnings (static_string_EXPRESSION);
14194          --  pragma Warnings (On | Off, STRING_LITERAL);
14195
14196          when Pragma_Warnings => Warnings : begin
14197             GNAT_Pragma;
14198             Check_At_Least_N_Arguments (1);
14199             Check_No_Identifiers;
14200
14201             --  If debug flag -gnatd.i is set, pragma is ignored
14202
14203             if Debug_Flag_Dot_I then
14204                return;
14205             end if;
14206
14207             --  Process various forms of the pragma
14208
14209             declare
14210                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
14211
14212             begin
14213                --  One argument case
14214
14215                if Arg_Count = 1 then
14216
14217                   --  On/Off one argument case was processed by parser
14218
14219                   if Nkind (Argx) = N_Identifier
14220                     and then
14221                       (Chars (Argx) = Name_On
14222                          or else
14223                        Chars (Argx) = Name_Off)
14224                   then
14225                      null;
14226
14227                   --  One argument case must be ON/OFF or static string expr
14228
14229                   elsif not Is_Static_String_Expression (Arg1) then
14230                      Error_Pragma_Arg
14231                        ("argument of pragma% must be On/Off or " &
14232                         "static string expression", Arg1);
14233
14234                   --  One argument string expression case
14235
14236                   else
14237                      declare
14238                         Lit : constant Node_Id   := Expr_Value_S (Argx);
14239                         Str : constant String_Id := Strval (Lit);
14240                         Len : constant Nat       := String_Length (Str);
14241                         C   : Char_Code;
14242                         J   : Nat;
14243                         OK  : Boolean;
14244                         Chr : Character;
14245
14246                      begin
14247                         J := 1;
14248                         while J <= Len loop
14249                            C := Get_String_Char (Str, J);
14250                            OK := In_Character_Range (C);
14251
14252                            if OK then
14253                               Chr := Get_Character (C);
14254
14255                               --  Dot case
14256
14257                               if J < Len and then Chr = '.' then
14258                                  J := J + 1;
14259                                  C := Get_String_Char (Str, J);
14260                                  Chr := Get_Character (C);
14261
14262                                  if not Set_Dot_Warning_Switch (Chr) then
14263                                     Error_Pragma_Arg
14264                                       ("invalid warning switch character " &
14265                                        '.' & Chr, Arg1);
14266                                  end if;
14267
14268                               --  Non-Dot case
14269
14270                               else
14271                                  OK := Set_Warning_Switch (Chr);
14272                               end if;
14273                            end if;
14274
14275                            if not OK then
14276                               Error_Pragma_Arg
14277                                 ("invalid warning switch character " & Chr,
14278                                  Arg1);
14279                            end if;
14280
14281                            J := J + 1;
14282                         end loop;
14283                      end;
14284                   end if;
14285
14286                   --  Two or more arguments (must be two)
14287
14288                else
14289                   Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
14290                   Check_At_Most_N_Arguments (2);
14291
14292                   declare
14293                      E_Id : Node_Id;
14294                      E    : Entity_Id;
14295                      Err  : Boolean;
14296
14297                   begin
14298                      E_Id := Get_Pragma_Arg (Arg2);
14299                      Analyze (E_Id);
14300
14301                      --  In the expansion of an inlined body, a reference to
14302                      --  the formal may be wrapped in a conversion if the
14303                      --  actual is a conversion. Retrieve the real entity name.
14304
14305                      if (In_Instance_Body
14306                          or else In_Inlined_Body)
14307                        and then Nkind (E_Id) = N_Unchecked_Type_Conversion
14308                      then
14309                         E_Id := Expression (E_Id);
14310                      end if;
14311
14312                      --  Entity name case
14313
14314                      if Is_Entity_Name (E_Id) then
14315                         E := Entity (E_Id);
14316
14317                         if E = Any_Id then
14318                            return;
14319                         else
14320                            loop
14321                               Set_Warnings_Off
14322                                 (E, (Chars (Get_Pragma_Arg (Arg1)) =
14323                                                               Name_Off));
14324
14325                               if Chars (Get_Pragma_Arg (Arg1)) = Name_Off
14326                                 and then Warn_On_Warnings_Off
14327                               then
14328                                  Warnings_Off_Pragmas.Append ((N, E));
14329                               end if;
14330
14331                               if Is_Enumeration_Type (E) then
14332                                  declare
14333                                     Lit : Entity_Id;
14334                                  begin
14335                                     Lit := First_Literal (E);
14336                                     while Present (Lit) loop
14337                                        Set_Warnings_Off (Lit);
14338                                        Next_Literal (Lit);
14339                                     end loop;
14340                                  end;
14341                               end if;
14342
14343                               exit when No (Homonym (E));
14344                               E := Homonym (E);
14345                            end loop;
14346                         end if;
14347
14348                      --  Error if not entity or static string literal case
14349
14350                      elsif not Is_Static_String_Expression (Arg2) then
14351                         Error_Pragma_Arg
14352                           ("second argument of pragma% must be entity " &
14353                            "name or static string expression", Arg2);
14354
14355                      --  String literal case
14356
14357                      else
14358                         String_To_Name_Buffer
14359                           (Strval (Expr_Value_S (Get_Pragma_Arg (Arg2))));
14360
14361                         --  Note on configuration pragma case: If this is a
14362                         --  configuration pragma, then for an OFF pragma, we
14363                         --  just set Config True in the call, which is all
14364                         --  that needs to be done. For the case of ON, this
14365                         --  is normally an error, unless it is canceling the
14366                         --  effect of a previous OFF pragma in the same file.
14367                         --  In any other case, an error will be signalled (ON
14368                         --  with no matching OFF).
14369
14370                         if Chars (Argx) = Name_Off then
14371                            Set_Specific_Warning_Off
14372                              (Loc, Name_Buffer (1 .. Name_Len),
14373                               Config => Is_Configuration_Pragma);
14374
14375                         elsif Chars (Argx) = Name_On then
14376                            Set_Specific_Warning_On
14377                              (Loc, Name_Buffer (1 .. Name_Len), Err);
14378
14379                            if Err then
14380                               Error_Msg
14381                                 ("?pragma Warnings On with no " &
14382                                  "matching Warnings Off",
14383                                  Loc);
14384                            end if;
14385                         end if;
14386                      end if;
14387                   end;
14388                end if;
14389             end;
14390          end Warnings;
14391
14392          -------------------
14393          -- Weak_External --
14394          -------------------
14395
14396          --  pragma Weak_External ([Entity =>] LOCAL_NAME);
14397
14398          when Pragma_Weak_External => Weak_External : declare
14399             Ent : Entity_Id;
14400
14401          begin
14402             GNAT_Pragma;
14403             Check_Arg_Count (1);
14404             Check_Optional_Identifier (Arg1, Name_Entity);
14405             Check_Arg_Is_Library_Level_Local_Name (Arg1);
14406             Ent := Entity (Get_Pragma_Arg (Arg1));
14407
14408             if Rep_Item_Too_Early (Ent, N) then
14409                return;
14410             else
14411                Ent := Underlying_Type (Ent);
14412             end if;
14413
14414             --  The only processing required is to link this item on to the
14415             --  list of rep items for the given entity. This is accomplished
14416             --  by the call to Rep_Item_Too_Late (when no error is detected
14417             --  and False is returned).
14418
14419             if Rep_Item_Too_Late (Ent, N) then
14420                return;
14421             else
14422                Set_Has_Gigi_Rep_Item (Ent);
14423             end if;
14424          end Weak_External;
14425
14426          -----------------------------
14427          -- Wide_Character_Encoding --
14428          -----------------------------
14429
14430          --  pragma Wide_Character_Encoding (IDENTIFIER);
14431
14432          when Pragma_Wide_Character_Encoding =>
14433             GNAT_Pragma;
14434
14435             --  Nothing to do, handled in parser. Note that we do not enforce
14436             --  configuration pragma placement, this pragma can appear at any
14437             --  place in the source, allowing mixed encodings within a single
14438             --  source program.
14439
14440             null;
14441
14442          --------------------
14443          -- Unknown_Pragma --
14444          --------------------
14445
14446          --  Should be impossible, since the case of an unknown pragma is
14447          --  separately processed before the case statement is entered.
14448
14449          when Unknown_Pragma =>
14450             raise Program_Error;
14451       end case;
14452
14453       --  AI05-0144: detect dangerous order dependence. Disabled for now,
14454       --  until AI is formally approved.
14455
14456       --  Check_Order_Dependence;
14457
14458    exception
14459       when Pragma_Exit => null;
14460    end Analyze_Pragma;
14461
14462    -----------------------------
14463    -- Analyze_TC_In_Decl_Part --
14464    -----------------------------
14465
14466    procedure Analyze_TC_In_Decl_Part (N : Node_Id; S : Entity_Id) is
14467    begin
14468       --  Install formals and push subprogram spec onto scope stack so that we
14469       --  can see the formals from the pragma.
14470
14471       Install_Formals (S);
14472       Push_Scope (S);
14473
14474       --  Preanalyze the boolean expressions, we treat these as spec
14475       --  expressions (i.e. similar to a default expression).
14476
14477       Preanalyze_TC_Args (Get_Requires_From_Test_Case_Pragma (N),
14478                           Get_Ensures_From_Test_Case_Pragma (N));
14479
14480       --  Remove the subprogram from the scope stack now that the pre-analysis
14481       --  of the expressions in the test-case is done.
14482
14483       End_Scope;
14484    end Analyze_TC_In_Decl_Part;
14485
14486    --------------------
14487    -- Check_Disabled --
14488    --------------------
14489
14490    function Check_Disabled (Nam : Name_Id) return Boolean is
14491       PP : Node_Id;
14492
14493    begin
14494       --  Loop through entries in check policy list
14495
14496       PP := Opt.Check_Policy_List;
14497       loop
14498          --  If there are no specific entries that matched, then nothing is
14499          --  disabled, so return False.
14500
14501          if No (PP) then
14502             return False;
14503
14504          --  Here we have an entry see if it matches
14505
14506          else
14507             declare
14508                PPA : constant List_Id := Pragma_Argument_Associations (PP);
14509             begin
14510                if Nam = Chars (Get_Pragma_Arg (First (PPA))) then
14511                   return Chars (Get_Pragma_Arg (Last (PPA))) = Name_Disable;
14512                else
14513                   PP := Next_Pragma (PP);
14514                end if;
14515             end;
14516          end if;
14517       end loop;
14518    end Check_Disabled;
14519
14520    -------------------
14521    -- Check_Enabled --
14522    -------------------
14523
14524    function Check_Enabled (Nam : Name_Id) return Boolean is
14525       PP : Node_Id;
14526
14527    begin
14528       --  Loop through entries in check policy list
14529
14530       PP := Opt.Check_Policy_List;
14531       loop
14532          --  If there are no specific entries that matched, then we let the
14533          --  setting of assertions govern. Note that this provides the needed
14534          --  compatibility with the RM for the cases of assertion, invariant,
14535          --  precondition, predicate, and postcondition.
14536
14537          if No (PP) then
14538             return Assertions_Enabled;
14539
14540          --  Here we have an entry see if it matches
14541
14542          else
14543             declare
14544                PPA : constant List_Id := Pragma_Argument_Associations (PP);
14545
14546             begin
14547                if Nam = Chars (Get_Pragma_Arg (First (PPA))) then
14548                   case (Chars (Get_Pragma_Arg (Last (PPA)))) is
14549                      when Name_On | Name_Check =>
14550                         return True;
14551                      when Name_Off | Name_Ignore =>
14552                         return False;
14553                      when others =>
14554                         raise Program_Error;
14555                   end case;
14556
14557                else
14558                   PP := Next_Pragma (PP);
14559                end if;
14560             end;
14561          end if;
14562       end loop;
14563    end Check_Enabled;
14564
14565    ---------------------------------
14566    -- Delay_Config_Pragma_Analyze --
14567    ---------------------------------
14568
14569    function Delay_Config_Pragma_Analyze (N : Node_Id) return Boolean is
14570    begin
14571       return Pragma_Name (N) = Name_Interrupt_State
14572                or else
14573              Pragma_Name (N) = Name_Priority_Specific_Dispatching;
14574    end Delay_Config_Pragma_Analyze;
14575
14576    -------------------------
14577    -- Get_Base_Subprogram --
14578    -------------------------
14579
14580    function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id is
14581       Result : Entity_Id;
14582
14583    begin
14584       --  Follow subprogram renaming chain
14585
14586       Result := Def_Id;
14587       while Is_Subprogram (Result)
14588         and then
14589           Nkind (Parent (Declaration_Node (Result))) =
14590                                          N_Subprogram_Renaming_Declaration
14591         and then Present (Alias (Result))
14592       loop
14593          Result := Alias (Result);
14594       end loop;
14595
14596       return Result;
14597    end Get_Base_Subprogram;
14598
14599    ----------------
14600    -- Initialize --
14601    ----------------
14602
14603    procedure Initialize is
14604    begin
14605       Externals.Init;
14606    end Initialize;
14607
14608    -----------------------------
14609    -- Is_Config_Static_String --
14610    -----------------------------
14611
14612    function Is_Config_Static_String (Arg : Node_Id) return Boolean is
14613
14614       function Add_Config_Static_String (Arg : Node_Id) return Boolean;
14615       --  This is an internal recursive function that is just like the outer
14616       --  function except that it adds the string to the name buffer rather
14617       --  than placing the string in the name buffer.
14618
14619       ------------------------------
14620       -- Add_Config_Static_String --
14621       ------------------------------
14622
14623       function Add_Config_Static_String (Arg : Node_Id) return Boolean is
14624          N : Node_Id;
14625          C : Char_Code;
14626
14627       begin
14628          N := Arg;
14629
14630          if Nkind (N) = N_Op_Concat then
14631             if Add_Config_Static_String (Left_Opnd (N)) then
14632                N := Right_Opnd (N);
14633             else
14634                return False;
14635             end if;
14636          end if;
14637
14638          if Nkind (N) /= N_String_Literal then
14639             Error_Msg_N ("string literal expected for pragma argument", N);
14640             return False;
14641
14642          else
14643             for J in 1 .. String_Length (Strval (N)) loop
14644                C := Get_String_Char (Strval (N), J);
14645
14646                if not In_Character_Range (C) then
14647                   Error_Msg
14648                     ("string literal contains invalid wide character",
14649                      Sloc (N) + 1 + Source_Ptr (J));
14650                   return False;
14651                end if;
14652
14653                Add_Char_To_Name_Buffer (Get_Character (C));
14654             end loop;
14655          end if;
14656
14657          return True;
14658       end Add_Config_Static_String;
14659
14660    --  Start of processing for Is_Config_Static_String
14661
14662    begin
14663
14664       Name_Len := 0;
14665       return Add_Config_Static_String (Arg);
14666    end Is_Config_Static_String;
14667
14668    -----------------------------------------
14669    -- Is_Non_Significant_Pragma_Reference --
14670    -----------------------------------------
14671
14672    --  This function makes use of the following static table which indicates
14673    --  whether a given pragma is significant.
14674
14675    --  -1  indicates that references in any argument position are significant
14676    --  0   indicates that appearance in any argument is not significant
14677    --  +n  indicates that appearance as argument n is significant, but all
14678    --      other arguments are not significant
14679    --  99  special processing required (e.g. for pragma Check)
14680
14681    Sig_Flags : constant array (Pragma_Id) of Int :=
14682      (Pragma_AST_Entry                     => -1,
14683       Pragma_Abort_Defer                   => -1,
14684       Pragma_Ada_83                        => -1,
14685       Pragma_Ada_95                        => -1,
14686       Pragma_Ada_05                        => -1,
14687       Pragma_Ada_2005                      => -1,
14688       Pragma_Ada_12                        => -1,
14689       Pragma_Ada_2012                      => -1,
14690       Pragma_All_Calls_Remote              => -1,
14691       Pragma_Annotate                      => -1,
14692       Pragma_Assert                        => -1,
14693       Pragma_Assertion_Policy              =>  0,
14694       Pragma_Assume_No_Invalid_Values      =>  0,
14695       Pragma_Asynchronous                  => -1,
14696       Pragma_Atomic                        =>  0,
14697       Pragma_Atomic_Components             =>  0,
14698       Pragma_Attach_Handler                => -1,
14699       Pragma_Check                         => 99,
14700       Pragma_Check_Name                    =>  0,
14701       Pragma_Check_Policy                  =>  0,
14702       Pragma_CIL_Constructor               => -1,
14703       Pragma_CPP_Class                     =>  0,
14704       Pragma_CPP_Constructor               =>  0,
14705       Pragma_CPP_Virtual                   =>  0,
14706       Pragma_CPP_Vtable                    =>  0,
14707       Pragma_CPU                           => -1,
14708       Pragma_C_Pass_By_Copy                =>  0,
14709       Pragma_Comment                       =>  0,
14710       Pragma_Common_Object                 => -1,
14711       Pragma_Compile_Time_Error            => -1,
14712       Pragma_Compile_Time_Warning          => -1,
14713       Pragma_Compiler_Unit                 =>  0,
14714       Pragma_Complete_Representation       =>  0,
14715       Pragma_Complex_Representation        =>  0,
14716       Pragma_Component_Alignment           => -1,
14717       Pragma_Controlled                    =>  0,
14718       Pragma_Convention                    =>  0,
14719       Pragma_Convention_Identifier         =>  0,
14720       Pragma_Debug                         => -1,
14721       Pragma_Debug_Policy                  =>  0,
14722       Pragma_Detect_Blocking               => -1,
14723       Pragma_Default_Storage_Pool          => -1,
14724       Pragma_Dimension                     => -1,
14725       Pragma_Discard_Names                 =>  0,
14726       Pragma_Dispatching_Domain            => -1,
14727       Pragma_Elaborate                     => -1,
14728       Pragma_Elaborate_All                 => -1,
14729       Pragma_Elaborate_Body                => -1,
14730       Pragma_Elaboration_Checks            => -1,
14731       Pragma_Eliminate                     => -1,
14732       Pragma_Export                        => -1,
14733       Pragma_Export_Exception              => -1,
14734       Pragma_Export_Function               => -1,
14735       Pragma_Export_Object                 => -1,
14736       Pragma_Export_Procedure              => -1,
14737       Pragma_Export_Value                  => -1,
14738       Pragma_Export_Valued_Procedure       => -1,
14739       Pragma_Extend_System                 => -1,
14740       Pragma_Extensions_Allowed            => -1,
14741       Pragma_External                      => -1,
14742       Pragma_Favor_Top_Level               => -1,
14743       Pragma_External_Name_Casing          => -1,
14744       Pragma_Fast_Math                     => -1,
14745       Pragma_Finalize_Storage_Only         =>  0,
14746       Pragma_Float_Representation          =>  0,
14747       Pragma_Ident                         => -1,
14748       Pragma_Implementation_Defined        => -1,
14749       Pragma_Implemented                   => -1,
14750       Pragma_Implicit_Packing              =>  0,
14751       Pragma_Import                        => +2,
14752       Pragma_Import_Exception              =>  0,
14753       Pragma_Import_Function               =>  0,
14754       Pragma_Import_Object                 =>  0,
14755       Pragma_Import_Procedure              =>  0,
14756       Pragma_Import_Valued_Procedure       =>  0,
14757       Pragma_Independent                   =>  0,
14758       Pragma_Independent_Components        =>  0,
14759       Pragma_Initialize_Scalars            => -1,
14760       Pragma_Inline                        =>  0,
14761       Pragma_Inline_Always                 =>  0,
14762       Pragma_Inline_Generic                =>  0,
14763       Pragma_Inspection_Point              => -1,
14764       Pragma_Interface                     => +2,
14765       Pragma_Interface_Name                => +2,
14766       Pragma_Interrupt_Handler             => -1,
14767       Pragma_Interrupt_Priority            => -1,
14768       Pragma_Interrupt_State               => -1,
14769       Pragma_Invariant                     => -1,
14770       Pragma_Java_Constructor              => -1,
14771       Pragma_Java_Interface                => -1,
14772       Pragma_Keep_Names                    =>  0,
14773       Pragma_License                       => -1,
14774       Pragma_Link_With                     => -1,
14775       Pragma_Linker_Alias                  => -1,
14776       Pragma_Linker_Constructor            => -1,
14777       Pragma_Linker_Destructor             => -1,
14778       Pragma_Linker_Options                => -1,
14779       Pragma_Linker_Section                => -1,
14780       Pragma_List                          => -1,
14781       Pragma_Locking_Policy                => -1,
14782       Pragma_Long_Float                    => -1,
14783       Pragma_Machine_Attribute             => -1,
14784       Pragma_Main                          => -1,
14785       Pragma_Main_Storage                  => -1,
14786       Pragma_Memory_Size                   => -1,
14787       Pragma_No_Return                     =>  0,
14788       Pragma_No_Body                       =>  0,
14789       Pragma_No_Run_Time                   => -1,
14790       Pragma_No_Strict_Aliasing            => -1,
14791       Pragma_Normalize_Scalars             => -1,
14792       Pragma_Obsolescent                   =>  0,
14793       Pragma_Optimize                      => -1,
14794       Pragma_Optimize_Alignment            => -1,
14795       Pragma_Ordered                       =>  0,
14796       Pragma_Pack                          =>  0,
14797       Pragma_Page                          => -1,
14798       Pragma_Passive                       => -1,
14799       Pragma_Preelaborable_Initialization  => -1,
14800       Pragma_Polling                       => -1,
14801       Pragma_Persistent_BSS                =>  0,
14802       Pragma_Postcondition                 => -1,
14803       Pragma_Precondition                  => -1,
14804       Pragma_Predicate                     => -1,
14805       Pragma_Preelaborate                  => -1,
14806       Pragma_Preelaborate_05               => -1,
14807       Pragma_Priority                      => -1,
14808       Pragma_Priority_Specific_Dispatching => -1,
14809       Pragma_Profile                       =>  0,
14810       Pragma_Profile_Warnings              =>  0,
14811       Pragma_Propagate_Exceptions          => -1,
14812       Pragma_Psect_Object                  => -1,
14813       Pragma_Pure                          => -1,
14814       Pragma_Pure_05                       => -1,
14815       Pragma_Pure_Function                 => -1,
14816       Pragma_Queuing_Policy                => -1,
14817       Pragma_Ravenscar                     => -1,
14818       Pragma_Relative_Deadline             => -1,
14819       Pragma_Remote_Call_Interface         => -1,
14820       Pragma_Remote_Types                  => -1,
14821       Pragma_Restricted_Run_Time           => -1,
14822       Pragma_Restriction_Warnings          => -1,
14823       Pragma_Restrictions                  => -1,
14824       Pragma_Reviewable                    => -1,
14825       Pragma_Short_Circuit_And_Or          => -1,
14826       Pragma_Share_Generic                 => -1,
14827       Pragma_Shared                        => -1,
14828       Pragma_Shared_Passive                => -1,
14829       Pragma_Short_Descriptors             =>  0,
14830       Pragma_Source_File_Name              => -1,
14831       Pragma_Source_File_Name_Project      => -1,
14832       Pragma_Source_Reference              => -1,
14833       Pragma_Storage_Size                  => -1,
14834       Pragma_Storage_Unit                  => -1,
14835       Pragma_Static_Elaboration_Desired    => -1,
14836       Pragma_Stream_Convert                => -1,
14837       Pragma_Style_Checks                  => -1,
14838       Pragma_Subtitle                      => -1,
14839       Pragma_Suppress                      =>  0,
14840       Pragma_Suppress_Exception_Locations  =>  0,
14841       Pragma_Suppress_All                  => -1,
14842       Pragma_Suppress_Debug_Info           =>  0,
14843       Pragma_Suppress_Initialization       =>  0,
14844       Pragma_System_Name                   => -1,
14845       Pragma_Task_Dispatching_Policy       => -1,
14846       Pragma_Task_Info                     => -1,
14847       Pragma_Task_Name                     => -1,
14848       Pragma_Task_Storage                  =>  0,
14849       Pragma_Test_Case                     => -1,
14850       Pragma_Thread_Local_Storage          =>  0,
14851       Pragma_Time_Slice                    => -1,
14852       Pragma_Title                         => -1,
14853       Pragma_Unchecked_Union               =>  0,
14854       Pragma_Unimplemented_Unit            => -1,
14855       Pragma_Universal_Aliasing            => -1,
14856       Pragma_Universal_Data                => -1,
14857       Pragma_Unmodified                    => -1,
14858       Pragma_Unreferenced                  => -1,
14859       Pragma_Unreferenced_Objects          => -1,
14860       Pragma_Unreserve_All_Interrupts      => -1,
14861       Pragma_Unsuppress                    =>  0,
14862       Pragma_Use_VADS_Size                 => -1,
14863       Pragma_Validity_Checks               => -1,
14864       Pragma_Volatile                      =>  0,
14865       Pragma_Volatile_Components           =>  0,
14866       Pragma_Warnings                      => -1,
14867       Pragma_Weak_External                 => -1,
14868       Pragma_Wide_Character_Encoding       =>  0,
14869       Unknown_Pragma                       =>  0);
14870
14871    function Is_Non_Significant_Pragma_Reference (N : Node_Id) return Boolean is
14872       Id : Pragma_Id;
14873       P  : Node_Id;
14874       C  : Int;
14875       A  : Node_Id;
14876
14877    begin
14878       P := Parent (N);
14879
14880       if Nkind (P) /= N_Pragma_Argument_Association then
14881          return False;
14882
14883       else
14884          Id := Get_Pragma_Id (Parent (P));
14885          C := Sig_Flags (Id);
14886
14887          case C is
14888             when -1 =>
14889                return False;
14890
14891             when 0 =>
14892                return True;
14893
14894             when 99 =>
14895                case Id is
14896
14897                   --  For pragma Check, the first argument is not significant,
14898                   --  the second and the third (if present) arguments are
14899                   --  significant.
14900
14901                   when Pragma_Check =>
14902                      return
14903                        P = First (Pragma_Argument_Associations (Parent (P)));
14904
14905                   when others =>
14906                      raise Program_Error;
14907                end case;
14908
14909             when others =>
14910                A := First (Pragma_Argument_Associations (Parent (P)));
14911                for J in 1 .. C - 1 loop
14912                   if No (A) then
14913                      return False;
14914                   end if;
14915
14916                   Next (A);
14917                end loop;
14918
14919                return A = P; -- is this wrong way round ???
14920          end case;
14921       end if;
14922    end Is_Non_Significant_Pragma_Reference;
14923
14924    ------------------------------
14925    -- Is_Pragma_String_Literal --
14926    ------------------------------
14927
14928    --  This function returns true if the corresponding pragma argument is a
14929    --  static string expression. These are the only cases in which string
14930    --  literals can appear as pragma arguments. We also allow a string literal
14931    --  as the first argument to pragma Assert (although it will of course
14932    --  always generate a type error).
14933
14934    function Is_Pragma_String_Literal (Par : Node_Id) return Boolean is
14935       Pragn : constant Node_Id := Parent (Par);
14936       Assoc : constant List_Id := Pragma_Argument_Associations (Pragn);
14937       Pname : constant Name_Id := Pragma_Name (Pragn);
14938       Argn  : Natural;
14939       N     : Node_Id;
14940
14941    begin
14942       Argn := 1;
14943       N := First (Assoc);
14944       loop
14945          exit when N = Par;
14946          Argn := Argn + 1;
14947          Next (N);
14948       end loop;
14949
14950       if Pname = Name_Assert then
14951          return True;
14952
14953       elsif Pname = Name_Export then
14954          return Argn > 2;
14955
14956       elsif Pname = Name_Ident then
14957          return Argn = 1;
14958
14959       elsif Pname = Name_Import then
14960          return Argn > 2;
14961
14962       elsif Pname = Name_Interface_Name then
14963          return Argn > 1;
14964
14965       elsif Pname = Name_Linker_Alias then
14966          return Argn = 2;
14967
14968       elsif Pname = Name_Linker_Section then
14969          return Argn = 2;
14970
14971       elsif Pname = Name_Machine_Attribute then
14972          return Argn = 2;
14973
14974       elsif Pname = Name_Source_File_Name then
14975          return True;
14976
14977       elsif Pname = Name_Source_Reference then
14978          return Argn = 2;
14979
14980       elsif Pname = Name_Title then
14981          return True;
14982
14983       elsif Pname = Name_Subtitle then
14984          return True;
14985
14986       else
14987          return False;
14988       end if;
14989    end Is_Pragma_String_Literal;
14990
14991    ------------------------
14992    -- Preanalyze_TC_Args --
14993    ------------------------
14994
14995    procedure Preanalyze_TC_Args (Arg_Req, Arg_Ens : Node_Id) is
14996    begin
14997       --  Preanalyze the boolean expressions, we treat these as spec
14998       --  expressions (i.e. similar to a default expression).
14999
15000       if Present (Arg_Req) then
15001          Preanalyze_Spec_Expression
15002            (Get_Pragma_Arg (Arg_Req), Standard_Boolean);
15003       end if;
15004
15005       if Present (Arg_Ens) then
15006          Preanalyze_Spec_Expression
15007            (Get_Pragma_Arg (Arg_Ens), Standard_Boolean);
15008       end if;
15009    end Preanalyze_TC_Args;
15010
15011    --------------------------------------
15012    -- Process_Compilation_Unit_Pragmas --
15013    --------------------------------------
15014
15015    procedure Process_Compilation_Unit_Pragmas (N : Node_Id) is
15016    begin
15017       --  A special check for pragma Suppress_All, a very strange DEC pragma,
15018       --  strange because it comes at the end of the unit. Rational has the
15019       --  same name for a pragma, but treats it as a program unit pragma, In
15020       --  GNAT we just decide to allow it anywhere at all. If it appeared then
15021       --  the flag Has_Pragma_Suppress_All was set on the compilation unit
15022       --  node, and we insert a pragma Suppress (All_Checks) at the start of
15023       --  the context clause to ensure the correct processing.
15024
15025       if Has_Pragma_Suppress_All (N) then
15026          Prepend_To (Context_Items (N),
15027            Make_Pragma (Sloc (N),
15028              Chars                        => Name_Suppress,
15029              Pragma_Argument_Associations => New_List (
15030                Make_Pragma_Argument_Association (Sloc (N),
15031                  Expression => Make_Identifier (Sloc (N), Name_All_Checks)))));
15032       end if;
15033
15034       --  Nothing else to do at the current time!
15035
15036    end Process_Compilation_Unit_Pragmas;
15037
15038    --------
15039    -- rv --
15040    --------
15041
15042    procedure rv is
15043    begin
15044       null;
15045    end rv;
15046
15047    --------------------------------
15048    -- Set_Encoded_Interface_Name --
15049    --------------------------------
15050
15051    procedure Set_Encoded_Interface_Name (E : Entity_Id; S : Node_Id) is
15052       Str : constant String_Id := Strval (S);
15053       Len : constant Int       := String_Length (Str);
15054       CC  : Char_Code;
15055       C   : Character;
15056       J   : Int;
15057
15058       Hex : constant array (0 .. 15) of Character := "0123456789abcdef";
15059
15060       procedure Encode;
15061       --  Stores encoded value of character code CC. The encoding we use an
15062       --  underscore followed by four lower case hex digits.
15063
15064       ------------
15065       -- Encode --
15066       ------------
15067
15068       procedure Encode is
15069       begin
15070          Store_String_Char (Get_Char_Code ('_'));
15071          Store_String_Char
15072            (Get_Char_Code (Hex (Integer (CC / 2 ** 12))));
15073          Store_String_Char
15074            (Get_Char_Code (Hex (Integer (CC / 2 ** 8 and 16#0F#))));
15075          Store_String_Char
15076            (Get_Char_Code (Hex (Integer (CC / 2 ** 4 and 16#0F#))));
15077          Store_String_Char
15078            (Get_Char_Code (Hex (Integer (CC and 16#0F#))));
15079       end Encode;
15080
15081    --  Start of processing for Set_Encoded_Interface_Name
15082
15083    begin
15084       --  If first character is asterisk, this is a link name, and we leave it
15085       --  completely unmodified. We also ignore null strings (the latter case
15086       --  happens only in error cases) and no encoding should occur for Java or
15087       --  AAMP interface names.
15088
15089       if Len = 0
15090         or else Get_String_Char (Str, 1) = Get_Char_Code ('*')
15091         or else VM_Target /= No_VM
15092         or else AAMP_On_Target
15093       then
15094          Set_Interface_Name (E, S);
15095
15096       else
15097          J := 1;
15098          loop
15099             CC := Get_String_Char (Str, J);
15100
15101             exit when not In_Character_Range (CC);
15102
15103             C := Get_Character (CC);
15104
15105             exit when C /= '_' and then C /= '$'
15106               and then C not in '0' .. '9'
15107               and then C not in 'a' .. 'z'
15108               and then C not in 'A' .. 'Z';
15109
15110             if J = Len then
15111                Set_Interface_Name (E, S);
15112                return;
15113
15114             else
15115                J := J + 1;
15116             end if;
15117          end loop;
15118
15119          --  Here we need to encode. The encoding we use as follows:
15120          --     three underscores  + four hex digits (lower case)
15121
15122          Start_String;
15123
15124          for J in 1 .. String_Length (Str) loop
15125             CC := Get_String_Char (Str, J);
15126
15127             if not In_Character_Range (CC) then
15128                Encode;
15129             else
15130                C := Get_Character (CC);
15131
15132                if C = '_' or else C = '$'
15133                  or else C in '0' .. '9'
15134                  or else C in 'a' .. 'z'
15135                  or else C in 'A' .. 'Z'
15136                then
15137                   Store_String_Char (CC);
15138                else
15139                   Encode;
15140                end if;
15141             end if;
15142          end loop;
15143
15144          Set_Interface_Name (E,
15145            Make_String_Literal (Sloc (S),
15146              Strval => End_String));
15147       end if;
15148    end Set_Encoded_Interface_Name;
15149
15150    -------------------
15151    -- Set_Unit_Name --
15152    -------------------
15153
15154    procedure Set_Unit_Name (N : Node_Id; With_Item : Node_Id) is
15155       Pref : Node_Id;
15156       Scop : Entity_Id;
15157
15158    begin
15159       if Nkind (N) = N_Identifier
15160         and then Nkind (With_Item) = N_Identifier
15161       then
15162          Set_Entity (N, Entity (With_Item));
15163
15164       elsif Nkind (N) = N_Selected_Component then
15165          Change_Selected_Component_To_Expanded_Name (N);
15166          Set_Entity (N, Entity (With_Item));
15167          Set_Entity (Selector_Name (N), Entity (N));
15168
15169          Pref := Prefix (N);
15170          Scop := Scope (Entity (N));
15171          while Nkind (Pref) = N_Selected_Component loop
15172             Change_Selected_Component_To_Expanded_Name (Pref);
15173             Set_Entity (Selector_Name (Pref), Scop);
15174             Set_Entity (Pref, Scop);
15175             Pref := Prefix (Pref);
15176             Scop := Scope (Scop);
15177          end loop;
15178
15179          Set_Entity (Pref, Scop);
15180       end if;
15181    end Set_Unit_Name;
15182
15183 end Sem_Prag;