OSDN Git Service

2011-10-24 Robert Dewar <dewar@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_Disable_Enable_Atomic_Sync (Nam : Name_Id);
754       --  Common processing for Disable/Enable_Atomic_Synchronization. Nam is
755       --  Name_Suppress for Disable and Name_Unsuppress for Enable.
756
757       procedure Process_Extended_Import_Export_Exception_Pragma
758         (Arg_Internal : Node_Id;
759          Arg_External : Node_Id;
760          Arg_Form     : Node_Id;
761          Arg_Code     : Node_Id);
762       --  Common processing for the pragmas Import/Export_Exception. The three
763       --  arguments correspond to the three named parameters of the pragma. An
764       --  argument is empty if the corresponding parameter is not present in
765       --  the pragma.
766
767       procedure Process_Extended_Import_Export_Object_Pragma
768         (Arg_Internal : Node_Id;
769          Arg_External : Node_Id;
770          Arg_Size     : Node_Id);
771       --  Common processing for the pragmas Import/Export_Object. The three
772       --  arguments correspond to the three named parameters of the pragmas. An
773       --  argument is empty if the corresponding parameter is not present in
774       --  the pragma.
775
776       procedure Process_Extended_Import_Export_Internal_Arg
777         (Arg_Internal : Node_Id := Empty);
778       --  Common processing for all extended Import and Export pragmas. The
779       --  argument is the pragma parameter for the Internal argument. If
780       --  Arg_Internal is empty or inappropriate, an error message is posted.
781       --  Otherwise, on normal return, the Entity_Field of Arg_Internal is
782       --  set to identify the referenced entity.
783
784       procedure Process_Extended_Import_Export_Subprogram_Pragma
785         (Arg_Internal                 : Node_Id;
786          Arg_External                 : Node_Id;
787          Arg_Parameter_Types          : Node_Id;
788          Arg_Result_Type              : Node_Id := Empty;
789          Arg_Mechanism                : Node_Id;
790          Arg_Result_Mechanism         : Node_Id := Empty;
791          Arg_First_Optional_Parameter : Node_Id := Empty);
792       --  Common processing for all extended Import and Export pragmas applying
793       --  to subprograms. The caller omits any arguments that do not apply to
794       --  the pragma in question (for example, Arg_Result_Type can be non-Empty
795       --  only in the Import_Function and Export_Function cases). The argument
796       --  names correspond to the allowed pragma association identifiers.
797
798       procedure Process_Generic_List;
799       --  Common processing for Share_Generic and Inline_Generic
800
801       procedure Process_Import_Or_Interface;
802       --  Common processing for Import of Interface
803
804       procedure Process_Import_Predefined_Type;
805       --  Processing for completing a type with pragma Import. This is used
806       --  to declare types that match predefined C types, especially for cases
807       --  without corresponding Ada predefined type.
808
809       procedure Process_Inline (Active : Boolean);
810       --  Common processing for Inline and Inline_Always. The parameter
811       --  indicates if the inline pragma is active, i.e. if it should actually
812       --  cause inlining to occur.
813
814       procedure Process_Interface_Name
815         (Subprogram_Def : Entity_Id;
816          Ext_Arg        : Node_Id;
817          Link_Arg       : Node_Id);
818       --  Given the last two arguments of pragma Import, pragma Export, or
819       --  pragma Interface_Name, performs validity checks and sets the
820       --  Interface_Name field of the given subprogram entity to the
821       --  appropriate external or link name, depending on the arguments given.
822       --  Ext_Arg is always present, but Link_Arg may be missing. Note that
823       --  Ext_Arg may represent the Link_Name if Link_Arg is missing, and
824       --  appropriate named notation is used for Ext_Arg. If neither Ext_Arg
825       --  nor Link_Arg is present, the interface name is set to the default
826       --  from the subprogram name.
827
828       procedure Process_Interrupt_Or_Attach_Handler;
829       --  Common processing for Interrupt and Attach_Handler pragmas
830
831       procedure Process_Restrictions_Or_Restriction_Warnings (Warn : Boolean);
832       --  Common processing for Restrictions and Restriction_Warnings pragmas.
833       --  Warn is True for Restriction_Warnings, or for Restrictions if the
834       --  flag Treat_Restrictions_As_Warnings is set, and False if this flag
835       --  is not set in the Restrictions case.
836
837       procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean);
838       --  Common processing for Suppress and Unsuppress. The boolean parameter
839       --  Suppress_Case is True for the Suppress case, and False for the
840       --  Unsuppress case.
841
842       procedure Set_Exported (E : Entity_Id; Arg : Node_Id);
843       --  This procedure sets the Is_Exported flag for the given entity,
844       --  checking that the entity was not previously imported. Arg is
845       --  the argument that specified the entity. A check is also made
846       --  for exporting inappropriate entities.
847
848       procedure Set_Extended_Import_Export_External_Name
849         (Internal_Ent : Entity_Id;
850          Arg_External : Node_Id);
851       --  Common processing for all extended import export pragmas. The first
852       --  argument, Internal_Ent, is the internal entity, which has already
853       --  been checked for validity by the caller. Arg_External is from the
854       --  Import or Export pragma, and may be null if no External parameter
855       --  was present. If Arg_External is present and is a non-null string
856       --  (a null string is treated as the default), then the Interface_Name
857       --  field of Internal_Ent is set appropriately.
858
859       procedure Set_Imported (E : Entity_Id);
860       --  This procedure sets the Is_Imported flag for the given entity,
861       --  checking that it is not previously exported or imported.
862
863       procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id);
864       --  Mech is a parameter passing mechanism (see Import_Function syntax
865       --  for MECHANISM_NAME). This routine checks that the mechanism argument
866       --  has the right form, and if not issues an error message. If the
867       --  argument has the right form then the Mechanism field of Ent is
868       --  set appropriately.
869
870       procedure Set_Ravenscar_Profile (N : Node_Id);
871       --  Activate the set of configuration pragmas and restrictions that make
872       --  up the Ravenscar Profile. N is the corresponding pragma node, which
873       --  is used for error messages on any constructs that violate the
874       --  profile.
875
876       ---------------------
877       -- Ada_2005_Pragma --
878       ---------------------
879
880       procedure Ada_2005_Pragma is
881       begin
882          if Ada_Version <= Ada_95 then
883             Check_Restriction (No_Implementation_Pragmas, N);
884          end if;
885       end Ada_2005_Pragma;
886
887       ---------------------
888       -- Ada_2012_Pragma --
889       ---------------------
890
891       procedure Ada_2012_Pragma is
892       begin
893          if Ada_Version <= Ada_2005 then
894             Check_Restriction (No_Implementation_Pragmas, N);
895          end if;
896       end Ada_2012_Pragma;
897
898       --------------------------
899       -- Check_Ada_83_Warning --
900       --------------------------
901
902       procedure Check_Ada_83_Warning is
903       begin
904          if Ada_Version = Ada_83 and then Comes_From_Source (N) then
905             Error_Msg_N ("(Ada 83) pragma& is non-standard?", N);
906          end if;
907       end Check_Ada_83_Warning;
908
909       ---------------------
910       -- Check_Arg_Count --
911       ---------------------
912
913       procedure Check_Arg_Count (Required : Nat) is
914       begin
915          if Arg_Count /= Required then
916             Error_Pragma ("wrong number of arguments for pragma%");
917          end if;
918       end Check_Arg_Count;
919
920       --------------------------------
921       -- Check_Arg_Is_External_Name --
922       --------------------------------
923
924       procedure Check_Arg_Is_External_Name (Arg : Node_Id) is
925          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
926
927       begin
928          if Nkind (Argx) = N_Identifier then
929             return;
930
931          else
932             Analyze_And_Resolve (Argx, Standard_String);
933
934             if Is_OK_Static_Expression (Argx) then
935                return;
936
937             elsif Etype (Argx) = Any_Type then
938                raise Pragma_Exit;
939
940             --  An interesting special case, if we have a string literal and
941             --  we are in Ada 83 mode, then we allow it even though it will
942             --  not be flagged as static. This allows expected Ada 83 mode
943             --  use of external names which are string literals, even though
944             --  technically these are not static in Ada 83.
945
946             elsif Ada_Version = Ada_83
947               and then Nkind (Argx) = N_String_Literal
948             then
949                return;
950
951             --  Static expression that raises Constraint_Error. This has
952             --  already been flagged, so just exit from pragma processing.
953
954             elsif Is_Static_Expression (Argx) then
955                raise Pragma_Exit;
956
957             --  Here we have a real error (non-static expression)
958
959             else
960                Error_Msg_Name_1 := Pname;
961
962                declare
963                   Msg : String :=
964                           "argument for pragma% must be a identifier or "
965                           & "static string expression!";
966                begin
967                   Fix_Error (Msg);
968                   Flag_Non_Static_Expr (Msg, Argx);
969                   raise Pragma_Exit;
970                end;
971             end if;
972          end if;
973       end Check_Arg_Is_External_Name;
974
975       -----------------------------
976       -- Check_Arg_Is_Identifier --
977       -----------------------------
978
979       procedure Check_Arg_Is_Identifier (Arg : Node_Id) is
980          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
981       begin
982          if Nkind (Argx) /= N_Identifier then
983             Error_Pragma_Arg
984               ("argument for pragma% must be identifier", Argx);
985          end if;
986       end Check_Arg_Is_Identifier;
987
988       ----------------------------------
989       -- Check_Arg_Is_Integer_Literal --
990       ----------------------------------
991
992       procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id) is
993          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
994       begin
995          if Nkind (Argx) /= N_Integer_Literal then
996             Error_Pragma_Arg
997               ("argument for pragma% must be integer literal", Argx);
998          end if;
999       end Check_Arg_Is_Integer_Literal;
1000
1001       -------------------------------------------
1002       -- Check_Arg_Is_Library_Level_Local_Name --
1003       -------------------------------------------
1004
1005       --  LOCAL_NAME ::=
1006       --    DIRECT_NAME
1007       --  | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
1008       --  | library_unit_NAME
1009
1010       procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id) is
1011       begin
1012          Check_Arg_Is_Local_Name (Arg);
1013
1014          if not Is_Library_Level_Entity (Entity (Get_Pragma_Arg (Arg)))
1015            and then Comes_From_Source (N)
1016          then
1017             Error_Pragma_Arg
1018               ("argument for pragma% must be library level entity", Arg);
1019          end if;
1020       end Check_Arg_Is_Library_Level_Local_Name;
1021
1022       -----------------------------
1023       -- Check_Arg_Is_Local_Name --
1024       -----------------------------
1025
1026       --  LOCAL_NAME ::=
1027       --    DIRECT_NAME
1028       --  | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
1029       --  | library_unit_NAME
1030
1031       procedure Check_Arg_Is_Local_Name (Arg : Node_Id) is
1032          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1033
1034       begin
1035          Analyze (Argx);
1036
1037          if Nkind (Argx) not in N_Direct_Name
1038            and then (Nkind (Argx) /= N_Attribute_Reference
1039                       or else Present (Expressions (Argx))
1040                       or else Nkind (Prefix (Argx)) /= N_Identifier)
1041            and then (not Is_Entity_Name (Argx)
1042                       or else not Is_Compilation_Unit (Entity (Argx)))
1043          then
1044             Error_Pragma_Arg ("argument for pragma% must be local name", Argx);
1045          end if;
1046
1047          --  No further check required if not an entity name
1048
1049          if not Is_Entity_Name (Argx) then
1050             null;
1051
1052          else
1053             declare
1054                OK   : Boolean;
1055                Ent  : constant Entity_Id := Entity (Argx);
1056                Scop : constant Entity_Id := Scope (Ent);
1057             begin
1058                --  Case of a pragma applied to a compilation unit: pragma must
1059                --  occur immediately after the program unit in the compilation.
1060
1061                if Is_Compilation_Unit (Ent) then
1062                   declare
1063                      Decl : constant Node_Id := Unit_Declaration_Node (Ent);
1064
1065                   begin
1066                      --  Case of pragma placed immediately after spec
1067
1068                      if Parent (N) = Aux_Decls_Node (Parent (Decl)) then
1069                         OK := True;
1070
1071                      --  Case of pragma placed immediately after body
1072
1073                      elsif Nkind (Decl) = N_Subprogram_Declaration
1074                              and then Present (Corresponding_Body (Decl))
1075                      then
1076                         OK := Parent (N) =
1077                                 Aux_Decls_Node
1078                                   (Parent (Unit_Declaration_Node
1079                                              (Corresponding_Body (Decl))));
1080
1081                      --  All other cases are illegal
1082
1083                      else
1084                         OK := False;
1085                      end if;
1086                   end;
1087
1088                --  Special restricted placement rule from 10.2.1(11.8/2)
1089
1090                elsif Is_Generic_Formal (Ent)
1091                        and then Prag_Id = Pragma_Preelaborable_Initialization
1092                then
1093                   OK := List_Containing (N) =
1094                           Generic_Formal_Declarations
1095                             (Unit_Declaration_Node (Scop));
1096
1097                --  Default case, just check that the pragma occurs in the scope
1098                --  of the entity denoted by the name.
1099
1100                else
1101                   OK := Current_Scope = Scop;
1102                end if;
1103
1104                if not OK then
1105                   Error_Pragma_Arg
1106                     ("pragma% argument must be in same declarative part", Arg);
1107                end if;
1108             end;
1109          end if;
1110       end Check_Arg_Is_Local_Name;
1111
1112       ---------------------------------
1113       -- Check_Arg_Is_Locking_Policy --
1114       ---------------------------------
1115
1116       procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id) is
1117          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1118
1119       begin
1120          Check_Arg_Is_Identifier (Argx);
1121
1122          if not Is_Locking_Policy_Name (Chars (Argx)) then
1123             Error_Pragma_Arg ("& is not a valid locking policy name", Argx);
1124          end if;
1125       end Check_Arg_Is_Locking_Policy;
1126
1127       -------------------------
1128       -- Check_Arg_Is_One_Of --
1129       -------------------------
1130
1131       procedure Check_Arg_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
1132          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1133
1134       begin
1135          Check_Arg_Is_Identifier (Argx);
1136
1137          if Chars (Argx) /= N1 and then Chars (Argx) /= N2 then
1138             Error_Msg_Name_2 := N1;
1139             Error_Msg_Name_3 := N2;
1140             Error_Pragma_Arg ("argument for pragma% must be% or%", Argx);
1141          end if;
1142       end Check_Arg_Is_One_Of;
1143
1144       procedure Check_Arg_Is_One_Of
1145         (Arg        : Node_Id;
1146          N1, N2, N3 : Name_Id)
1147       is
1148          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1149
1150       begin
1151          Check_Arg_Is_Identifier (Argx);
1152
1153          if Chars (Argx) /= N1
1154            and then Chars (Argx) /= N2
1155            and then Chars (Argx) /= N3
1156          then
1157             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1158          end if;
1159       end Check_Arg_Is_One_Of;
1160
1161       procedure Check_Arg_Is_One_Of
1162         (Arg                : Node_Id;
1163          N1, N2, N3, N4, N5 : Name_Id)
1164       is
1165          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1166
1167       begin
1168          Check_Arg_Is_Identifier (Argx);
1169
1170          if Chars (Argx) /= N1
1171            and then Chars (Argx) /= N2
1172            and then Chars (Argx) /= N3
1173            and then Chars (Argx) /= N4
1174            and then Chars (Argx) /= N5
1175          then
1176             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1177          end if;
1178       end Check_Arg_Is_One_Of;
1179       ---------------------------------
1180       -- Check_Arg_Is_Queuing_Policy --
1181       ---------------------------------
1182
1183       procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id) is
1184          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1185
1186       begin
1187          Check_Arg_Is_Identifier (Argx);
1188
1189          if not Is_Queuing_Policy_Name (Chars (Argx)) then
1190             Error_Pragma_Arg ("& is not a valid queuing policy name", Argx);
1191          end if;
1192       end Check_Arg_Is_Queuing_Policy;
1193
1194       ------------------------------------
1195       -- Check_Arg_Is_Static_Expression --
1196       ------------------------------------
1197
1198       procedure Check_Arg_Is_Static_Expression
1199         (Arg : Node_Id;
1200          Typ : Entity_Id := Empty)
1201       is
1202          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1203
1204       begin
1205          if Present (Typ) then
1206             Analyze_And_Resolve (Argx, Typ);
1207          else
1208             Analyze_And_Resolve (Argx);
1209          end if;
1210
1211          if Is_OK_Static_Expression (Argx) then
1212             return;
1213
1214          elsif Etype (Argx) = Any_Type then
1215             raise Pragma_Exit;
1216
1217          --  An interesting special case, if we have a string literal and we
1218          --  are in Ada 83 mode, then we allow it even though it will not be
1219          --  flagged as static. This allows the use of Ada 95 pragmas like
1220          --  Import in Ada 83 mode. They will of course be flagged with
1221          --  warnings as usual, but will not cause errors.
1222
1223          elsif Ada_Version = Ada_83
1224            and then Nkind (Argx) = N_String_Literal
1225          then
1226             return;
1227
1228          --  Static expression that raises Constraint_Error. This has already
1229          --  been flagged, so just exit from pragma processing.
1230
1231          elsif Is_Static_Expression (Argx) then
1232             raise Pragma_Exit;
1233
1234          --  Finally, we have a real error
1235
1236          else
1237             Error_Msg_Name_1 := Pname;
1238
1239             declare
1240                Msg : String :=
1241                        "argument for pragma% must be a static expression!";
1242             begin
1243                Fix_Error (Msg);
1244                Flag_Non_Static_Expr (Msg, Argx);
1245             end;
1246
1247             raise Pragma_Exit;
1248          end if;
1249       end Check_Arg_Is_Static_Expression;
1250
1251       ------------------------------------------
1252       -- Check_Arg_Is_Task_Dispatching_Policy --
1253       ------------------------------------------
1254
1255       procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id) is
1256          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1257
1258       begin
1259          Check_Arg_Is_Identifier (Argx);
1260
1261          if not Is_Task_Dispatching_Policy_Name (Chars (Argx)) then
1262             Error_Pragma_Arg
1263               ("& is not a valid task dispatching policy name", Argx);
1264          end if;
1265       end Check_Arg_Is_Task_Dispatching_Policy;
1266
1267       ---------------------
1268       -- Check_Arg_Order --
1269       ---------------------
1270
1271       procedure Check_Arg_Order (Names : Name_List) is
1272          Arg : Node_Id;
1273
1274          Highest_So_Far : Natural := 0;
1275          --  Highest index in Names seen do far
1276
1277       begin
1278          Arg := Arg1;
1279          for J in 1 .. Arg_Count loop
1280             if Chars (Arg) /= No_Name then
1281                for K in Names'Range loop
1282                   if Chars (Arg) = Names (K) then
1283                      if K < Highest_So_Far then
1284                         Error_Msg_Name_1 := Pname;
1285                         Error_Msg_N
1286                           ("parameters out of order for pragma%", Arg);
1287                         Error_Msg_Name_1 := Names (K);
1288                         Error_Msg_Name_2 := Names (Highest_So_Far);
1289                         Error_Msg_N ("\% must appear before %", Arg);
1290                         raise Pragma_Exit;
1291
1292                      else
1293                         Highest_So_Far := K;
1294                      end if;
1295                   end if;
1296                end loop;
1297             end if;
1298
1299             Arg := Next (Arg);
1300          end loop;
1301       end Check_Arg_Order;
1302
1303       --------------------------------
1304       -- Check_At_Least_N_Arguments --
1305       --------------------------------
1306
1307       procedure Check_At_Least_N_Arguments (N : Nat) is
1308       begin
1309          if Arg_Count < N then
1310             Error_Pragma ("too few arguments for pragma%");
1311          end if;
1312       end Check_At_Least_N_Arguments;
1313
1314       -------------------------------
1315       -- Check_At_Most_N_Arguments --
1316       -------------------------------
1317
1318       procedure Check_At_Most_N_Arguments (N : Nat) is
1319          Arg : Node_Id;
1320       begin
1321          if Arg_Count > N then
1322             Arg := Arg1;
1323             for J in 1 .. N loop
1324                Next (Arg);
1325                Error_Pragma_Arg ("too many arguments for pragma%", Arg);
1326             end loop;
1327          end if;
1328       end Check_At_Most_N_Arguments;
1329
1330       ---------------------
1331       -- Check_Component --
1332       ---------------------
1333
1334       procedure Check_Component
1335         (Comp            : Node_Id;
1336          UU_Typ          : Entity_Id;
1337          In_Variant_Part : Boolean := False)
1338       is
1339          Comp_Id : constant Entity_Id := Defining_Identifier (Comp);
1340          Sindic  : constant Node_Id :=
1341                      Subtype_Indication (Component_Definition (Comp));
1342          Typ     : constant Entity_Id := Etype (Comp_Id);
1343
1344          function Inside_Generic_Body (Id : Entity_Id) return Boolean;
1345          --  Determine whether entity Id appears inside a generic body.
1346          --  Shouldn't this be in a more general place ???
1347
1348          -------------------------
1349          -- Inside_Generic_Body --
1350          -------------------------
1351
1352          function Inside_Generic_Body (Id : Entity_Id) return Boolean is
1353             S : Entity_Id;
1354
1355          begin
1356             S := Id;
1357             while Present (S) and then S /= Standard_Standard loop
1358                if Ekind (S) = E_Generic_Package
1359                  and then In_Package_Body (S)
1360                then
1361                   return True;
1362                end if;
1363
1364                S := Scope (S);
1365             end loop;
1366
1367             return False;
1368          end Inside_Generic_Body;
1369
1370       --  Start of processing for Check_Component
1371
1372       begin
1373          --  Ada 2005 (AI-216): If a component subtype is subject to a per-
1374          --  object constraint, then the component type shall be an Unchecked_
1375          --  Union.
1376
1377          if Nkind (Sindic) = N_Subtype_Indication
1378            and then Has_Per_Object_Constraint (Comp_Id)
1379            and then not Is_Unchecked_Union (Etype (Subtype_Mark (Sindic)))
1380          then
1381             Error_Msg_N
1382               ("component subtype subject to per-object constraint " &
1383                "must be an Unchecked_Union", Comp);
1384
1385          --  Ada 2012 (AI05-0026): For an unchecked union type declared within
1386          --  the body of a generic unit, or within the body of any of its
1387          --  descendant library units, no part of the type of a component
1388          --  declared in a variant_part of the unchecked union type shall be of
1389          --  a formal private type or formal private extension declared within
1390          --  the formal part of the generic unit.
1391
1392          elsif Ada_Version >= Ada_2012
1393            and then Inside_Generic_Body (UU_Typ)
1394            and then In_Variant_Part
1395            and then Is_Private_Type (Typ)
1396            and then Is_Generic_Type (Typ)
1397          then
1398             Error_Msg_N
1399               ("component of Unchecked_Union cannot be of generic type", Comp);
1400
1401          elsif Needs_Finalization (Typ) then
1402             Error_Msg_N
1403               ("component of Unchecked_Union cannot be controlled", Comp);
1404
1405          elsif Has_Task (Typ) then
1406             Error_Msg_N
1407               ("component of Unchecked_Union cannot have tasks", Comp);
1408          end if;
1409       end Check_Component;
1410
1411       ----------------------------
1412       -- Check_Duplicate_Pragma --
1413       ----------------------------
1414
1415       procedure Check_Duplicate_Pragma (E : Entity_Id) is
1416          P : Node_Id;
1417
1418       begin
1419          --  Nothing to do if this pragma comes from an aspect specification,
1420          --  since we could not be duplicating a pragma, and we dealt with the
1421          --  case of duplicated aspects in Analyze_Aspect_Specifications.
1422
1423          if From_Aspect_Specification (N) then
1424             return;
1425          end if;
1426
1427          --  Otherwise current pragma may duplicate previous pragma or a
1428          --  previously given aspect specification for the same pragma.
1429
1430          P := Get_Rep_Item_For_Entity (E, Pragma_Name (N));
1431
1432          if Present (P) then
1433             Error_Msg_Name_1 := Pragma_Name (N);
1434             Error_Msg_Sloc := Sloc (P);
1435
1436             if Nkind (P) = N_Aspect_Specification
1437               or else From_Aspect_Specification (P)
1438             then
1439                Error_Msg_NE ("aspect% for & previously given#", N, E);
1440             else
1441                Error_Msg_NE ("pragma% for & duplicates pragma#", N, E);
1442             end if;
1443
1444             raise Pragma_Exit;
1445          end if;
1446       end Check_Duplicate_Pragma;
1447
1448       ----------------------------------
1449       -- Check_Duplicated_Export_Name --
1450       ----------------------------------
1451
1452       procedure Check_Duplicated_Export_Name (Nam : Node_Id) is
1453          String_Val : constant String_Id := Strval (Nam);
1454
1455       begin
1456          --  We are only interested in the export case, and in the case of
1457          --  generics, it is the instance, not the template, that is the
1458          --  problem (the template will generate a warning in any case).
1459
1460          if not Inside_A_Generic
1461            and then (Prag_Id = Pragma_Export
1462                        or else
1463                      Prag_Id = Pragma_Export_Procedure
1464                        or else
1465                      Prag_Id = Pragma_Export_Valued_Procedure
1466                        or else
1467                      Prag_Id = Pragma_Export_Function)
1468          then
1469             for J in Externals.First .. Externals.Last loop
1470                if String_Equal (String_Val, Strval (Externals.Table (J))) then
1471                   Error_Msg_Sloc := Sloc (Externals.Table (J));
1472                   Error_Msg_N ("external name duplicates name given#", Nam);
1473                   exit;
1474                end if;
1475             end loop;
1476
1477             Externals.Append (Nam);
1478          end if;
1479       end Check_Duplicated_Export_Name;
1480
1481       -------------------------
1482       -- Check_First_Subtype --
1483       -------------------------
1484
1485       procedure Check_First_Subtype (Arg : Node_Id) is
1486          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1487          Ent  : constant Entity_Id := Entity (Argx);
1488
1489       begin
1490          if Is_First_Subtype (Ent) then
1491             null;
1492
1493          elsif Is_Type (Ent) then
1494             Error_Pragma_Arg
1495               ("pragma% cannot apply to subtype", Argx);
1496
1497          elsif Is_Object (Ent) then
1498             Error_Pragma_Arg
1499               ("pragma% cannot apply to object, requires a type", Argx);
1500
1501          else
1502             Error_Pragma_Arg
1503               ("pragma% cannot apply to&, requires a type", Argx);
1504          end if;
1505       end Check_First_Subtype;
1506
1507       ----------------------
1508       -- Check_Identifier --
1509       ----------------------
1510
1511       procedure Check_Identifier (Arg : Node_Id; Id : Name_Id) is
1512       begin
1513          if Present (Arg)
1514            and then Nkind (Arg) = N_Pragma_Argument_Association
1515          then
1516             if Chars (Arg) = No_Name or else Chars (Arg) /= Id then
1517                Error_Msg_Name_1 := Pname;
1518                Error_Msg_Name_2 := Id;
1519                Error_Msg_N ("pragma% argument expects identifier%", Arg);
1520                raise Pragma_Exit;
1521             end if;
1522          end if;
1523       end Check_Identifier;
1524
1525       --------------------------------
1526       -- Check_Identifier_Is_One_Of --
1527       --------------------------------
1528
1529       procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
1530       begin
1531          if Present (Arg)
1532            and then Nkind (Arg) = N_Pragma_Argument_Association
1533          then
1534             if Chars (Arg) = No_Name then
1535                Error_Msg_Name_1 := Pname;
1536                Error_Msg_N ("pragma% argument expects an identifier", Arg);
1537                raise Pragma_Exit;
1538
1539             elsif Chars (Arg) /= N1
1540               and then Chars (Arg) /= N2
1541             then
1542                Error_Msg_Name_1 := Pname;
1543                Error_Msg_N ("invalid identifier for pragma% argument", Arg);
1544                raise Pragma_Exit;
1545             end if;
1546          end if;
1547       end Check_Identifier_Is_One_Of;
1548
1549       ---------------------------
1550       -- Check_In_Main_Program --
1551       ---------------------------
1552
1553       procedure Check_In_Main_Program is
1554          P : constant Node_Id := Parent (N);
1555
1556       begin
1557          --  Must be at in subprogram body
1558
1559          if Nkind (P) /= N_Subprogram_Body then
1560             Error_Pragma ("% pragma allowed only in subprogram");
1561
1562          --  Otherwise warn if obviously not main program
1563
1564          elsif Present (Parameter_Specifications (Specification (P)))
1565            or else not Is_Compilation_Unit (Defining_Entity (P))
1566          then
1567             Error_Msg_Name_1 := Pname;
1568             Error_Msg_N
1569               ("?pragma% is only effective in main program", N);
1570          end if;
1571       end Check_In_Main_Program;
1572
1573       ---------------------------------------
1574       -- Check_Interrupt_Or_Attach_Handler --
1575       ---------------------------------------
1576
1577       procedure Check_Interrupt_Or_Attach_Handler is
1578          Arg1_X : constant Node_Id := Get_Pragma_Arg (Arg1);
1579          Handler_Proc, Proc_Scope : Entity_Id;
1580
1581       begin
1582          Analyze (Arg1_X);
1583
1584          if Prag_Id = Pragma_Interrupt_Handler then
1585             Check_Restriction (No_Dynamic_Attachment, N);
1586          end if;
1587
1588          Handler_Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
1589          Proc_Scope := Scope (Handler_Proc);
1590
1591          --  On AAMP only, a pragma Interrupt_Handler is supported for
1592          --  nonprotected parameterless procedures.
1593
1594          if not AAMP_On_Target
1595            or else Prag_Id = Pragma_Attach_Handler
1596          then
1597             if Ekind (Proc_Scope) /= E_Protected_Type then
1598                Error_Pragma_Arg
1599                  ("argument of pragma% must be protected procedure", Arg1);
1600             end if;
1601
1602             if Parent (N) /= Protected_Definition (Parent (Proc_Scope)) then
1603                Error_Pragma ("pragma% must be in protected definition");
1604             end if;
1605          end if;
1606
1607          if not Is_Library_Level_Entity (Proc_Scope)
1608            or else (AAMP_On_Target
1609                      and then not Is_Library_Level_Entity (Handler_Proc))
1610          then
1611             Error_Pragma_Arg
1612               ("argument for pragma% must be library level entity", Arg1);
1613          end if;
1614
1615          --  AI05-0033: A pragma cannot appear within a generic body, because
1616          --  instance can be in a nested scope. The check that protected type
1617          --  is itself a library-level declaration is done elsewhere.
1618
1619          --  Note: we omit this check in Codepeer mode to properly handle code
1620          --  prior to AI-0033 (pragmas don't matter to codepeer in any case).
1621
1622          if Inside_A_Generic then
1623             if Ekind (Scope (Current_Scope)) = E_Generic_Package
1624               and then In_Package_Body (Scope (Current_Scope))
1625               and then not CodePeer_Mode
1626             then
1627                Error_Pragma ("pragma% cannot be used inside a generic");
1628             end if;
1629          end if;
1630       end Check_Interrupt_Or_Attach_Handler;
1631
1632       -------------------------------------------
1633       -- Check_Is_In_Decl_Part_Or_Package_Spec --
1634       -------------------------------------------
1635
1636       procedure Check_Is_In_Decl_Part_Or_Package_Spec is
1637          P : Node_Id;
1638
1639       begin
1640          P := Parent (N);
1641          loop
1642             if No (P) then
1643                exit;
1644
1645             elsif Nkind (P) = N_Handled_Sequence_Of_Statements then
1646                exit;
1647
1648             elsif Nkind_In (P, N_Package_Specification,
1649                                N_Block_Statement)
1650             then
1651                return;
1652
1653             --  Note: the following tests seem a little peculiar, because
1654             --  they test for bodies, but if we were in the statement part
1655             --  of the body, we would already have hit the handled statement
1656             --  sequence, so the only way we get here is by being in the
1657             --  declarative part of the body.
1658
1659             elsif Nkind_In (P, N_Subprogram_Body,
1660                                N_Package_Body,
1661                                N_Task_Body,
1662                                N_Entry_Body)
1663             then
1664                return;
1665             end if;
1666
1667             P := Parent (P);
1668          end loop;
1669
1670          Error_Pragma ("pragma% is not in declarative part or package spec");
1671       end Check_Is_In_Decl_Part_Or_Package_Spec;
1672
1673       -------------------------
1674       -- Check_No_Identifier --
1675       -------------------------
1676
1677       procedure Check_No_Identifier (Arg : Node_Id) is
1678       begin
1679          if Nkind (Arg) = N_Pragma_Argument_Association
1680            and then Chars (Arg) /= No_Name
1681          then
1682             Error_Pragma_Arg_Ident
1683               ("pragma% does not permit identifier& here", Arg);
1684          end if;
1685       end Check_No_Identifier;
1686
1687       --------------------------
1688       -- Check_No_Identifiers --
1689       --------------------------
1690
1691       procedure Check_No_Identifiers is
1692          Arg_Node : Node_Id;
1693       begin
1694          if Arg_Count > 0 then
1695             Arg_Node := Arg1;
1696             while Present (Arg_Node) loop
1697                Check_No_Identifier (Arg_Node);
1698                Next (Arg_Node);
1699             end loop;
1700          end if;
1701       end Check_No_Identifiers;
1702
1703       ------------------------
1704       -- Check_No_Link_Name --
1705       ------------------------
1706
1707       procedure Check_No_Link_Name is
1708       begin
1709          if Present (Arg3)
1710            and then Chars (Arg3) = Name_Link_Name
1711          then
1712             Arg4 := Arg3;
1713          end if;
1714
1715          if Present (Arg4) then
1716             Error_Pragma_Arg
1717               ("Link_Name argument not allowed for Import Intrinsic", Arg4);
1718          end if;
1719       end Check_No_Link_Name;
1720
1721       -------------------------------
1722       -- Check_Optional_Identifier --
1723       -------------------------------
1724
1725       procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id) is
1726       begin
1727          if Present (Arg)
1728            and then Nkind (Arg) = N_Pragma_Argument_Association
1729            and then Chars (Arg) /= No_Name
1730          then
1731             if Chars (Arg) /= Id then
1732                Error_Msg_Name_1 := Pname;
1733                Error_Msg_Name_2 := Id;
1734                Error_Msg_N ("pragma% argument expects identifier%", Arg);
1735                raise Pragma_Exit;
1736             end if;
1737          end if;
1738       end Check_Optional_Identifier;
1739
1740       procedure Check_Optional_Identifier (Arg : Node_Id; Id : String) is
1741       begin
1742          Name_Buffer (1 .. Id'Length) := Id;
1743          Name_Len := Id'Length;
1744          Check_Optional_Identifier (Arg, Name_Find);
1745       end Check_Optional_Identifier;
1746
1747       --------------------------------------
1748       -- Check_Precondition_Postcondition --
1749       --------------------------------------
1750
1751       procedure Check_Precondition_Postcondition (In_Body : out Boolean) is
1752          P  : Node_Id;
1753          PO : Node_Id;
1754
1755          procedure Chain_PPC (PO : Node_Id);
1756          --  If PO is an entry or a [generic] subprogram declaration node, then
1757          --  the precondition/postcondition applies to this subprogram and the
1758          --  processing for the pragma is completed. Otherwise the pragma is
1759          --  misplaced.
1760
1761          ---------------
1762          -- Chain_PPC --
1763          ---------------
1764
1765          procedure Chain_PPC (PO : Node_Id) is
1766             S   : Entity_Id;
1767             P   : Node_Id;
1768
1769          begin
1770             if Nkind (PO) = N_Abstract_Subprogram_Declaration then
1771                if not From_Aspect_Specification (N) then
1772                   Error_Pragma
1773                     ("pragma% cannot be applied to abstract subprogram");
1774
1775                elsif Class_Present (N) then
1776                   null;
1777
1778                else
1779                   Error_Pragma
1780                     ("aspect % requires ''Class for abstract subprogram");
1781                end if;
1782
1783             --  AI05-0230: The same restriction applies to null procedures. For
1784             --  compatibility with earlier uses of the Ada pragma, apply this
1785             --  rule only to aspect specifications.
1786
1787             --  The above discrpency needs documentation. Robert is dubious
1788             --  about whether it is a good idea ???
1789
1790             elsif Nkind (PO) = N_Subprogram_Declaration
1791               and then Nkind (Specification (PO)) = N_Procedure_Specification
1792               and then Null_Present (Specification (PO))
1793               and then From_Aspect_Specification (N)
1794               and then not Class_Present (N)
1795             then
1796                Error_Pragma
1797                  ("aspect % requires ''Class for null procedure");
1798
1799             elsif not Nkind_In (PO, N_Subprogram_Declaration,
1800                                     N_Generic_Subprogram_Declaration,
1801                                     N_Entry_Declaration)
1802             then
1803                Pragma_Misplaced;
1804             end if;
1805
1806             --  Here if we have [generic] subprogram or entry declaration
1807
1808             if Nkind (PO) = N_Entry_Declaration then
1809                S := Defining_Entity (PO);
1810             else
1811                S := Defining_Unit_Name (Specification (PO));
1812             end if;
1813
1814             --  Make sure we do not have the case of a precondition pragma when
1815             --  the Pre'Class aspect is present.
1816
1817             --  We do this by looking at pragmas already chained to the entity
1818             --  since the aspect derived pragma will be put on this list first.
1819
1820             if Pragma_Name (N) = Name_Precondition then
1821                if not From_Aspect_Specification (N) then
1822                   P := Spec_PPC_List (Contract (S));
1823                   while Present (P) loop
1824                      if Pragma_Name (P) = Name_Precondition
1825                        and then From_Aspect_Specification (P)
1826                        and then Class_Present (P)
1827                      then
1828                         Error_Msg_Sloc := Sloc (P);
1829                         Error_Pragma
1830                           ("pragma% not allowed, `Pre''Class` aspect given#");
1831                      end if;
1832
1833                      P := Next_Pragma (P);
1834                   end loop;
1835                end if;
1836             end if;
1837
1838             --  Similarly check for Pre with inherited Pre'Class. Note that
1839             --  we cover the aspect case as well here.
1840
1841             if Pragma_Name (N) = Name_Precondition
1842               and then not Class_Present (N)
1843             then
1844                declare
1845                   Inherited : constant Subprogram_List :=
1846                                 Inherited_Subprograms (S);
1847                   P         : Node_Id;
1848
1849                begin
1850                   for J in Inherited'Range loop
1851                      P := Spec_PPC_List (Contract (Inherited (J)));
1852                      while Present (P) loop
1853                         if Pragma_Name (P) = Name_Precondition
1854                           and then Class_Present (P)
1855                         then
1856                            Error_Msg_Sloc := Sloc (P);
1857                            Error_Pragma
1858                              ("pragma% not allowed, `Pre''Class` "
1859                               & "aspect inherited from#");
1860                         end if;
1861
1862                         P := Next_Pragma (P);
1863                      end loop;
1864                   end loop;
1865                end;
1866             end if;
1867
1868             --  Note: we do not analyze the pragma at this point. Instead we
1869             --  delay this analysis until the end of the declarative part in
1870             --  which the pragma appears. This implements the required delay
1871             --  in this analysis, allowing forward references. The analysis
1872             --  happens at the end of Analyze_Declarations.
1873
1874             --  Chain spec PPC pragma to list for subprogram
1875
1876             Set_Next_Pragma (N, Spec_PPC_List (Contract (S)));
1877             Set_Spec_PPC_List (Contract (S), N);
1878
1879             --  Return indicating spec case
1880
1881             In_Body := False;
1882             return;
1883          end Chain_PPC;
1884
1885       --  Start of processing for Check_Precondition_Postcondition
1886
1887       begin
1888          if not Is_List_Member (N) then
1889             Pragma_Misplaced;
1890          end if;
1891
1892          --  Preanalyze message argument if present. Visibility in this
1893          --  argument is established at the point of pragma occurrence.
1894
1895          if Arg_Count = 2 then
1896             Check_Optional_Identifier (Arg2, Name_Message);
1897             Preanalyze_Spec_Expression
1898               (Get_Pragma_Arg (Arg2), Standard_String);
1899          end if;
1900
1901          --  Record if pragma is disabled
1902
1903          if Check_Enabled (Pname) then
1904             Set_SCO_Pragma_Enabled (Loc);
1905          end if;
1906
1907          --  If we are within an inlined body, the legality of the pragma
1908          --  has been checked already.
1909
1910          if In_Inlined_Body then
1911             In_Body := True;
1912             return;
1913          end if;
1914
1915          --  Search prior declarations
1916
1917          P := N;
1918          while Present (Prev (P)) loop
1919             P := Prev (P);
1920
1921             --  If the previous node is a generic subprogram, do not go to to
1922             --  the original node, which is the unanalyzed tree: we need to
1923             --  attach the pre/postconditions to the analyzed version at this
1924             --  point. They get propagated to the original tree when analyzing
1925             --  the corresponding body.
1926
1927             if Nkind (P) not in N_Generic_Declaration then
1928                PO := Original_Node (P);
1929             else
1930                PO := P;
1931             end if;
1932
1933             --  Skip past prior pragma
1934
1935             if Nkind (PO) = N_Pragma then
1936                null;
1937
1938             --  Skip stuff not coming from source
1939
1940             elsif not Comes_From_Source (PO) then
1941
1942                --  The condition may apply to a subprogram instantiation
1943
1944                if Nkind (PO) = N_Subprogram_Declaration
1945                  and then Present (Generic_Parent (Specification (PO)))
1946                then
1947                   Chain_PPC (PO);
1948                   return;
1949
1950                elsif Nkind (PO) = N_Subprogram_Declaration
1951                  and then In_Instance
1952                then
1953                   Chain_PPC (PO);
1954                   return;
1955
1956                --  For all other cases of non source code, do nothing
1957
1958                else
1959                   null;
1960                end if;
1961
1962             --  Only remaining possibility is subprogram declaration
1963
1964             else
1965                Chain_PPC (PO);
1966                return;
1967             end if;
1968          end loop;
1969
1970          --  If we fall through loop, pragma is at start of list, so see if it
1971          --  is at the start of declarations of a subprogram body.
1972
1973          if Nkind (Parent (N)) = N_Subprogram_Body
1974            and then List_Containing (N) = Declarations (Parent (N))
1975          then
1976             if Operating_Mode /= Generate_Code
1977               or else Inside_A_Generic
1978             then
1979                --  Analyze pragma expression for correctness and for ASIS use
1980
1981                Preanalyze_Spec_Expression
1982                  (Get_Pragma_Arg (Arg1), Standard_Boolean);
1983             end if;
1984
1985             In_Body := True;
1986             return;
1987
1988          --  See if it is in the pragmas after a library level subprogram
1989
1990          elsif Nkind (Parent (N)) = N_Compilation_Unit_Aux then
1991
1992             --  In formal verification mode, analyze pragma expression for
1993             --  correctness, as it is not expanded later.
1994
1995             if Alfa_Mode then
1996                Analyze_PPC_In_Decl_Part
1997                  (N, Defining_Entity (Unit (Parent (Parent (N)))));
1998             end if;
1999
2000             Chain_PPC (Unit (Parent (Parent (N))));
2001             return;
2002          end if;
2003
2004          --  If we fall through, pragma was misplaced
2005
2006          Pragma_Misplaced;
2007       end Check_Precondition_Postcondition;
2008
2009       -----------------------------
2010       -- Check_Static_Constraint --
2011       -----------------------------
2012
2013       --  Note: for convenience in writing this procedure, in addition to
2014       --  the officially (i.e. by spec) allowed argument which is always a
2015       --  constraint, it also allows ranges and discriminant associations.
2016       --  Above is not clear ???
2017
2018       procedure Check_Static_Constraint (Constr : Node_Id) is
2019
2020          procedure Require_Static (E : Node_Id);
2021          --  Require given expression to be static expression
2022
2023          --------------------
2024          -- Require_Static --
2025          --------------------
2026
2027          procedure Require_Static (E : Node_Id) is
2028          begin
2029             if not Is_OK_Static_Expression (E) then
2030                Flag_Non_Static_Expr
2031                  ("non-static constraint not allowed in Unchecked_Union!", E);
2032                raise Pragma_Exit;
2033             end if;
2034          end Require_Static;
2035
2036       --  Start of processing for Check_Static_Constraint
2037
2038       begin
2039          case Nkind (Constr) is
2040             when N_Discriminant_Association =>
2041                Require_Static (Expression (Constr));
2042
2043             when N_Range =>
2044                Require_Static (Low_Bound (Constr));
2045                Require_Static (High_Bound (Constr));
2046
2047             when N_Attribute_Reference =>
2048                Require_Static (Type_Low_Bound  (Etype (Prefix (Constr))));
2049                Require_Static (Type_High_Bound (Etype (Prefix (Constr))));
2050
2051             when N_Range_Constraint =>
2052                Check_Static_Constraint (Range_Expression (Constr));
2053
2054             when N_Index_Or_Discriminant_Constraint =>
2055                declare
2056                   IDC : Entity_Id;
2057                begin
2058                   IDC := First (Constraints (Constr));
2059                   while Present (IDC) loop
2060                      Check_Static_Constraint (IDC);
2061                      Next (IDC);
2062                   end loop;
2063                end;
2064
2065             when others =>
2066                null;
2067          end case;
2068       end Check_Static_Constraint;
2069
2070       ---------------------
2071       -- Check_Test_Case --
2072       ---------------------
2073
2074       procedure Check_Test_Case is
2075          P  : Node_Id;
2076          PO : Node_Id;
2077
2078          procedure Chain_TC (PO : Node_Id);
2079          --  If PO is a [generic] subprogram declaration node, then the
2080          --  test-case applies to this subprogram and the processing for the
2081          --  pragma is completed. Otherwise the pragma is misplaced.
2082
2083          --------------
2084          -- Chain_TC --
2085          --------------
2086
2087          procedure Chain_TC (PO : Node_Id) is
2088             S   : Entity_Id;
2089
2090          begin
2091             if Nkind (PO) = N_Abstract_Subprogram_Declaration then
2092                if From_Aspect_Specification (N) then
2093                   Error_Pragma
2094                     ("aspect% cannot be applied to abstract subprogram");
2095                else
2096                   Error_Pragma
2097                     ("pragma% cannot be applied to abstract subprogram");
2098                end if;
2099
2100             elsif Nkind (PO) = N_Entry_Declaration then
2101                if From_Aspect_Specification (N) then
2102                   Error_Pragma ("aspect% cannot be applied to entry");
2103                else
2104                   Error_Pragma ("pragma% cannot be applied to entry");
2105                end if;
2106
2107             elsif not Nkind_In (PO, N_Subprogram_Declaration,
2108                                     N_Generic_Subprogram_Declaration)
2109             then
2110                Pragma_Misplaced;
2111             end if;
2112
2113             --  Here if we have [generic] subprogram declaration
2114
2115             S := Defining_Unit_Name (Specification (PO));
2116
2117             --  Note: we do not analyze the pragma at this point. Instead we
2118             --  delay this analysis until the end of the declarative part in
2119             --  which the pragma appears. This implements the required delay
2120             --  in this analysis, allowing forward references. The analysis
2121             --  happens at the end of Analyze_Declarations.
2122
2123             --  There should not be another test case with the same name
2124             --  associated to this subprogram.
2125
2126             declare
2127                Name : constant String_Id := Get_Name_From_Test_Case_Pragma (N);
2128                TC   : Node_Id;
2129
2130             begin
2131                TC := Spec_TC_List (Contract (S));
2132                while Present (TC) loop
2133
2134                   if String_Equal
2135                     (Name, Get_Name_From_Test_Case_Pragma (TC))
2136                   then
2137                      Error_Msg_Sloc := Sloc (TC);
2138
2139                      if From_Aspect_Specification (N) then
2140                         Error_Pragma ("name for aspect% is already used#");
2141                      else
2142                         Error_Pragma ("name for pragma% is already used#");
2143                      end if;
2144                   end if;
2145
2146                   TC := Next_Pragma (TC);
2147                end loop;
2148             end;
2149
2150             --  Chain spec TC pragma to list for subprogram
2151
2152             Set_Next_Pragma (N, Spec_TC_List (Contract (S)));
2153             Set_Spec_TC_List (Contract (S), N);
2154          end Chain_TC;
2155
2156       --  Start of processing for Check_Test_Case
2157
2158       begin
2159          if not Is_List_Member (N) then
2160             Pragma_Misplaced;
2161          end if;
2162
2163          --  Test cases should only appear in package spec unit
2164
2165          if Get_Source_Unit (N) = No_Unit
2166            or else not Nkind_In (Sinfo.Unit (Cunit (Get_Source_Unit (N))),
2167                                  N_Package_Declaration,
2168                                  N_Generic_Package_Declaration)
2169          then
2170             Pragma_Misplaced;
2171          end if;
2172
2173          --  Search prior declarations
2174
2175          P := N;
2176          while Present (Prev (P)) loop
2177             P := Prev (P);
2178
2179             --  If the previous node is a generic subprogram, do not go to to
2180             --  the original node, which is the unanalyzed tree: we need to
2181             --  attach the test-case to the analyzed version at this point.
2182             --  They get propagated to the original tree when analyzing the
2183             --  corresponding body.
2184
2185             if Nkind (P) not in N_Generic_Declaration then
2186                PO := Original_Node (P);
2187             else
2188                PO := P;
2189             end if;
2190
2191             --  Skip past prior pragma
2192
2193             if Nkind (PO) = N_Pragma then
2194                null;
2195
2196             --  Skip stuff not coming from source
2197
2198             elsif not Comes_From_Source (PO) then
2199                null;
2200
2201             --  Only remaining possibility is subprogram declaration. First
2202             --  check that it is declared directly in a package declaration.
2203             --  This may be either the package declaration for the current unit
2204             --  being defined or a local package declaration.
2205
2206             elsif not Present (Parent (Parent (PO)))
2207               or else not Present (Parent (Parent (Parent (PO))))
2208               or else not Nkind_In (Parent (Parent (PO)),
2209                                     N_Package_Declaration,
2210                                     N_Generic_Package_Declaration)
2211             then
2212                Pragma_Misplaced;
2213
2214             else
2215                Chain_TC (PO);
2216                return;
2217             end if;
2218          end loop;
2219
2220          --  If we fall through, pragma was misplaced
2221
2222          Pragma_Misplaced;
2223       end Check_Test_Case;
2224
2225       --------------------------------------
2226       -- Check_Valid_Configuration_Pragma --
2227       --------------------------------------
2228
2229       --  A configuration pragma must appear in the context clause of a
2230       --  compilation unit, and only other pragmas may precede it. Note that
2231       --  the test also allows use in a configuration pragma file.
2232
2233       procedure Check_Valid_Configuration_Pragma is
2234       begin
2235          if not Is_Configuration_Pragma then
2236             Error_Pragma ("incorrect placement for configuration pragma%");
2237          end if;
2238       end Check_Valid_Configuration_Pragma;
2239
2240       -------------------------------------
2241       -- Check_Valid_Library_Unit_Pragma --
2242       -------------------------------------
2243
2244       procedure Check_Valid_Library_Unit_Pragma is
2245          Plist       : List_Id;
2246          Parent_Node : Node_Id;
2247          Unit_Name   : Entity_Id;
2248          Unit_Kind   : Node_Kind;
2249          Unit_Node   : Node_Id;
2250          Sindex      : Source_File_Index;
2251
2252       begin
2253          if not Is_List_Member (N) then
2254             Pragma_Misplaced;
2255
2256          else
2257             Plist := List_Containing (N);
2258             Parent_Node := Parent (Plist);
2259
2260             if Parent_Node = Empty then
2261                Pragma_Misplaced;
2262
2263             --  Case of pragma appearing after a compilation unit. In this case
2264             --  it must have an argument with the corresponding name and must
2265             --  be part of the following pragmas of its parent.
2266
2267             elsif Nkind (Parent_Node) = N_Compilation_Unit_Aux then
2268                if Plist /= Pragmas_After (Parent_Node) then
2269                   Pragma_Misplaced;
2270
2271                elsif Arg_Count = 0 then
2272                   Error_Pragma
2273                     ("argument required if outside compilation unit");
2274
2275                else
2276                   Check_No_Identifiers;
2277                   Check_Arg_Count (1);
2278                   Unit_Node := Unit (Parent (Parent_Node));
2279                   Unit_Kind := Nkind (Unit_Node);
2280
2281                   Analyze (Get_Pragma_Arg (Arg1));
2282
2283                   if Unit_Kind = N_Generic_Subprogram_Declaration
2284                     or else Unit_Kind = N_Subprogram_Declaration
2285                   then
2286                      Unit_Name := Defining_Entity (Unit_Node);
2287
2288                   elsif Unit_Kind in N_Generic_Instantiation then
2289                      Unit_Name := Defining_Entity (Unit_Node);
2290
2291                   else
2292                      Unit_Name := Cunit_Entity (Current_Sem_Unit);
2293                   end if;
2294
2295                   if Chars (Unit_Name) /=
2296                      Chars (Entity (Get_Pragma_Arg (Arg1)))
2297                   then
2298                      Error_Pragma_Arg
2299                        ("pragma% argument is not current unit name", Arg1);
2300                   end if;
2301
2302                   if Ekind (Unit_Name) = E_Package
2303                     and then Present (Renamed_Entity (Unit_Name))
2304                   then
2305                      Error_Pragma ("pragma% not allowed for renamed package");
2306                   end if;
2307                end if;
2308
2309             --  Pragma appears other than after a compilation unit
2310
2311             else
2312                --  Here we check for the generic instantiation case and also
2313                --  for the case of processing a generic formal package. We
2314                --  detect these cases by noting that the Sloc on the node
2315                --  does not belong to the current compilation unit.
2316
2317                Sindex := Source_Index (Current_Sem_Unit);
2318
2319                if Loc not in Source_First (Sindex) .. Source_Last (Sindex) then
2320                   Rewrite (N, Make_Null_Statement (Loc));
2321                   return;
2322
2323                --  If before first declaration, the pragma applies to the
2324                --  enclosing unit, and the name if present must be this name.
2325
2326                elsif Is_Before_First_Decl (N, Plist) then
2327                   Unit_Node := Unit_Declaration_Node (Current_Scope);
2328                   Unit_Kind := Nkind (Unit_Node);
2329
2330                   if Nkind (Parent (Unit_Node)) /= N_Compilation_Unit then
2331                      Pragma_Misplaced;
2332
2333                   elsif Unit_Kind = N_Subprogram_Body
2334                     and then not Acts_As_Spec (Unit_Node)
2335                   then
2336                      Pragma_Misplaced;
2337
2338                   elsif Nkind (Parent_Node) = N_Package_Body then
2339                      Pragma_Misplaced;
2340
2341                   elsif Nkind (Parent_Node) = N_Package_Specification
2342                     and then Plist = Private_Declarations (Parent_Node)
2343                   then
2344                      Pragma_Misplaced;
2345
2346                   elsif (Nkind (Parent_Node) = N_Generic_Package_Declaration
2347                            or else Nkind (Parent_Node) =
2348                                              N_Generic_Subprogram_Declaration)
2349                     and then Plist = Generic_Formal_Declarations (Parent_Node)
2350                   then
2351                      Pragma_Misplaced;
2352
2353                   elsif Arg_Count > 0 then
2354                      Analyze (Get_Pragma_Arg (Arg1));
2355
2356                      if Entity (Get_Pragma_Arg (Arg1)) /= Current_Scope then
2357                         Error_Pragma_Arg
2358                           ("name in pragma% must be enclosing unit", Arg1);
2359                      end if;
2360
2361                   --  It is legal to have no argument in this context
2362
2363                   else
2364                      return;
2365                   end if;
2366
2367                --  Error if not before first declaration. This is because a
2368                --  library unit pragma argument must be the name of a library
2369                --  unit (RM 10.1.5(7)), but the only names permitted in this
2370                --  context are (RM 10.1.5(6)) names of subprogram declarations,
2371                --  generic subprogram declarations or generic instantiations.
2372
2373                else
2374                   Error_Pragma
2375                     ("pragma% misplaced, must be before first declaration");
2376                end if;
2377             end if;
2378          end if;
2379       end Check_Valid_Library_Unit_Pragma;
2380
2381       -------------------
2382       -- Check_Variant --
2383       -------------------
2384
2385       procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id) is
2386          Clist : constant Node_Id := Component_List (Variant);
2387          Comp  : Node_Id;
2388
2389       begin
2390          if not Is_Non_Empty_List (Component_Items (Clist)) then
2391             Error_Msg_N
2392               ("Unchecked_Union may not have empty component list",
2393                Variant);
2394             return;
2395          end if;
2396
2397          Comp := First (Component_Items (Clist));
2398          while Present (Comp) loop
2399             Check_Component (Comp, UU_Typ, In_Variant_Part => True);
2400             Next (Comp);
2401          end loop;
2402       end Check_Variant;
2403
2404       ------------------
2405       -- Error_Pragma --
2406       ------------------
2407
2408       procedure Error_Pragma (Msg : String) is
2409          MsgF : String := Msg;
2410       begin
2411          Error_Msg_Name_1 := Pname;
2412          Fix_Error (MsgF);
2413          Error_Msg_N (MsgF, N);
2414          raise Pragma_Exit;
2415       end Error_Pragma;
2416
2417       ----------------------
2418       -- Error_Pragma_Arg --
2419       ----------------------
2420
2421       procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id) is
2422          MsgF : String := Msg;
2423       begin
2424          Error_Msg_Name_1 := Pname;
2425          Fix_Error (MsgF);
2426          Error_Msg_N (MsgF, Get_Pragma_Arg (Arg));
2427          raise Pragma_Exit;
2428       end Error_Pragma_Arg;
2429
2430       procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id) is
2431          MsgF : String := Msg1;
2432       begin
2433          Error_Msg_Name_1 := Pname;
2434          Fix_Error (MsgF);
2435          Error_Msg_N (MsgF, Get_Pragma_Arg (Arg));
2436          Error_Pragma_Arg (Msg2, Arg);
2437       end Error_Pragma_Arg;
2438
2439       ----------------------------
2440       -- Error_Pragma_Arg_Ident --
2441       ----------------------------
2442
2443       procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id) is
2444          MsgF : String := Msg;
2445       begin
2446          Error_Msg_Name_1 := Pname;
2447          Fix_Error (MsgF);
2448          Error_Msg_N (MsgF, Arg);
2449          raise Pragma_Exit;
2450       end Error_Pragma_Arg_Ident;
2451
2452       ----------------------
2453       -- Error_Pragma_Ref --
2454       ----------------------
2455
2456       procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id) is
2457          MsgF : String := Msg;
2458       begin
2459          Error_Msg_Name_1 := Pname;
2460          Fix_Error (MsgF);
2461          Error_Msg_Sloc   := Sloc (Ref);
2462          Error_Msg_NE (MsgF, N, Ref);
2463          raise Pragma_Exit;
2464       end Error_Pragma_Ref;
2465
2466       ------------------------
2467       -- Find_Lib_Unit_Name --
2468       ------------------------
2469
2470       function Find_Lib_Unit_Name return Entity_Id is
2471       begin
2472          --  Return inner compilation unit entity, for case of nested
2473          --  categorization pragmas. This happens in generic unit.
2474
2475          if Nkind (Parent (N)) = N_Package_Specification
2476            and then Defining_Entity (Parent (N)) /= Current_Scope
2477          then
2478             return Defining_Entity (Parent (N));
2479          else
2480             return Current_Scope;
2481          end if;
2482       end Find_Lib_Unit_Name;
2483
2484       ----------------------------
2485       -- Find_Program_Unit_Name --
2486       ----------------------------
2487
2488       procedure Find_Program_Unit_Name (Id : Node_Id) is
2489          Unit_Name : Entity_Id;
2490          Unit_Kind : Node_Kind;
2491          P         : constant Node_Id := Parent (N);
2492
2493       begin
2494          if Nkind (P) = N_Compilation_Unit then
2495             Unit_Kind := Nkind (Unit (P));
2496
2497             if Unit_Kind = N_Subprogram_Declaration
2498               or else Unit_Kind = N_Package_Declaration
2499               or else Unit_Kind in N_Generic_Declaration
2500             then
2501                Unit_Name := Defining_Entity (Unit (P));
2502
2503                if Chars (Id) = Chars (Unit_Name) then
2504                   Set_Entity (Id, Unit_Name);
2505                   Set_Etype (Id, Etype (Unit_Name));
2506                else
2507                   Set_Etype (Id, Any_Type);
2508                   Error_Pragma
2509                     ("cannot find program unit referenced by pragma%");
2510                end if;
2511
2512             else
2513                Set_Etype (Id, Any_Type);
2514                Error_Pragma ("pragma% inapplicable to this unit");
2515             end if;
2516
2517          else
2518             Analyze (Id);
2519          end if;
2520       end Find_Program_Unit_Name;
2521
2522       -----------------------------------------
2523       -- Find_Unique_Parameterless_Procedure --
2524       -----------------------------------------
2525
2526       function Find_Unique_Parameterless_Procedure
2527         (Name : Entity_Id;
2528          Arg  : Node_Id) return Entity_Id
2529       is
2530          Proc : Entity_Id := Empty;
2531
2532       begin
2533          --  The body of this procedure needs some comments ???
2534
2535          if not Is_Entity_Name (Name) then
2536             Error_Pragma_Arg
2537               ("argument of pragma% must be entity name", Arg);
2538
2539          elsif not Is_Overloaded (Name) then
2540             Proc := Entity (Name);
2541
2542             if Ekind (Proc) /= E_Procedure
2543               or else Present (First_Formal (Proc))
2544             then
2545                Error_Pragma_Arg
2546                  ("argument of pragma% must be parameterless procedure", Arg);
2547             end if;
2548
2549          else
2550             declare
2551                Found : Boolean := False;
2552                It    : Interp;
2553                Index : Interp_Index;
2554
2555             begin
2556                Get_First_Interp (Name, Index, It);
2557                while Present (It.Nam) loop
2558                   Proc := It.Nam;
2559
2560                   if Ekind (Proc) = E_Procedure
2561                     and then No (First_Formal (Proc))
2562                   then
2563                      if not Found then
2564                         Found := True;
2565                         Set_Entity (Name, Proc);
2566                         Set_Is_Overloaded (Name, False);
2567                      else
2568                         Error_Pragma_Arg
2569                           ("ambiguous handler name for pragma% ", Arg);
2570                      end if;
2571                   end if;
2572
2573                   Get_Next_Interp (Index, It);
2574                end loop;
2575
2576                if not Found then
2577                   Error_Pragma_Arg
2578                     ("argument of pragma% must be parameterless procedure",
2579                      Arg);
2580                else
2581                   Proc := Entity (Name);
2582                end if;
2583             end;
2584          end if;
2585
2586          return Proc;
2587       end Find_Unique_Parameterless_Procedure;
2588
2589       ---------------
2590       -- Fix_Error --
2591       ---------------
2592
2593       procedure Fix_Error (Msg : in out String) is
2594       begin
2595          if From_Aspect_Specification (N) then
2596             for J in Msg'First .. Msg'Last - 5 loop
2597                if Msg (J .. J + 5) = "pragma" then
2598                   Msg (J .. J + 5) := "aspect";
2599                end if;
2600             end loop;
2601
2602             if Error_Msg_Name_1 = Name_Precondition then
2603                Error_Msg_Name_1 := Name_Pre;
2604             elsif Error_Msg_Name_1 = Name_Postcondition then
2605                Error_Msg_Name_1 := Name_Post;
2606             end if;
2607          end if;
2608       end Fix_Error;
2609
2610       -------------------------
2611       -- Gather_Associations --
2612       -------------------------
2613
2614       procedure Gather_Associations
2615         (Names : Name_List;
2616          Args  : out Args_List)
2617       is
2618          Arg : Node_Id;
2619
2620       begin
2621          --  Initialize all parameters to Empty
2622
2623          for J in Args'Range loop
2624             Args (J) := Empty;
2625          end loop;
2626
2627          --  That's all we have to do if there are no argument associations
2628
2629          if No (Pragma_Argument_Associations (N)) then
2630             return;
2631          end if;
2632
2633          --  Otherwise first deal with any positional parameters present
2634
2635          Arg := First (Pragma_Argument_Associations (N));
2636          for Index in Args'Range loop
2637             exit when No (Arg) or else Chars (Arg) /= No_Name;
2638             Args (Index) := Get_Pragma_Arg (Arg);
2639             Next (Arg);
2640          end loop;
2641
2642          --  Positional parameters all processed, if any left, then we
2643          --  have too many positional parameters.
2644
2645          if Present (Arg) and then Chars (Arg) = No_Name then
2646             Error_Pragma_Arg
2647               ("too many positional associations for pragma%", Arg);
2648          end if;
2649
2650          --  Process named parameters if any are present
2651
2652          while Present (Arg) loop
2653             if Chars (Arg) = No_Name then
2654                Error_Pragma_Arg
2655                  ("positional association cannot follow named association",
2656                   Arg);
2657
2658             else
2659                for Index in Names'Range loop
2660                   if Names (Index) = Chars (Arg) then
2661                      if Present (Args (Index)) then
2662                         Error_Pragma_Arg
2663                           ("duplicate argument association for pragma%", Arg);
2664                      else
2665                         Args (Index) := Get_Pragma_Arg (Arg);
2666                         exit;
2667                      end if;
2668                   end if;
2669
2670                   if Index = Names'Last then
2671                      Error_Msg_Name_1 := Pname;
2672                      Error_Msg_N ("pragma% does not allow & argument", Arg);
2673
2674                      --  Check for possible misspelling
2675
2676                      for Index1 in Names'Range loop
2677                         if Is_Bad_Spelling_Of
2678                              (Chars (Arg), Names (Index1))
2679                         then
2680                            Error_Msg_Name_1 := Names (Index1);
2681                            Error_Msg_N -- CODEFIX
2682                              ("\possible misspelling of%", Arg);
2683                            exit;
2684                         end if;
2685                      end loop;
2686
2687                      raise Pragma_Exit;
2688                   end if;
2689                end loop;
2690             end if;
2691
2692             Next (Arg);
2693          end loop;
2694       end Gather_Associations;
2695
2696       -----------------
2697       -- GNAT_Pragma --
2698       -----------------
2699
2700       procedure GNAT_Pragma is
2701       begin
2702          Check_Restriction (No_Implementation_Pragmas, N);
2703       end GNAT_Pragma;
2704
2705       --------------------------
2706       -- Is_Before_First_Decl --
2707       --------------------------
2708
2709       function Is_Before_First_Decl
2710         (Pragma_Node : Node_Id;
2711          Decls       : List_Id) return Boolean
2712       is
2713          Item : Node_Id := First (Decls);
2714
2715       begin
2716          --  Only other pragmas can come before this pragma
2717
2718          loop
2719             if No (Item) or else Nkind (Item) /= N_Pragma then
2720                return False;
2721
2722             elsif Item = Pragma_Node then
2723                return True;
2724             end if;
2725
2726             Next (Item);
2727          end loop;
2728       end Is_Before_First_Decl;
2729
2730       -----------------------------
2731       -- Is_Configuration_Pragma --
2732       -----------------------------
2733
2734       --  A configuration pragma must appear in the context clause of a
2735       --  compilation unit, and only other pragmas may precede it. Note that
2736       --  the test below also permits use in a configuration pragma file.
2737
2738       function Is_Configuration_Pragma return Boolean is
2739          Lis : constant List_Id := List_Containing (N);
2740          Par : constant Node_Id := Parent (N);
2741          Prg : Node_Id;
2742
2743       begin
2744          --  If no parent, then we are in the configuration pragma file,
2745          --  so the placement is definitely appropriate.
2746
2747          if No (Par) then
2748             return True;
2749
2750          --  Otherwise we must be in the context clause of a compilation unit
2751          --  and the only thing allowed before us in the context list is more
2752          --  configuration pragmas.
2753
2754          elsif Nkind (Par) = N_Compilation_Unit
2755            and then Context_Items (Par) = Lis
2756          then
2757             Prg := First (Lis);
2758
2759             loop
2760                if Prg = N then
2761                   return True;
2762                elsif Nkind (Prg) /= N_Pragma then
2763                   return False;
2764                end if;
2765
2766                Next (Prg);
2767             end loop;
2768
2769          else
2770             return False;
2771          end if;
2772       end Is_Configuration_Pragma;
2773
2774       --------------------------
2775       -- Is_In_Context_Clause --
2776       --------------------------
2777
2778       function Is_In_Context_Clause return Boolean is
2779          Plist       : List_Id;
2780          Parent_Node : Node_Id;
2781
2782       begin
2783          if not Is_List_Member (N) then
2784             return False;
2785
2786          else
2787             Plist := List_Containing (N);
2788             Parent_Node := Parent (Plist);
2789
2790             if Parent_Node = Empty
2791               or else Nkind (Parent_Node) /= N_Compilation_Unit
2792               or else Context_Items (Parent_Node) /= Plist
2793             then
2794                return False;
2795             end if;
2796          end if;
2797
2798          return True;
2799       end Is_In_Context_Clause;
2800
2801       ---------------------------------
2802       -- Is_Static_String_Expression --
2803       ---------------------------------
2804
2805       function Is_Static_String_Expression (Arg : Node_Id) return Boolean is
2806          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
2807
2808       begin
2809          Analyze_And_Resolve (Argx);
2810          return Is_OK_Static_Expression (Argx)
2811            and then Nkind (Argx) = N_String_Literal;
2812       end Is_Static_String_Expression;
2813
2814       ----------------------
2815       -- Pragma_Misplaced --
2816       ----------------------
2817
2818       procedure Pragma_Misplaced is
2819       begin
2820          Error_Pragma ("incorrect placement of pragma%");
2821       end Pragma_Misplaced;
2822
2823       ------------------------------------
2824       -- Process Atomic_Shared_Volatile --
2825       ------------------------------------
2826
2827       procedure Process_Atomic_Shared_Volatile is
2828          E_Id : Node_Id;
2829          E    : Entity_Id;
2830          D    : Node_Id;
2831          K    : Node_Kind;
2832          Utyp : Entity_Id;
2833
2834          procedure Set_Atomic (E : Entity_Id);
2835          --  Set given type as atomic, and if no explicit alignment was given,
2836          --  set alignment to unknown, since back end knows what the alignment
2837          --  requirements are for atomic arrays. Note: this step is necessary
2838          --  for derived types.
2839
2840          ----------------
2841          -- Set_Atomic --
2842          ----------------
2843
2844          procedure Set_Atomic (E : Entity_Id) is
2845          begin
2846             Set_Is_Atomic (E);
2847
2848             if not Has_Alignment_Clause (E) then
2849                Set_Alignment (E, Uint_0);
2850             end if;
2851          end Set_Atomic;
2852
2853       --  Start of processing for Process_Atomic_Shared_Volatile
2854
2855       begin
2856          Check_Ada_83_Warning;
2857          Check_No_Identifiers;
2858          Check_Arg_Count (1);
2859          Check_Arg_Is_Local_Name (Arg1);
2860          E_Id := Get_Pragma_Arg (Arg1);
2861
2862          if Etype (E_Id) = Any_Type then
2863             return;
2864          end if;
2865
2866          E := Entity (E_Id);
2867          D := Declaration_Node (E);
2868          K := Nkind (D);
2869
2870          --  Check duplicate before we chain ourselves!
2871
2872          Check_Duplicate_Pragma (E);
2873
2874          --  Now check appropriateness of the entity
2875
2876          if Is_Type (E) then
2877             if Rep_Item_Too_Early (E, N)
2878                  or else
2879                Rep_Item_Too_Late (E, N)
2880             then
2881                return;
2882             else
2883                Check_First_Subtype (Arg1);
2884             end if;
2885
2886             if Prag_Id /= Pragma_Volatile then
2887                Set_Atomic (E);
2888                Set_Atomic (Underlying_Type (E));
2889                Set_Atomic (Base_Type (E));
2890             end if;
2891
2892             --  Attribute belongs on the base type. If the view of the type is
2893             --  currently private, it also belongs on the underlying type.
2894
2895             Set_Is_Volatile (Base_Type (E));
2896             Set_Is_Volatile (Underlying_Type (E));
2897
2898             Set_Treat_As_Volatile (E);
2899             Set_Treat_As_Volatile (Underlying_Type (E));
2900
2901          elsif K = N_Object_Declaration
2902            or else (K = N_Component_Declaration
2903                      and then Original_Record_Component (E) = E)
2904          then
2905             if Rep_Item_Too_Late (E, N) then
2906                return;
2907             end if;
2908
2909             if Prag_Id /= Pragma_Volatile then
2910                Set_Is_Atomic (E);
2911
2912                --  If the object declaration has an explicit initialization, a
2913                --  temporary may have to be created to hold the expression, to
2914                --  ensure that access to the object remain atomic.
2915
2916                if Nkind (Parent (E)) = N_Object_Declaration
2917                  and then Present (Expression (Parent (E)))
2918                then
2919                   Set_Has_Delayed_Freeze (E);
2920                end if;
2921
2922                --  An interesting improvement here. If an object of type X is
2923                --  declared atomic, and the type X is not atomic, that's a
2924                --  pity, since it may not have appropriate alignment etc. We
2925                --  can rescue this in the special case where the object and
2926                --  type are in the same unit by just setting the type as
2927                --  atomic, so that the back end will process it as atomic.
2928
2929                Utyp := Underlying_Type (Etype (E));
2930
2931                if Present (Utyp)
2932                  and then Sloc (E) > No_Location
2933                  and then Sloc (Utyp) > No_Location
2934                  and then
2935                    Get_Source_File_Index (Sloc (E)) =
2936                    Get_Source_File_Index (Sloc (Underlying_Type (Etype (E))))
2937                then
2938                   Set_Is_Atomic (Underlying_Type (Etype (E)));
2939                end if;
2940             end if;
2941
2942             Set_Is_Volatile (E);
2943             Set_Treat_As_Volatile (E);
2944
2945          else
2946             Error_Pragma_Arg
2947               ("inappropriate entity for pragma%", Arg1);
2948          end if;
2949       end Process_Atomic_Shared_Volatile;
2950
2951       -------------------------------------------
2952       -- Process_Compile_Time_Warning_Or_Error --
2953       -------------------------------------------
2954
2955       procedure Process_Compile_Time_Warning_Or_Error is
2956          Arg1x : constant Node_Id := Get_Pragma_Arg (Arg1);
2957
2958       begin
2959          Check_Arg_Count (2);
2960          Check_No_Identifiers;
2961          Check_Arg_Is_Static_Expression (Arg2, Standard_String);
2962          Analyze_And_Resolve (Arg1x, Standard_Boolean);
2963
2964          if Compile_Time_Known_Value (Arg1x) then
2965             if Is_True (Expr_Value (Get_Pragma_Arg (Arg1))) then
2966                declare
2967                   Str   : constant String_Id :=
2968                             Strval (Get_Pragma_Arg (Arg2));
2969                   Len   : constant Int := String_Length (Str);
2970                   Cont  : Boolean;
2971                   Ptr   : Nat;
2972                   CC    : Char_Code;
2973                   C     : Character;
2974                   Cent  : constant Entity_Id :=
2975                             Cunit_Entity (Current_Sem_Unit);
2976
2977                   Force : constant Boolean :=
2978                             Prag_Id = Pragma_Compile_Time_Warning
2979                               and then
2980                                 Is_Spec_Name (Unit_Name (Current_Sem_Unit))
2981                               and then (Ekind (Cent) /= E_Package
2982                                           or else not In_Private_Part (Cent));
2983                   --  Set True if this is the warning case, and we are in the
2984                   --  visible part of a package spec, or in a subprogram spec,
2985                   --  in which case we want to force the client to see the
2986                   --  warning, even though it is not in the main unit.
2987
2988                begin
2989                   --  Loop through segments of message separated by line feeds.
2990                   --  We output these segments as separate messages with
2991                   --  continuation marks for all but the first.
2992
2993                   Cont := False;
2994                   Ptr := 1;
2995                   loop
2996                      Error_Msg_Strlen := 0;
2997
2998                      --  Loop to copy characters from argument to error message
2999                      --  string buffer.
3000
3001                      loop
3002                         exit when Ptr > Len;
3003                         CC := Get_String_Char (Str, Ptr);
3004                         Ptr := Ptr + 1;
3005
3006                         --  Ignore wide chars ??? else store character
3007
3008                         if In_Character_Range (CC) then
3009                            C := Get_Character (CC);
3010                            exit when C = ASCII.LF;
3011                            Error_Msg_Strlen := Error_Msg_Strlen + 1;
3012                            Error_Msg_String (Error_Msg_Strlen) := C;
3013                         end if;
3014                      end loop;
3015
3016                      --  Here with one line ready to go
3017
3018                      Error_Msg_Warn := Prag_Id = Pragma_Compile_Time_Warning;
3019
3020                      --  If this is a warning in a spec, then we want clients
3021                      --  to see the warning, so mark the message with the
3022                      --  special sequence !! to force the warning. In the case
3023                      --  of a package spec, we do not force this if we are in
3024                      --  the private part of the spec.
3025
3026                      if Force then
3027                         if Cont = False then
3028                            Error_Msg_N ("<~!!", Arg1);
3029                            Cont := True;
3030                         else
3031                            Error_Msg_N ("\<~!!", Arg1);
3032                         end if;
3033
3034                      --  Error, rather than warning, or in a body, so we do not
3035                      --  need to force visibility for client (error will be
3036                      --  output in any case, and this is the situation in which
3037                      --  we do not want a client to get a warning, since the
3038                      --  warning is in the body or the spec private part).
3039
3040                      else
3041                         if Cont = False then
3042                            Error_Msg_N ("<~", Arg1);
3043                            Cont := True;
3044                         else
3045                            Error_Msg_N ("\<~", Arg1);
3046                         end if;
3047                      end if;
3048
3049                      exit when Ptr > Len;
3050                   end loop;
3051                end;
3052             end if;
3053          end if;
3054       end Process_Compile_Time_Warning_Or_Error;
3055
3056       ------------------------
3057       -- Process_Convention --
3058       ------------------------
3059
3060       procedure Process_Convention
3061         (C   : out Convention_Id;
3062          Ent : out Entity_Id)
3063       is
3064          Id        : Node_Id;
3065          E         : Entity_Id;
3066          E1        : Entity_Id;
3067          Cname     : Name_Id;
3068          Comp_Unit : Unit_Number_Type;
3069
3070          procedure Diagnose_Multiple_Pragmas (S : Entity_Id);
3071          --  Called if we have more than one Export/Import/Convention pragma.
3072          --  This is generally illegal, but we have a special case of allowing
3073          --  Import and Interface to coexist if they specify the convention in
3074          --  a consistent manner. We are allowed to do this, since Interface is
3075          --  an implementation defined pragma, and we choose to do it since we
3076          --  know Rational allows this combination. S is the entity id of the
3077          --  subprogram in question. This procedure also sets the special flag
3078          --  Import_Interface_Present in both pragmas in the case where we do
3079          --  have matching Import and Interface pragmas.
3080
3081          procedure Set_Convention_From_Pragma (E : Entity_Id);
3082          --  Set convention in entity E, and also flag that the entity has a
3083          --  convention pragma. If entity is for a private or incomplete type,
3084          --  also set convention and flag on underlying type. This procedure
3085          --  also deals with the special case of C_Pass_By_Copy convention.
3086
3087          -------------------------------
3088          -- Diagnose_Multiple_Pragmas --
3089          -------------------------------
3090
3091          procedure Diagnose_Multiple_Pragmas (S : Entity_Id) is
3092             Pdec : constant Node_Id := Declaration_Node (S);
3093             Decl : Node_Id;
3094             Err  : Boolean;
3095
3096             function Same_Convention (Decl : Node_Id) return Boolean;
3097             --  Decl is a pragma node. This function returns True if this
3098             --  pragma has a first argument that is an identifier with a
3099             --  Chars field corresponding to the Convention_Id C.
3100
3101             function Same_Name (Decl : Node_Id) return Boolean;
3102             --  Decl is a pragma node. This function returns True if this
3103             --  pragma has a second argument that is an identifier with a
3104             --  Chars field that matches the Chars of the current subprogram.
3105
3106             ---------------------
3107             -- Same_Convention --
3108             ---------------------
3109
3110             function Same_Convention (Decl : Node_Id) return Boolean is
3111                Arg1 : constant Node_Id :=
3112                         First (Pragma_Argument_Associations (Decl));
3113
3114             begin
3115                if Present (Arg1) then
3116                   declare
3117                      Arg : constant Node_Id := Get_Pragma_Arg (Arg1);
3118                   begin
3119                      if Nkind (Arg) = N_Identifier
3120                        and then Is_Convention_Name (Chars (Arg))
3121                        and then Get_Convention_Id (Chars (Arg)) = C
3122                      then
3123                         return True;
3124                      end if;
3125                   end;
3126                end if;
3127
3128                return False;
3129             end Same_Convention;
3130
3131             ---------------
3132             -- Same_Name --
3133             ---------------
3134
3135             function Same_Name (Decl : Node_Id) return Boolean is
3136                Arg1 : constant Node_Id :=
3137                         First (Pragma_Argument_Associations (Decl));
3138                Arg2 : Node_Id;
3139
3140             begin
3141                if No (Arg1) then
3142                   return False;
3143                end if;
3144
3145                Arg2 := Next (Arg1);
3146
3147                if No (Arg2) then
3148                   return False;
3149                end if;
3150
3151                declare
3152                   Arg : constant Node_Id := Get_Pragma_Arg (Arg2);
3153                begin
3154                   if Nkind (Arg) = N_Identifier
3155                     and then Chars (Arg) = Chars (S)
3156                   then
3157                      return True;
3158                   end if;
3159                end;
3160
3161                return False;
3162             end Same_Name;
3163
3164          --  Start of processing for Diagnose_Multiple_Pragmas
3165
3166          begin
3167             Err := True;
3168
3169             --  Definitely give message if we have Convention/Export here
3170
3171             if Prag_Id = Pragma_Convention or else Prag_Id = Pragma_Export then
3172                null;
3173
3174                --  If we have an Import or Export, scan back from pragma to
3175                --  find any previous pragma applying to the same procedure.
3176                --  The scan will be terminated by the start of the list, or
3177                --  hitting the subprogram declaration. This won't allow one
3178                --  pragma to appear in the public part and one in the private
3179                --  part, but that seems very unlikely in practice.
3180
3181             else
3182                Decl := Prev (N);
3183                while Present (Decl) and then Decl /= Pdec loop
3184
3185                   --  Look for pragma with same name as us
3186
3187                   if Nkind (Decl) = N_Pragma
3188                     and then Same_Name (Decl)
3189                   then
3190                      --  Give error if same as our pragma or Export/Convention
3191
3192                      if Pragma_Name (Decl) = Name_Export
3193                           or else
3194                         Pragma_Name (Decl) = Name_Convention
3195                           or else
3196                         Pragma_Name (Decl) = Pragma_Name (N)
3197                      then
3198                         exit;
3199
3200                      --  Case of Import/Interface or the other way round
3201
3202                      elsif Pragma_Name (Decl) = Name_Interface
3203                              or else
3204                            Pragma_Name (Decl) = Name_Import
3205                      then
3206                         --  Here we know that we have Import and Interface. It
3207                         --  doesn't matter which way round they are. See if
3208                         --  they specify the same convention. If so, all OK,
3209                         --  and set special flags to stop other messages
3210
3211                         if Same_Convention (Decl) then
3212                            Set_Import_Interface_Present (N);
3213                            Set_Import_Interface_Present (Decl);
3214                            Err := False;
3215
3216                         --  If different conventions, special message
3217
3218                         else
3219                            Error_Msg_Sloc := Sloc (Decl);
3220                            Error_Pragma_Arg
3221                              ("convention differs from that given#", Arg1);
3222                            return;
3223                         end if;
3224                      end if;
3225                   end if;
3226
3227                   Next (Decl);
3228                end loop;
3229             end if;
3230
3231             --  Give message if needed if we fall through those tests
3232
3233             if Err then
3234                Error_Pragma_Arg
3235                  ("at most one Convention/Export/Import pragma is allowed",
3236                   Arg2);
3237             end if;
3238          end Diagnose_Multiple_Pragmas;
3239
3240          --------------------------------
3241          -- Set_Convention_From_Pragma --
3242          --------------------------------
3243
3244          procedure Set_Convention_From_Pragma (E : Entity_Id) is
3245          begin
3246             --  Ada 2005 (AI-430): Check invalid attempt to change convention
3247             --  for an overridden dispatching operation. Technically this is
3248             --  an amendment and should only be done in Ada 2005 mode. However,
3249             --  this is clearly a mistake, since the problem that is addressed
3250             --  by this AI is that there is a clear gap in the RM!
3251
3252             if Is_Dispatching_Operation (E)
3253               and then Present (Overridden_Operation (E))
3254               and then C /= Convention (Overridden_Operation (E))
3255             then
3256                Error_Pragma_Arg
3257                  ("cannot change convention for " &
3258                   "overridden dispatching operation",
3259                   Arg1);
3260             end if;
3261
3262             --  Set the convention
3263
3264             Set_Convention (E, C);
3265             Set_Has_Convention_Pragma (E);
3266
3267             if Is_Incomplete_Or_Private_Type (E)
3268               and then Present (Underlying_Type (E))
3269             then
3270                Set_Convention            (Underlying_Type (E), C);
3271                Set_Has_Convention_Pragma (Underlying_Type (E), True);
3272             end if;
3273
3274             --  A class-wide type should inherit the convention of the specific
3275             --  root type (although this isn't specified clearly by the RM).
3276
3277             if Is_Type (E) and then Present (Class_Wide_Type (E)) then
3278                Set_Convention (Class_Wide_Type (E), C);
3279             end if;
3280
3281             --  If the entity is a record type, then check for special case of
3282             --  C_Pass_By_Copy, which is treated the same as C except that the
3283             --  special record flag is set. This convention is only permitted
3284             --  on record types (see AI95-00131).
3285
3286             if Cname = Name_C_Pass_By_Copy then
3287                if Is_Record_Type (E) then
3288                   Set_C_Pass_By_Copy (Base_Type (E));
3289                elsif Is_Incomplete_Or_Private_Type (E)
3290                  and then Is_Record_Type (Underlying_Type (E))
3291                then
3292                   Set_C_Pass_By_Copy (Base_Type (Underlying_Type (E)));
3293                else
3294                   Error_Pragma_Arg
3295                     ("C_Pass_By_Copy convention allowed only for record type",
3296                      Arg2);
3297                end if;
3298             end if;
3299
3300             --  If the entity is a derived boolean type, check for the special
3301             --  case of convention C, C++, or Fortran, where we consider any
3302             --  nonzero value to represent true.
3303
3304             if Is_Discrete_Type (E)
3305               and then Root_Type (Etype (E)) = Standard_Boolean
3306               and then
3307                 (C = Convention_C
3308                    or else
3309                  C = Convention_CPP
3310                    or else
3311                  C = Convention_Fortran)
3312             then
3313                Set_Nonzero_Is_True (Base_Type (E));
3314             end if;
3315          end Set_Convention_From_Pragma;
3316
3317       --  Start of processing for Process_Convention
3318
3319       begin
3320          Check_At_Least_N_Arguments (2);
3321          Check_Optional_Identifier (Arg1, Name_Convention);
3322          Check_Arg_Is_Identifier (Arg1);
3323          Cname := Chars (Get_Pragma_Arg (Arg1));
3324
3325          --  C_Pass_By_Copy is treated as a synonym for convention C (this is
3326          --  tested again below to set the critical flag).
3327
3328          if Cname = Name_C_Pass_By_Copy then
3329             C := Convention_C;
3330
3331          --  Otherwise we must have something in the standard convention list
3332
3333          elsif Is_Convention_Name (Cname) then
3334             C := Get_Convention_Id (Chars (Get_Pragma_Arg (Arg1)));
3335
3336          --  In DEC VMS, it seems that there is an undocumented feature that
3337          --  any unrecognized convention is treated as the default, which for
3338          --  us is convention C. It does not seem so terrible to do this
3339          --  unconditionally, silently in the VMS case, and with a warning
3340          --  in the non-VMS case.
3341
3342          else
3343             if Warn_On_Export_Import and not OpenVMS_On_Target then
3344                Error_Msg_N
3345                  ("?unrecognized convention name, C assumed",
3346                   Get_Pragma_Arg (Arg1));
3347             end if;
3348
3349             C := Convention_C;
3350          end if;
3351
3352          Check_Optional_Identifier (Arg2, Name_Entity);
3353          Check_Arg_Is_Local_Name (Arg2);
3354
3355          Id := Get_Pragma_Arg (Arg2);
3356          Analyze (Id);
3357
3358          if not Is_Entity_Name (Id) then
3359             Error_Pragma_Arg ("entity name required", Arg2);
3360          end if;
3361
3362          E := Entity (Id);
3363
3364          --  Set entity to return
3365
3366          Ent := E;
3367
3368          --  Ada_Pass_By_Copy special checking
3369
3370          if C = Convention_Ada_Pass_By_Copy then
3371             if not Is_First_Subtype (E) then
3372                Error_Pragma_Arg
3373                  ("convention `Ada_Pass_By_Copy` only "
3374                   & "allowed for types", Arg2);
3375             end if;
3376
3377             if Is_By_Reference_Type (E) then
3378                Error_Pragma_Arg
3379                  ("convention `Ada_Pass_By_Copy` not allowed for "
3380                   & "by-reference type", Arg1);
3381             end if;
3382          end if;
3383
3384          --  Ada_Pass_By_Reference special checking
3385
3386          if C = Convention_Ada_Pass_By_Reference then
3387             if not Is_First_Subtype (E) then
3388                Error_Pragma_Arg
3389                  ("convention `Ada_Pass_By_Reference` only "
3390                   & "allowed for types", Arg2);
3391             end if;
3392
3393             if Is_By_Copy_Type (E) then
3394                Error_Pragma_Arg
3395                  ("convention `Ada_Pass_By_Reference` not allowed for "
3396                   & "by-copy type", Arg1);
3397             end if;
3398          end if;
3399
3400          --  Go to renamed subprogram if present, since convention applies to
3401          --  the actual renamed entity, not to the renaming entity. If the
3402          --  subprogram is inherited, go to parent subprogram.
3403
3404          if Is_Subprogram (E)
3405            and then Present (Alias (E))
3406          then
3407             if Nkind (Parent (Declaration_Node (E))) =
3408                                        N_Subprogram_Renaming_Declaration
3409             then
3410                if Scope (E) /= Scope (Alias (E)) then
3411                   Error_Pragma_Ref
3412                     ("cannot apply pragma% to non-local entity&#", E);
3413                end if;
3414
3415                E := Alias (E);
3416
3417             elsif Nkind_In (Parent (E), N_Full_Type_Declaration,
3418                                         N_Private_Extension_Declaration)
3419               and then Scope (E) = Scope (Alias (E))
3420             then
3421                E := Alias (E);
3422
3423                --  Return the parent subprogram the entity was inherited from
3424
3425                Ent := E;
3426             end if;
3427          end if;
3428
3429          --  Check that we are not applying this to a specless body
3430
3431          if Is_Subprogram (E)
3432            and then Nkind (Parent (Declaration_Node (E))) = N_Subprogram_Body
3433          then
3434             Error_Pragma
3435               ("pragma% requires separate spec and must come before body");
3436          end if;
3437
3438          --  Check that we are not applying this to a named constant
3439
3440          if Ekind_In (E, E_Named_Integer, E_Named_Real) then
3441             Error_Msg_Name_1 := Pname;
3442             Error_Msg_N
3443               ("cannot apply pragma% to named constant!",
3444                Get_Pragma_Arg (Arg2));
3445             Error_Pragma_Arg
3446               ("\supply appropriate type for&!", Arg2);
3447          end if;
3448
3449          if Ekind (E) = E_Enumeration_Literal then
3450             Error_Pragma ("enumeration literal not allowed for pragma%");
3451          end if;
3452
3453          --  Check for rep item appearing too early or too late
3454
3455          if Etype (E) = Any_Type
3456            or else Rep_Item_Too_Early (E, N)
3457          then
3458             raise Pragma_Exit;
3459
3460          elsif Present (Underlying_Type (E)) then
3461             E := Underlying_Type (E);
3462          end if;
3463
3464          if Rep_Item_Too_Late (E, N) then
3465             raise Pragma_Exit;
3466          end if;
3467
3468          if Has_Convention_Pragma (E) then
3469             Diagnose_Multiple_Pragmas (E);
3470
3471          elsif Convention (E) = Convention_Protected
3472            or else Ekind (Scope (E)) = E_Protected_Type
3473          then
3474             Error_Pragma_Arg
3475               ("a protected operation cannot be given a different convention",
3476                 Arg2);
3477          end if;
3478
3479          --  For Intrinsic, a subprogram is required
3480
3481          if C = Convention_Intrinsic
3482            and then not Is_Subprogram (E)
3483            and then not Is_Generic_Subprogram (E)
3484          then
3485             Error_Pragma_Arg
3486               ("second argument of pragma% must be a subprogram", Arg2);
3487          end if;
3488
3489          --  For Stdcall, a subprogram, variable or subprogram type is required
3490
3491          if C = Convention_Stdcall
3492            and then not Is_Subprogram (E)
3493            and then not Is_Generic_Subprogram (E)
3494            and then Ekind (E) /= E_Variable
3495            and then not
3496              (Is_Access_Type (E)
3497                and then Ekind (Designated_Type (E)) = E_Subprogram_Type)
3498          then
3499             Error_Pragma_Arg
3500               ("second argument of pragma% must be subprogram (type)",
3501                Arg2);
3502          end if;
3503
3504          if not Is_Subprogram (E)
3505            and then not Is_Generic_Subprogram (E)
3506          then
3507             Set_Convention_From_Pragma (E);
3508
3509             if Is_Type (E) then
3510                Check_First_Subtype (Arg2);
3511                Set_Convention_From_Pragma (Base_Type (E));
3512
3513                --  For subprograms, we must set the convention on the
3514                --  internally generated directly designated type as well.
3515
3516                if Ekind (E) = E_Access_Subprogram_Type then
3517                   Set_Convention_From_Pragma (Directly_Designated_Type (E));
3518                end if;
3519             end if;
3520
3521          --  For the subprogram case, set proper convention for all homonyms
3522          --  in same scope and the same declarative part, i.e. the same
3523          --  compilation unit.
3524
3525          else
3526             Comp_Unit := Get_Source_Unit (E);
3527             Set_Convention_From_Pragma (E);
3528
3529             --  Treat a pragma Import as an implicit body, for GPS use
3530
3531             if Prag_Id = Pragma_Import then
3532                Generate_Reference (E, Id, 'b');
3533             end if;
3534
3535             --  Loop through the homonyms of the pragma argument's entity
3536
3537             E1 := Ent;
3538             loop
3539                E1 := Homonym (E1);
3540                exit when No (E1) or else Scope (E1) /= Current_Scope;
3541
3542                --  Do not set the pragma on inherited operations or on formal
3543                --  subprograms.
3544
3545                if Comes_From_Source (E1)
3546                  and then Comp_Unit = Get_Source_Unit (E1)
3547                  and then not Is_Formal_Subprogram (E1)
3548                  and then Nkind (Original_Node (Parent (E1))) /=
3549                                                     N_Full_Type_Declaration
3550                then
3551                   if Present (Alias (E1))
3552                     and then Scope (E1) /= Scope (Alias (E1))
3553                   then
3554                      Error_Pragma_Ref
3555                        ("cannot apply pragma% to non-local entity& declared#",
3556                         E1);
3557                   end if;
3558
3559                   Set_Convention_From_Pragma (E1);
3560
3561                   if Prag_Id = Pragma_Import then
3562                      Generate_Reference (E1, Id, 'b');
3563                   end if;
3564                end if;
3565
3566                --  For aspect case, do NOT apply to homonyms
3567
3568                exit when From_Aspect_Specification (N);
3569             end loop;
3570          end if;
3571       end Process_Convention;
3572
3573       ----------------------------------------
3574       -- Process_Disable_Enable_Atomic_Sync --
3575       ----------------------------------------
3576
3577       procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id) is
3578       begin
3579          GNAT_Pragma;
3580          Check_No_Identifiers;
3581          Check_At_Most_N_Arguments (1);
3582
3583          --  Modeled internally as
3584          --    pragma Unsuppress (Atomic_Synchronization [,Entity])
3585
3586          Rewrite (N,
3587            Make_Pragma (Loc,
3588              Pragma_Identifier            =>
3589                Make_Identifier (Loc, Nam),
3590              Pragma_Argument_Associations => New_List (
3591                Make_Pragma_Argument_Association (Loc,
3592                  Expression =>
3593                    Make_Identifier (Loc, Name_Atomic_Synchronization)))));
3594
3595          if Present (Arg1) then
3596             Append_To (Pragma_Argument_Associations (N), New_Copy (Arg1));
3597          end if;
3598
3599          Analyze (N);
3600       end Process_Disable_Enable_Atomic_Sync;
3601
3602       -----------------------------------------------------
3603       -- Process_Extended_Import_Export_Exception_Pragma --
3604       -----------------------------------------------------
3605
3606       procedure Process_Extended_Import_Export_Exception_Pragma
3607         (Arg_Internal : Node_Id;
3608          Arg_External : Node_Id;
3609          Arg_Form     : Node_Id;
3610          Arg_Code     : Node_Id)
3611       is
3612          Def_Id   : Entity_Id;
3613          Code_Val : Uint;
3614
3615       begin
3616          if not OpenVMS_On_Target then
3617             Error_Pragma
3618               ("?pragma% ignored (applies only to Open'V'M'S)");
3619          end if;
3620
3621          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3622          Def_Id := Entity (Arg_Internal);
3623
3624          if Ekind (Def_Id) /= E_Exception then
3625             Error_Pragma_Arg
3626               ("pragma% must refer to declared exception", Arg_Internal);
3627          end if;
3628
3629          Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
3630
3631          if Present (Arg_Form) then
3632             Check_Arg_Is_One_Of (Arg_Form, Name_Ada, Name_VMS);
3633          end if;
3634
3635          if Present (Arg_Form)
3636            and then Chars (Arg_Form) = Name_Ada
3637          then
3638             null;
3639          else
3640             Set_Is_VMS_Exception (Def_Id);
3641             Set_Exception_Code (Def_Id, No_Uint);
3642          end if;
3643
3644          if Present (Arg_Code) then
3645             if not Is_VMS_Exception (Def_Id) then
3646                Error_Pragma_Arg
3647                  ("Code option for pragma% not allowed for Ada case",
3648                   Arg_Code);
3649             end if;
3650
3651             Check_Arg_Is_Static_Expression (Arg_Code, Any_Integer);
3652             Code_Val := Expr_Value (Arg_Code);
3653
3654             if not UI_Is_In_Int_Range (Code_Val) then
3655                Error_Pragma_Arg
3656                  ("Code option for pragma% must be in 32-bit range",
3657                   Arg_Code);
3658
3659             else
3660                Set_Exception_Code (Def_Id, Code_Val);
3661             end if;
3662          end if;
3663       end Process_Extended_Import_Export_Exception_Pragma;
3664
3665       -------------------------------------------------
3666       -- Process_Extended_Import_Export_Internal_Arg --
3667       -------------------------------------------------
3668
3669       procedure Process_Extended_Import_Export_Internal_Arg
3670         (Arg_Internal : Node_Id := Empty)
3671       is
3672       begin
3673          if No (Arg_Internal) then
3674             Error_Pragma ("Internal parameter required for pragma%");
3675          end if;
3676
3677          if Nkind (Arg_Internal) = N_Identifier then
3678             null;
3679
3680          elsif Nkind (Arg_Internal) = N_Operator_Symbol
3681            and then (Prag_Id = Pragma_Import_Function
3682                        or else
3683                      Prag_Id = Pragma_Export_Function)
3684          then
3685             null;
3686
3687          else
3688             Error_Pragma_Arg
3689               ("wrong form for Internal parameter for pragma%", Arg_Internal);
3690          end if;
3691
3692          Check_Arg_Is_Local_Name (Arg_Internal);
3693       end Process_Extended_Import_Export_Internal_Arg;
3694
3695       --------------------------------------------------
3696       -- Process_Extended_Import_Export_Object_Pragma --
3697       --------------------------------------------------
3698
3699       procedure Process_Extended_Import_Export_Object_Pragma
3700         (Arg_Internal : Node_Id;
3701          Arg_External : Node_Id;
3702          Arg_Size     : Node_Id)
3703       is
3704          Def_Id : Entity_Id;
3705
3706       begin
3707          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3708          Def_Id := Entity (Arg_Internal);
3709
3710          if not Ekind_In (Def_Id, E_Constant, E_Variable) then
3711             Error_Pragma_Arg
3712               ("pragma% must designate an object", Arg_Internal);
3713          end if;
3714
3715          if Has_Rep_Pragma (Def_Id, Name_Common_Object)
3716               or else
3717             Has_Rep_Pragma (Def_Id, Name_Psect_Object)
3718          then
3719             Error_Pragma_Arg
3720               ("previous Common/Psect_Object applies, pragma % not permitted",
3721                Arg_Internal);
3722          end if;
3723
3724          if Rep_Item_Too_Late (Def_Id, N) then
3725             raise Pragma_Exit;
3726          end if;
3727
3728          Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
3729
3730          if Present (Arg_Size) then
3731             Check_Arg_Is_External_Name (Arg_Size);
3732          end if;
3733
3734          --  Export_Object case
3735
3736          if Prag_Id = Pragma_Export_Object then
3737             if not Is_Library_Level_Entity (Def_Id) then
3738                Error_Pragma_Arg
3739                  ("argument for pragma% must be library level entity",
3740                   Arg_Internal);
3741             end if;
3742
3743             if Ekind (Current_Scope) = E_Generic_Package then
3744                Error_Pragma ("pragma& cannot appear in a generic unit");
3745             end if;
3746
3747             if not Size_Known_At_Compile_Time (Etype (Def_Id)) then
3748                Error_Pragma_Arg
3749                  ("exported object must have compile time known size",
3750                   Arg_Internal);
3751             end if;
3752
3753             if Warn_On_Export_Import and then Is_Exported (Def_Id) then
3754                Error_Msg_N ("?duplicate Export_Object pragma", N);
3755             else
3756                Set_Exported (Def_Id, Arg_Internal);
3757             end if;
3758
3759          --  Import_Object case
3760
3761          else
3762             if Is_Concurrent_Type (Etype (Def_Id)) then
3763                Error_Pragma_Arg
3764                  ("cannot use pragma% for task/protected object",
3765                   Arg_Internal);
3766             end if;
3767
3768             if Ekind (Def_Id) = E_Constant then
3769                Error_Pragma_Arg
3770                  ("cannot import a constant", Arg_Internal);
3771             end if;
3772
3773             if Warn_On_Export_Import
3774               and then Has_Discriminants (Etype (Def_Id))
3775             then
3776                Error_Msg_N
3777                  ("imported value must be initialized?", Arg_Internal);
3778             end if;
3779
3780             if Warn_On_Export_Import
3781               and then Is_Access_Type (Etype (Def_Id))
3782             then
3783                Error_Pragma_Arg
3784                  ("cannot import object of an access type?", Arg_Internal);
3785             end if;
3786
3787             if Warn_On_Export_Import
3788               and then Is_Imported (Def_Id)
3789             then
3790                Error_Msg_N
3791                  ("?duplicate Import_Object pragma", N);
3792
3793             --  Check for explicit initialization present. Note that an
3794             --  initialization generated by the code generator, e.g. for an
3795             --  access type, does not count here.
3796
3797             elsif Present (Expression (Parent (Def_Id)))
3798                and then
3799                  Comes_From_Source
3800                    (Original_Node (Expression (Parent (Def_Id))))
3801             then
3802                Error_Msg_Sloc := Sloc (Def_Id);
3803                Error_Pragma_Arg
3804                  ("imported entities cannot be initialized (RM B.1(24))",
3805                   "\no initialization allowed for & declared#", Arg1);
3806             else
3807                Set_Imported (Def_Id);
3808                Note_Possible_Modification (Arg_Internal, Sure => False);
3809             end if;
3810          end if;
3811       end Process_Extended_Import_Export_Object_Pragma;
3812
3813       ------------------------------------------------------
3814       -- Process_Extended_Import_Export_Subprogram_Pragma --
3815       ------------------------------------------------------
3816
3817       procedure Process_Extended_Import_Export_Subprogram_Pragma
3818         (Arg_Internal                 : Node_Id;
3819          Arg_External                 : Node_Id;
3820          Arg_Parameter_Types          : Node_Id;
3821          Arg_Result_Type              : Node_Id := Empty;
3822          Arg_Mechanism                : Node_Id;
3823          Arg_Result_Mechanism         : Node_Id := Empty;
3824          Arg_First_Optional_Parameter : Node_Id := Empty)
3825       is
3826          Ent       : Entity_Id;
3827          Def_Id    : Entity_Id;
3828          Hom_Id    : Entity_Id;
3829          Formal    : Entity_Id;
3830          Ambiguous : Boolean;
3831          Match     : Boolean;
3832          Dval      : Node_Id;
3833
3834          function Same_Base_Type
3835           (Ptype  : Node_Id;
3836            Formal : Entity_Id) return Boolean;
3837          --  Determines if Ptype references the type of Formal. Note that only
3838          --  the base types need to match according to the spec. Ptype here is
3839          --  the argument from the pragma, which is either a type name, or an
3840          --  access attribute.
3841
3842          --------------------
3843          -- Same_Base_Type --
3844          --------------------
3845
3846          function Same_Base_Type
3847            (Ptype  : Node_Id;
3848             Formal : Entity_Id) return Boolean
3849          is
3850             Ftyp : constant Entity_Id := Base_Type (Etype (Formal));
3851             Pref : Node_Id;
3852
3853          begin
3854             --  Case where pragma argument is typ'Access
3855
3856             if Nkind (Ptype) = N_Attribute_Reference
3857               and then Attribute_Name (Ptype) = Name_Access
3858             then
3859                Pref := Prefix (Ptype);
3860                Find_Type (Pref);
3861
3862                if not Is_Entity_Name (Pref)
3863                  or else Entity (Pref) = Any_Type
3864                then
3865                   raise Pragma_Exit;
3866                end if;
3867
3868                --  We have a match if the corresponding argument is of an
3869                --  anonymous access type, and its designated type matches the
3870                --  type of the prefix of the access attribute
3871
3872                return Ekind (Ftyp) = E_Anonymous_Access_Type
3873                  and then Base_Type (Entity (Pref)) =
3874                             Base_Type (Etype (Designated_Type (Ftyp)));
3875
3876             --  Case where pragma argument is a type name
3877
3878             else
3879                Find_Type (Ptype);
3880
3881                if not Is_Entity_Name (Ptype)
3882                  or else Entity (Ptype) = Any_Type
3883                then
3884                   raise Pragma_Exit;
3885                end if;
3886
3887                --  We have a match if the corresponding argument is of the type
3888                --  given in the pragma (comparing base types)
3889
3890                return Base_Type (Entity (Ptype)) = Ftyp;
3891             end if;
3892          end Same_Base_Type;
3893
3894       --  Start of processing for
3895       --  Process_Extended_Import_Export_Subprogram_Pragma
3896
3897       begin
3898          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3899          Ent := Empty;
3900          Ambiguous := False;
3901
3902          --  Loop through homonyms (overloadings) of the entity
3903
3904          Hom_Id := Entity (Arg_Internal);
3905          while Present (Hom_Id) loop
3906             Def_Id := Get_Base_Subprogram (Hom_Id);
3907
3908             --  We need a subprogram in the current scope
3909
3910             if not Is_Subprogram (Def_Id)
3911               or else Scope (Def_Id) /= Current_Scope
3912             then
3913                null;
3914
3915             else
3916                Match := True;
3917
3918                --  Pragma cannot apply to subprogram body
3919
3920                if Is_Subprogram (Def_Id)
3921                  and then Nkind (Parent (Declaration_Node (Def_Id))) =
3922                                                              N_Subprogram_Body
3923                then
3924                   Error_Pragma
3925                     ("pragma% requires separate spec"
3926                       & " and must come before body");
3927                end if;
3928
3929                --  Test result type if given, note that the result type
3930                --  parameter can only be present for the function cases.
3931
3932                if Present (Arg_Result_Type)
3933                  and then not Same_Base_Type (Arg_Result_Type, Def_Id)
3934                then
3935                   Match := False;
3936
3937                elsif Etype (Def_Id) /= Standard_Void_Type
3938                  and then
3939                    (Pname = Name_Export_Procedure
3940                       or else
3941                     Pname = Name_Import_Procedure)
3942                then
3943                   Match := False;
3944
3945                --  Test parameter types if given. Note that this parameter
3946                --  has not been analyzed (and must not be, since it is
3947                --  semantic nonsense), so we get it as the parser left it.
3948
3949                elsif Present (Arg_Parameter_Types) then
3950                   Check_Matching_Types : declare
3951                      Formal : Entity_Id;
3952                      Ptype  : Node_Id;
3953
3954                   begin
3955                      Formal := First_Formal (Def_Id);
3956
3957                      if Nkind (Arg_Parameter_Types) = N_Null then
3958                         if Present (Formal) then
3959                            Match := False;
3960                         end if;
3961
3962                      --  A list of one type, e.g. (List) is parsed as
3963                      --  a parenthesized expression.
3964
3965                      elsif Nkind (Arg_Parameter_Types) /= N_Aggregate
3966                        and then Paren_Count (Arg_Parameter_Types) = 1
3967                      then
3968                         if No (Formal)
3969                           or else Present (Next_Formal (Formal))
3970                         then
3971                            Match := False;
3972                         else
3973                            Match :=
3974                              Same_Base_Type (Arg_Parameter_Types, Formal);
3975                         end if;
3976
3977                      --  A list of more than one type is parsed as a aggregate
3978
3979                      elsif Nkind (Arg_Parameter_Types) = N_Aggregate
3980                        and then Paren_Count (Arg_Parameter_Types) = 0
3981                      then
3982                         Ptype := First (Expressions (Arg_Parameter_Types));
3983                         while Present (Ptype) or else Present (Formal) loop
3984                            if No (Ptype)
3985                              or else No (Formal)
3986                              or else not Same_Base_Type (Ptype, Formal)
3987                            then
3988                               Match := False;
3989                               exit;
3990                            else
3991                               Next_Formal (Formal);
3992                               Next (Ptype);
3993                            end if;
3994                         end loop;
3995
3996                      --  Anything else is of the wrong form
3997
3998                      else
3999                         Error_Pragma_Arg
4000                           ("wrong form for Parameter_Types parameter",
4001                            Arg_Parameter_Types);
4002                      end if;
4003                   end Check_Matching_Types;
4004                end if;
4005
4006                --  Match is now False if the entry we found did not match
4007                --  either a supplied Parameter_Types or Result_Types argument
4008
4009                if Match then
4010                   if No (Ent) then
4011                      Ent := Def_Id;
4012
4013                   --  Ambiguous case, the flag Ambiguous shows if we already
4014                   --  detected this and output the initial messages.
4015
4016                   else
4017                      if not Ambiguous then
4018                         Ambiguous := True;
4019                         Error_Msg_Name_1 := Pname;
4020                         Error_Msg_N
4021                           ("pragma% does not uniquely identify subprogram!",
4022                            N);
4023                         Error_Msg_Sloc := Sloc (Ent);
4024                         Error_Msg_N ("matching subprogram #!", N);
4025                         Ent := Empty;
4026                      end if;
4027
4028                      Error_Msg_Sloc := Sloc (Def_Id);
4029                      Error_Msg_N ("matching subprogram #!", N);
4030                   end if;
4031                end if;
4032             end if;
4033
4034             Hom_Id := Homonym (Hom_Id);
4035          end loop;
4036
4037          --  See if we found an entry
4038
4039          if No (Ent) then
4040             if not Ambiguous then
4041                if Is_Generic_Subprogram (Entity (Arg_Internal)) then
4042                   Error_Pragma
4043                     ("pragma% cannot be given for generic subprogram");
4044                else
4045                   Error_Pragma
4046                     ("pragma% does not identify local subprogram");
4047                end if;
4048             end if;
4049
4050             return;
4051          end if;
4052
4053          --  Import pragmas must be for imported entities
4054
4055          if Prag_Id = Pragma_Import_Function
4056               or else
4057             Prag_Id = Pragma_Import_Procedure
4058               or else
4059             Prag_Id = Pragma_Import_Valued_Procedure
4060          then
4061             if not Is_Imported (Ent) then
4062                Error_Pragma
4063                  ("pragma Import or Interface must precede pragma%");
4064             end if;
4065
4066          --  Here we have the Export case which can set the entity as exported
4067
4068          --  But does not do so if the specified external name is null, since
4069          --  that is taken as a signal in DEC Ada 83 (with which we want to be
4070          --  compatible) to request no external name.
4071
4072          elsif Nkind (Arg_External) = N_String_Literal
4073            and then String_Length (Strval (Arg_External)) = 0
4074          then
4075             null;
4076
4077          --  In all other cases, set entity as exported
4078
4079          else
4080             Set_Exported (Ent, Arg_Internal);
4081          end if;
4082
4083          --  Special processing for Valued_Procedure cases
4084
4085          if Prag_Id = Pragma_Import_Valued_Procedure
4086            or else
4087             Prag_Id = Pragma_Export_Valued_Procedure
4088          then
4089             Formal := First_Formal (Ent);
4090
4091             if No (Formal) then
4092                Error_Pragma ("at least one parameter required for pragma%");
4093
4094             elsif Ekind (Formal) /= E_Out_Parameter then
4095                Error_Pragma ("first parameter must have mode out for pragma%");
4096
4097             else
4098                Set_Is_Valued_Procedure (Ent);
4099             end if;
4100          end if;
4101
4102          Set_Extended_Import_Export_External_Name (Ent, Arg_External);
4103
4104          --  Process Result_Mechanism argument if present. We have already
4105          --  checked that this is only allowed for the function case.
4106
4107          if Present (Arg_Result_Mechanism) then
4108             Set_Mechanism_Value (Ent, Arg_Result_Mechanism);
4109          end if;
4110
4111          --  Process Mechanism parameter if present. Note that this parameter
4112          --  is not analyzed, and must not be analyzed since it is semantic
4113          --  nonsense, so we get it in exactly as the parser left it.
4114
4115          if Present (Arg_Mechanism) then
4116             declare
4117                Formal : Entity_Id;
4118                Massoc : Node_Id;
4119                Mname  : Node_Id;
4120                Choice : Node_Id;
4121
4122             begin
4123                --  A single mechanism association without a formal parameter
4124                --  name is parsed as a parenthesized expression. All other
4125                --  cases are parsed as aggregates, so we rewrite the single
4126                --  parameter case as an aggregate for consistency.
4127
4128                if Nkind (Arg_Mechanism) /= N_Aggregate
4129                  and then Paren_Count (Arg_Mechanism) = 1
4130                then
4131                   Rewrite (Arg_Mechanism,
4132                     Make_Aggregate (Sloc (Arg_Mechanism),
4133                       Expressions => New_List (
4134                         Relocate_Node (Arg_Mechanism))));
4135                end if;
4136
4137                --  Case of only mechanism name given, applies to all formals
4138
4139                if Nkind (Arg_Mechanism) /= N_Aggregate then
4140                   Formal := First_Formal (Ent);
4141                   while Present (Formal) loop
4142                      Set_Mechanism_Value (Formal, Arg_Mechanism);
4143                      Next_Formal (Formal);
4144                   end loop;
4145
4146                --  Case of list of mechanism associations given
4147
4148                else
4149                   if Null_Record_Present (Arg_Mechanism) then
4150                      Error_Pragma_Arg
4151                        ("inappropriate form for Mechanism parameter",
4152                         Arg_Mechanism);
4153                   end if;
4154
4155                   --  Deal with positional ones first
4156
4157                   Formal := First_Formal (Ent);
4158
4159                   if Present (Expressions (Arg_Mechanism)) then
4160                      Mname := First (Expressions (Arg_Mechanism));
4161                      while Present (Mname) loop
4162                         if No (Formal) then
4163                            Error_Pragma_Arg
4164                              ("too many mechanism associations", Mname);
4165                         end if;
4166
4167                         Set_Mechanism_Value (Formal, Mname);
4168                         Next_Formal (Formal);
4169                         Next (Mname);
4170                      end loop;
4171                   end if;
4172
4173                   --  Deal with named entries
4174
4175                   if Present (Component_Associations (Arg_Mechanism)) then
4176                      Massoc := First (Component_Associations (Arg_Mechanism));
4177                      while Present (Massoc) loop
4178                         Choice := First (Choices (Massoc));
4179
4180                         if Nkind (Choice) /= N_Identifier
4181                           or else Present (Next (Choice))
4182                         then
4183                            Error_Pragma_Arg
4184                              ("incorrect form for mechanism association",
4185                               Massoc);
4186                         end if;
4187
4188                         Formal := First_Formal (Ent);
4189                         loop
4190                            if No (Formal) then
4191                               Error_Pragma_Arg
4192                                 ("parameter name & not present", Choice);
4193                            end if;
4194
4195                            if Chars (Choice) = Chars (Formal) then
4196                               Set_Mechanism_Value
4197                                 (Formal, Expression (Massoc));
4198
4199                               --  Set entity on identifier (needed by ASIS)
4200
4201                               Set_Entity (Choice, Formal);
4202
4203                               exit;
4204                            end if;
4205
4206                            Next_Formal (Formal);
4207                         end loop;
4208
4209                         Next (Massoc);
4210                      end loop;
4211                   end if;
4212                end if;
4213             end;
4214          end if;
4215
4216          --  Process First_Optional_Parameter argument if present. We have
4217          --  already checked that this is only allowed for the Import case.
4218
4219          if Present (Arg_First_Optional_Parameter) then
4220             if Nkind (Arg_First_Optional_Parameter) /= N_Identifier then
4221                Error_Pragma_Arg
4222                  ("first optional parameter must be formal parameter name",
4223                   Arg_First_Optional_Parameter);
4224             end if;
4225
4226             Formal := First_Formal (Ent);
4227             loop
4228                if No (Formal) then
4229                   Error_Pragma_Arg
4230                     ("specified formal parameter& not found",
4231                      Arg_First_Optional_Parameter);
4232                end if;
4233
4234                exit when Chars (Formal) =
4235                          Chars (Arg_First_Optional_Parameter);
4236
4237                Next_Formal (Formal);
4238             end loop;
4239
4240             Set_First_Optional_Parameter (Ent, Formal);
4241
4242             --  Check specified and all remaining formals have right form
4243
4244             while Present (Formal) loop
4245                if Ekind (Formal) /= E_In_Parameter then
4246                   Error_Msg_NE
4247                     ("optional formal& is not of mode in!",
4248                      Arg_First_Optional_Parameter, Formal);
4249
4250                else
4251                   Dval := Default_Value (Formal);
4252
4253                   if No (Dval) then
4254                      Error_Msg_NE
4255                        ("optional formal& does not have default value!",
4256                         Arg_First_Optional_Parameter, Formal);
4257
4258                   elsif Compile_Time_Known_Value_Or_Aggr (Dval) then
4259                      null;
4260
4261                   else
4262                      Error_Msg_FE
4263                        ("default value for optional formal& is non-static!",
4264                         Arg_First_Optional_Parameter, Formal);
4265                   end if;
4266                end if;
4267
4268                Set_Is_Optional_Parameter (Formal);
4269                Next_Formal (Formal);
4270             end loop;
4271          end if;
4272       end Process_Extended_Import_Export_Subprogram_Pragma;
4273
4274       --------------------------
4275       -- Process_Generic_List --
4276       --------------------------
4277
4278       procedure Process_Generic_List is
4279          Arg : Node_Id;
4280          Exp : Node_Id;
4281
4282       begin
4283          Check_No_Identifiers;
4284          Check_At_Least_N_Arguments (1);
4285
4286          Arg := Arg1;
4287          while Present (Arg) loop
4288             Exp := Get_Pragma_Arg (Arg);
4289             Analyze (Exp);
4290
4291             if not Is_Entity_Name (Exp)
4292               or else
4293                 (not Is_Generic_Instance (Entity (Exp))
4294                   and then
4295                  not Is_Generic_Unit (Entity (Exp)))
4296             then
4297                Error_Pragma_Arg
4298                  ("pragma% argument must be name of generic unit/instance",
4299                   Arg);
4300             end if;
4301
4302             Next (Arg);
4303          end loop;
4304       end Process_Generic_List;
4305
4306       ------------------------------------
4307       -- Process_Import_Predefined_Type --
4308       ------------------------------------
4309
4310       procedure Process_Import_Predefined_Type is
4311          Loc  : constant Source_Ptr := Sloc (N);
4312          Elmt : Elmt_Id;
4313          Ftyp : Node_Id := Empty;
4314          Decl : Node_Id;
4315          Def  : Node_Id;
4316          Nam  : Name_Id;
4317
4318       begin
4319          String_To_Name_Buffer (Strval (Expression (Arg3)));
4320          Nam := Name_Find;
4321
4322          Elmt := First_Elmt (Predefined_Float_Types);
4323          while Present (Elmt) and then Chars (Node (Elmt)) /= Nam loop
4324             Next_Elmt (Elmt);
4325          end loop;
4326
4327          Ftyp := Node (Elmt);
4328
4329          if Present (Ftyp) then
4330
4331             --  Don't build a derived type declaration, because predefined C
4332             --  types have no declaration anywhere, so cannot really be named.
4333             --  Instead build a full type declaration, starting with an
4334             --  appropriate type definition is built
4335
4336             if Is_Floating_Point_Type (Ftyp) then
4337                Def := Make_Floating_Point_Definition (Loc,
4338                  Make_Integer_Literal (Loc, Digits_Value (Ftyp)),
4339                  Make_Real_Range_Specification (Loc,
4340                    Make_Real_Literal (Loc, Realval (Type_Low_Bound (Ftyp))),
4341                    Make_Real_Literal (Loc, Realval (Type_High_Bound (Ftyp)))));
4342
4343             --  Should never have a predefined type we cannot handle
4344
4345             else
4346                raise Program_Error;
4347             end if;
4348
4349             --  Build and insert a Full_Type_Declaration, which will be
4350             --  analyzed as soon as this list entry has been analyzed.
4351
4352             Decl := Make_Full_Type_Declaration (Loc,
4353               Make_Defining_Identifier (Loc, Chars (Expression (Arg2))),
4354               Type_Definition => Def);
4355
4356             Insert_After (N, Decl);
4357             Mark_Rewrite_Insertion (Decl);
4358
4359          else
4360             Error_Pragma_Arg ("no matching type found for pragma%",
4361             Arg2);
4362          end if;
4363       end Process_Import_Predefined_Type;
4364
4365       ---------------------------------
4366       -- Process_Import_Or_Interface --
4367       ---------------------------------
4368
4369       procedure Process_Import_Or_Interface is
4370          C      : Convention_Id;
4371          Def_Id : Entity_Id;
4372          Hom_Id : Entity_Id;
4373
4374       begin
4375          Process_Convention (C, Def_Id);
4376          Kill_Size_Check_Code (Def_Id);
4377          Note_Possible_Modification (Get_Pragma_Arg (Arg2), Sure => False);
4378
4379          if Ekind_In (Def_Id, E_Variable, E_Constant) then
4380
4381             --  We do not permit Import to apply to a renaming declaration
4382
4383             if Present (Renamed_Object (Def_Id)) then
4384                Error_Pragma_Arg
4385                  ("pragma% not allowed for object renaming", Arg2);
4386
4387             --  User initialization is not allowed for imported object, but
4388             --  the object declaration may contain a default initialization,
4389             --  that will be discarded. Note that an explicit initialization
4390             --  only counts if it comes from source, otherwise it is simply
4391             --  the code generator making an implicit initialization explicit.
4392
4393             elsif Present (Expression (Parent (Def_Id)))
4394               and then Comes_From_Source (Expression (Parent (Def_Id)))
4395             then
4396                Error_Msg_Sloc := Sloc (Def_Id);
4397                Error_Pragma_Arg
4398                  ("no initialization allowed for declaration of& #",
4399                   "\imported entities cannot be initialized (RM B.1(24))",
4400                   Arg2);
4401
4402             else
4403                Set_Imported (Def_Id);
4404                Process_Interface_Name (Def_Id, Arg3, Arg4);
4405
4406                --  Note that we do not set Is_Public here. That's because we
4407                --  only want to set it if there is no address clause, and we
4408                --  don't know that yet, so we delay that processing till
4409                --  freeze time.
4410
4411                --  pragma Import completes deferred constants
4412
4413                if Ekind (Def_Id) = E_Constant then
4414                   Set_Has_Completion (Def_Id);
4415                end if;
4416
4417                --  It is not possible to import a constant of an unconstrained
4418                --  array type (e.g. string) because there is no simple way to
4419                --  write a meaningful subtype for it.
4420
4421                if Is_Array_Type (Etype (Def_Id))
4422                  and then not Is_Constrained (Etype (Def_Id))
4423                then
4424                   Error_Msg_NE
4425                     ("imported constant& must have a constrained subtype",
4426                       N, Def_Id);
4427                end if;
4428             end if;
4429
4430          elsif Is_Subprogram (Def_Id)
4431            or else Is_Generic_Subprogram (Def_Id)
4432          then
4433             --  If the name is overloaded, pragma applies to all of the denoted
4434             --  entities in the same declarative part.
4435
4436             Hom_Id := Def_Id;
4437             while Present (Hom_Id) loop
4438                Def_Id := Get_Base_Subprogram (Hom_Id);
4439
4440                --  Ignore inherited subprograms because the pragma will apply
4441                --  to the parent operation, which is the one called.
4442
4443                if Is_Overloadable (Def_Id)
4444                  and then Present (Alias (Def_Id))
4445                then
4446                   null;
4447
4448                --  If it is not a subprogram, it must be in an outer scope and
4449                --  pragma does not apply.
4450
4451                elsif not Is_Subprogram (Def_Id)
4452                  and then not Is_Generic_Subprogram (Def_Id)
4453                then
4454                   null;
4455
4456                --  The pragma does not apply to primitives of interfaces
4457
4458                elsif Is_Dispatching_Operation (Def_Id)
4459                  and then Present (Find_Dispatching_Type (Def_Id))
4460                  and then Is_Interface (Find_Dispatching_Type (Def_Id))
4461                then
4462                   null;
4463
4464                --  Verify that the homonym is in the same declarative part (not
4465                --  just the same scope).
4466
4467                elsif Parent (Unit_Declaration_Node (Def_Id)) /= Parent (N)
4468                  and then Nkind (Parent (N)) /= N_Compilation_Unit_Aux
4469                then
4470                   exit;
4471
4472                else
4473                   Set_Imported (Def_Id);
4474
4475                   --  Reject an Import applied to an abstract subprogram
4476
4477                   if Is_Subprogram (Def_Id)
4478                     and then Is_Abstract_Subprogram (Def_Id)
4479                   then
4480                      Error_Msg_Sloc := Sloc (Def_Id);
4481                      Error_Msg_NE
4482                        ("cannot import abstract subprogram& declared#",
4483                         Arg2, Def_Id);
4484                   end if;
4485
4486                   --  Special processing for Convention_Intrinsic
4487
4488                   if C = Convention_Intrinsic then
4489
4490                      --  Link_Name argument not allowed for intrinsic
4491
4492                      Check_No_Link_Name;
4493
4494                      Set_Is_Intrinsic_Subprogram (Def_Id);
4495
4496                      --  If no external name is present, then check that this
4497                      --  is a valid intrinsic subprogram. If an external name
4498                      --  is present, then this is handled by the back end.
4499
4500                      if No (Arg3) then
4501                         Check_Intrinsic_Subprogram
4502                           (Def_Id, Get_Pragma_Arg (Arg2));
4503                      end if;
4504                   end if;
4505
4506                   --  All interfaced procedures need an external symbol created
4507                   --  for them since they are always referenced from another
4508                   --  object file.
4509
4510                   Set_Is_Public (Def_Id);
4511
4512                   --  Verify that the subprogram does not have a completion
4513                   --  through a renaming declaration. For other completions the
4514                   --  pragma appears as a too late representation.
4515
4516                   declare
4517                      Decl : constant Node_Id := Unit_Declaration_Node (Def_Id);
4518
4519                   begin
4520                      if Present (Decl)
4521                        and then Nkind (Decl) = N_Subprogram_Declaration
4522                        and then Present (Corresponding_Body (Decl))
4523                        and then Nkind (Unit_Declaration_Node
4524                                         (Corresponding_Body (Decl))) =
4525                                              N_Subprogram_Renaming_Declaration
4526                      then
4527                         Error_Msg_Sloc := Sloc (Def_Id);
4528                         Error_Msg_NE
4529                           ("cannot import&, renaming already provided for " &
4530                            "declaration #", N, Def_Id);
4531                      end if;
4532                   end;
4533
4534                   Set_Has_Completion (Def_Id);
4535                   Process_Interface_Name (Def_Id, Arg3, Arg4);
4536                end if;
4537
4538                if Is_Compilation_Unit (Hom_Id) then
4539
4540                   --  Its possible homonyms are not affected by the pragma.
4541                   --  Such homonyms might be present in the context of other
4542                   --  units being compiled.
4543
4544                   exit;
4545
4546                else
4547                   Hom_Id := Homonym (Hom_Id);
4548                end if;
4549             end loop;
4550
4551          --  When the convention is Java or CIL, we also allow Import to be
4552          --  given for packages, generic packages, exceptions, record
4553          --  components, and access to subprograms.
4554
4555          elsif (C = Convention_Java or else C = Convention_CIL)
4556            and then
4557              (Is_Package_Or_Generic_Package (Def_Id)
4558                or else Ekind (Def_Id) = E_Exception
4559                or else Ekind (Def_Id) = E_Access_Subprogram_Type
4560                or else Nkind (Parent (Def_Id)) = N_Component_Declaration)
4561          then
4562             Set_Imported (Def_Id);
4563             Set_Is_Public (Def_Id);
4564             Process_Interface_Name (Def_Id, Arg3, Arg4);
4565
4566          --  Import a CPP class
4567
4568          elsif Is_Record_Type (Def_Id)
4569            and then C = Convention_CPP
4570          then
4571             --  Types treated as CPP classes must be declared limited (note:
4572             --  this used to be a warning but there is no real benefit to it
4573             --  since we did effectively intend to treat the type as limited
4574             --  anyway).
4575
4576             if not Is_Limited_Type (Def_Id) then
4577                Error_Msg_N
4578                  ("imported 'C'P'P type must be limited",
4579                   Get_Pragma_Arg (Arg2));
4580             end if;
4581
4582             Set_Is_CPP_Class (Def_Id);
4583
4584             --  Imported CPP types must not have discriminants (because C++
4585             --  classes do not have discriminants).
4586
4587             if Has_Discriminants (Def_Id) then
4588                Error_Msg_N
4589                  ("imported 'C'P'P type cannot have discriminants",
4590                   First (Discriminant_Specifications
4591                           (Declaration_Node (Def_Id))));
4592             end if;
4593
4594             --  Components of imported CPP types must not have default
4595             --  expressions because the constructor (if any) is on the
4596             --  C++ side.
4597
4598             declare
4599                Tdef  : constant Node_Id :=
4600                          Type_Definition (Declaration_Node (Def_Id));
4601                Clist : Node_Id;
4602                Comp  : Node_Id;
4603
4604             begin
4605                if Nkind (Tdef) = N_Record_Definition then
4606                   Clist := Component_List (Tdef);
4607
4608                else
4609                   pragma Assert (Nkind (Tdef) = N_Derived_Type_Definition);
4610                   Clist := Component_List (Record_Extension_Part (Tdef));
4611                end if;
4612
4613                if Present (Clist) then
4614                   Comp := First (Component_Items (Clist));
4615                   while Present (Comp) loop
4616                      if Present (Expression (Comp)) then
4617                         Error_Msg_N
4618                           ("component of imported 'C'P'P type cannot have" &
4619                            " default expression", Expression (Comp));
4620                      end if;
4621
4622                      Next (Comp);
4623                   end loop;
4624                end if;
4625             end;
4626
4627          elsif Nkind (Parent (Def_Id)) = N_Incomplete_Type_Declaration then
4628             Check_No_Link_Name;
4629             Check_Arg_Count (3);
4630             Check_Arg_Is_Static_Expression (Arg3, Standard_String);
4631
4632             Process_Import_Predefined_Type;
4633
4634          else
4635             Error_Pragma_Arg
4636               ("second argument of pragma% must be object, subprogram" &
4637                " or incomplete type",
4638                Arg2);
4639          end if;
4640
4641          --  If this pragma applies to a compilation unit, then the unit, which
4642          --  is a subprogram, does not require (or allow) a body. We also do
4643          --  not need to elaborate imported procedures.
4644
4645          if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
4646             declare
4647                Cunit : constant Node_Id := Parent (Parent (N));
4648             begin
4649                Set_Body_Required (Cunit, False);
4650             end;
4651          end if;
4652       end Process_Import_Or_Interface;
4653
4654       --------------------
4655       -- Process_Inline --
4656       --------------------
4657
4658       procedure Process_Inline (Active : Boolean) is
4659          Assoc     : Node_Id;
4660          Decl      : Node_Id;
4661          Subp_Id   : Node_Id;
4662          Subp      : Entity_Id;
4663          Applies   : Boolean;
4664
4665          Effective : Boolean := False;
4666          --  Set True if inline has some effect, i.e. if there is at least one
4667          --  subprogram set as inlined as a result of the use of the pragma.
4668
4669          procedure Make_Inline (Subp : Entity_Id);
4670          --  Subp is the defining unit name of the subprogram declaration. Set
4671          --  the flag, as well as the flag in the corresponding body, if there
4672          --  is one present.
4673
4674          procedure Set_Inline_Flags (Subp : Entity_Id);
4675          --  Sets Is_Inlined and Has_Pragma_Inline flags for Subp and also
4676          --  Has_Pragma_Inline_Always for the Inline_Always case.
4677
4678          function Inlining_Not_Possible (Subp : Entity_Id) return Boolean;
4679          --  Returns True if it can be determined at this stage that inlining
4680          --  is not possible, for example if the body is available and contains
4681          --  exception handlers, we prevent inlining, since otherwise we can
4682          --  get undefined symbols at link time. This function also emits a
4683          --  warning if front-end inlining is enabled and the pragma appears
4684          --  too late.
4685          --
4686          --  ??? is business with link symbols still valid, or does it relate
4687          --  to front end ZCX which is being phased out ???
4688
4689          ---------------------------
4690          -- Inlining_Not_Possible --
4691          ---------------------------
4692
4693          function Inlining_Not_Possible (Subp : Entity_Id) return Boolean is
4694             Decl  : constant Node_Id := Unit_Declaration_Node (Subp);
4695             Stats : Node_Id;
4696
4697          begin
4698             if Nkind (Decl) = N_Subprogram_Body then
4699                Stats := Handled_Statement_Sequence (Decl);
4700                return Present (Exception_Handlers (Stats))
4701                  or else Present (At_End_Proc (Stats));
4702
4703             elsif Nkind (Decl) = N_Subprogram_Declaration
4704               and then Present (Corresponding_Body (Decl))
4705             then
4706                if Front_End_Inlining
4707                  and then Analyzed (Corresponding_Body (Decl))
4708                then
4709                   Error_Msg_N ("pragma appears too late, ignored?", N);
4710                   return True;
4711
4712                --  If the subprogram is a renaming as body, the body is just a
4713                --  call to the renamed subprogram, and inlining is trivially
4714                --  possible.
4715
4716                elsif
4717                  Nkind (Unit_Declaration_Node (Corresponding_Body (Decl))) =
4718                                              N_Subprogram_Renaming_Declaration
4719                then
4720                   return False;
4721
4722                else
4723                   Stats :=
4724                     Handled_Statement_Sequence
4725                         (Unit_Declaration_Node (Corresponding_Body (Decl)));
4726
4727                   return
4728                     Present (Exception_Handlers (Stats))
4729                       or else Present (At_End_Proc (Stats));
4730                end if;
4731
4732             else
4733                --  If body is not available, assume the best, the check is
4734                --  performed again when compiling enclosing package bodies.
4735
4736                return False;
4737             end if;
4738          end Inlining_Not_Possible;
4739
4740          -----------------
4741          -- Make_Inline --
4742          -----------------
4743
4744          procedure Make_Inline (Subp : Entity_Id) is
4745             Kind       : constant Entity_Kind := Ekind (Subp);
4746             Inner_Subp : Entity_Id   := Subp;
4747
4748          begin
4749             --  Ignore if bad type, avoid cascaded error
4750
4751             if Etype (Subp) = Any_Type then
4752                Applies := True;
4753                return;
4754
4755             --  Ignore if all inlining is suppressed
4756
4757             elsif Suppress_All_Inlining then
4758                Applies := True;
4759                return;
4760
4761             --  If inlining is not possible, for now do not treat as an error
4762
4763             elsif Inlining_Not_Possible (Subp) then
4764                Applies := True;
4765                return;
4766
4767             --  Here we have a candidate for inlining, but we must exclude
4768             --  derived operations. Otherwise we would end up trying to inline
4769             --  a phantom declaration, and the result would be to drag in a
4770             --  body which has no direct inlining associated with it. That
4771             --  would not only be inefficient but would also result in the
4772             --  backend doing cross-unit inlining in cases where it was
4773             --  definitely inappropriate to do so.
4774
4775             --  However, a simple Comes_From_Source test is insufficient, since
4776             --  we do want to allow inlining of generic instances which also do
4777             --  not come from source. We also need to recognize specs generated
4778             --  by the front-end for bodies that carry the pragma. Finally,
4779             --  predefined operators do not come from source but are not
4780             --  inlineable either.
4781
4782             elsif Is_Generic_Instance (Subp)
4783               or else Nkind (Parent (Parent (Subp))) = N_Subprogram_Declaration
4784             then
4785                null;
4786
4787             elsif not Comes_From_Source (Subp)
4788               and then Scope (Subp) /= Standard_Standard
4789             then
4790                Applies := True;
4791                return;
4792             end if;
4793
4794             --  The referenced entity must either be the enclosing entity, or
4795             --  an entity declared within the current open scope.
4796
4797             if Present (Scope (Subp))
4798               and then Scope (Subp) /= Current_Scope
4799               and then Subp /= Current_Scope
4800             then
4801                Error_Pragma_Arg
4802                  ("argument of% must be entity in current scope", Assoc);
4803                return;
4804             end if;
4805
4806             --  Processing for procedure, operator or function. If subprogram
4807             --  is aliased (as for an instance) indicate that the renamed
4808             --  entity (if declared in the same unit) is inlined.
4809
4810             if Is_Subprogram (Subp) then
4811                Inner_Subp := Ultimate_Alias (Inner_Subp);
4812
4813                if In_Same_Source_Unit (Subp, Inner_Subp) then
4814                   Set_Inline_Flags (Inner_Subp);
4815
4816                   Decl := Parent (Parent (Inner_Subp));
4817
4818                   if Nkind (Decl) = N_Subprogram_Declaration
4819                     and then Present (Corresponding_Body (Decl))
4820                   then
4821                      Set_Inline_Flags (Corresponding_Body (Decl));
4822
4823                   elsif Is_Generic_Instance (Subp) then
4824
4825                      --  Indicate that the body needs to be created for
4826                      --  inlining subsequent calls. The instantiation node
4827                      --  follows the declaration of the wrapper package
4828                      --  created for it.
4829
4830                      if Scope (Subp) /= Standard_Standard
4831                        and then
4832                          Need_Subprogram_Instance_Body
4833                           (Next (Unit_Declaration_Node (Scope (Alias (Subp)))),
4834                               Subp)
4835                      then
4836                         null;
4837                      end if;
4838
4839                   --  Inline is a program unit pragma (RM 10.1.5) and cannot
4840                   --  appear in a formal part to apply to a formal subprogram.
4841                   --  Do not apply check within an instance or a formal package
4842                   --  the test will have been applied to the original generic.
4843
4844                   elsif Nkind (Decl) in N_Formal_Subprogram_Declaration
4845                     and then List_Containing (Decl) = List_Containing (N)
4846                     and then not In_Instance
4847                   then
4848                      Error_Msg_N
4849                        ("Inline cannot apply to a formal subprogram", N);
4850                   end if;
4851                end if;
4852
4853                Applies := True;
4854
4855             --  For a generic subprogram set flag as well, for use at the point
4856             --  of instantiation, to determine whether the body should be
4857             --  generated.
4858
4859             elsif Is_Generic_Subprogram (Subp) then
4860                Set_Inline_Flags (Subp);
4861                Applies := True;
4862
4863             --  Literals are by definition inlined
4864
4865             elsif Kind = E_Enumeration_Literal then
4866                null;
4867
4868             --  Anything else is an error
4869
4870             else
4871                Error_Pragma_Arg
4872                  ("expect subprogram name for pragma%", Assoc);
4873             end if;
4874          end Make_Inline;
4875
4876          ----------------------
4877          -- Set_Inline_Flags --
4878          ----------------------
4879
4880          procedure Set_Inline_Flags (Subp : Entity_Id) is
4881          begin
4882             if Active then
4883                Set_Is_Inlined (Subp);
4884             end if;
4885
4886             if not Has_Pragma_Inline (Subp) then
4887                Set_Has_Pragma_Inline (Subp);
4888                Effective := True;
4889             end if;
4890
4891             if Prag_Id = Pragma_Inline_Always then
4892                Set_Has_Pragma_Inline_Always (Subp);
4893             end if;
4894          end Set_Inline_Flags;
4895
4896       --  Start of processing for Process_Inline
4897
4898       begin
4899          Check_No_Identifiers;
4900          Check_At_Least_N_Arguments (1);
4901
4902          if Active then
4903             Inline_Processing_Required := True;
4904          end if;
4905
4906          Assoc := Arg1;
4907          while Present (Assoc) loop
4908             Subp_Id := Get_Pragma_Arg (Assoc);
4909             Analyze (Subp_Id);
4910             Applies := False;
4911
4912             if Is_Entity_Name (Subp_Id) then
4913                Subp := Entity (Subp_Id);
4914
4915                if Subp = Any_Id then
4916
4917                   --  If previous error, avoid cascaded errors
4918
4919                   Applies := True;
4920                   Effective := True;
4921
4922                else
4923                   Make_Inline (Subp);
4924
4925                   --  For the pragma case, climb homonym chain. This is
4926                   --  what implements allowing the pragma in the renaming
4927                   --  case, with the result applying to the ancestors, and
4928                   --  also allows Inline to apply to all previous homonyms.
4929
4930                   if not From_Aspect_Specification (N) then
4931                      while Present (Homonym (Subp))
4932                        and then Scope (Homonym (Subp)) = Current_Scope
4933                      loop
4934                         Make_Inline (Homonym (Subp));
4935                         Subp := Homonym (Subp);
4936                      end loop;
4937                   end if;
4938                end if;
4939             end if;
4940
4941             if not Applies then
4942                Error_Pragma_Arg
4943                  ("inappropriate argument for pragma%", Assoc);
4944
4945             elsif not Effective
4946               and then Warn_On_Redundant_Constructs
4947               and then not Suppress_All_Inlining
4948             then
4949                if Inlining_Not_Possible (Subp) then
4950                   Error_Msg_NE
4951                     ("pragma Inline for& is ignored?", N, Entity (Subp_Id));
4952                else
4953                   Error_Msg_NE
4954                     ("pragma Inline for& is redundant?", N, Entity (Subp_Id));
4955                end if;
4956             end if;
4957
4958             Next (Assoc);
4959          end loop;
4960       end Process_Inline;
4961
4962       ----------------------------
4963       -- Process_Interface_Name --
4964       ----------------------------
4965
4966       procedure Process_Interface_Name
4967         (Subprogram_Def : Entity_Id;
4968          Ext_Arg        : Node_Id;
4969          Link_Arg       : Node_Id)
4970       is
4971          Ext_Nam    : Node_Id;
4972          Link_Nam   : Node_Id;
4973          String_Val : String_Id;
4974
4975          procedure Check_Form_Of_Interface_Name
4976            (SN            : Node_Id;
4977             Ext_Name_Case : Boolean);
4978          --  SN is a string literal node for an interface name. This routine
4979          --  performs some minimal checks that the name is reasonable. In
4980          --  particular that no spaces or other obviously incorrect characters
4981          --  appear. This is only a warning, since any characters are allowed.
4982          --  Ext_Name_Case is True for an External_Name, False for a Link_Name.
4983
4984          ----------------------------------
4985          -- Check_Form_Of_Interface_Name --
4986          ----------------------------------
4987
4988          procedure Check_Form_Of_Interface_Name
4989            (SN            : Node_Id;
4990             Ext_Name_Case : Boolean)
4991          is
4992             S  : constant String_Id := Strval (Expr_Value_S (SN));
4993             SL : constant Nat       := String_Length (S);
4994             C  : Char_Code;
4995
4996          begin
4997             if SL = 0 then
4998                Error_Msg_N ("interface name cannot be null string", SN);
4999             end if;
5000
5001             for J in 1 .. SL loop
5002                C := Get_String_Char (S, J);
5003
5004                --  Look for dubious character and issue unconditional warning.
5005                --  Definitely dubious if not in character range.
5006
5007                if not In_Character_Range (C)
5008
5009                   --  For all cases except CLI target,
5010                   --  commas, spaces and slashes are dubious (in CLI, we use
5011                   --  commas and backslashes in external names to specify
5012                   --  assembly version and public key, while slashes and spaces
5013                   --  can be used in names to mark nested classes and
5014                   --  valuetypes).
5015
5016                   or else ((not Ext_Name_Case or else VM_Target /= CLI_Target)
5017                              and then (Get_Character (C) = ','
5018                                          or else
5019                                        Get_Character (C) = '\'))
5020                  or else (VM_Target /= CLI_Target
5021                             and then (Get_Character (C) = ' '
5022                                         or else
5023                                       Get_Character (C) = '/'))
5024                then
5025                   Error_Msg
5026                     ("?interface name contains illegal character",
5027                      Sloc (SN) + Source_Ptr (J));
5028                end if;
5029             end loop;
5030          end Check_Form_Of_Interface_Name;
5031
5032       --  Start of processing for Process_Interface_Name
5033
5034       begin
5035          if No (Link_Arg) then
5036             if No (Ext_Arg) then
5037                if VM_Target = CLI_Target
5038                  and then Ekind (Subprogram_Def) = E_Package
5039                  and then Nkind (Parent (Subprogram_Def)) =
5040                                                  N_Package_Specification
5041                  and then Present (Generic_Parent (Parent (Subprogram_Def)))
5042                then
5043                   Set_Interface_Name
5044                      (Subprogram_Def,
5045                       Interface_Name
5046                         (Generic_Parent (Parent (Subprogram_Def))));
5047                end if;
5048
5049                return;
5050
5051             elsif Chars (Ext_Arg) = Name_Link_Name then
5052                Ext_Nam  := Empty;
5053                Link_Nam := Expression (Ext_Arg);
5054
5055             else
5056                Check_Optional_Identifier (Ext_Arg, Name_External_Name);
5057                Ext_Nam  := Expression (Ext_Arg);
5058                Link_Nam := Empty;
5059             end if;
5060
5061          else
5062             Check_Optional_Identifier (Ext_Arg,  Name_External_Name);
5063             Check_Optional_Identifier (Link_Arg, Name_Link_Name);
5064             Ext_Nam  := Expression (Ext_Arg);
5065             Link_Nam := Expression (Link_Arg);
5066          end if;
5067
5068          --  Check expressions for external name and link name are static
5069
5070          if Present (Ext_Nam) then
5071             Check_Arg_Is_Static_Expression (Ext_Nam, Standard_String);
5072             Check_Form_Of_Interface_Name (Ext_Nam, Ext_Name_Case => True);
5073
5074             --  Verify that external name is not the name of a local entity,
5075             --  which would hide the imported one and could lead to run-time
5076             --  surprises. The problem can only arise for entities declared in
5077             --  a package body (otherwise the external name is fully qualified
5078             --  and will not conflict).
5079
5080             declare
5081                Nam : Name_Id;
5082                E   : Entity_Id;
5083                Par : Node_Id;
5084
5085             begin
5086                if Prag_Id = Pragma_Import then
5087                   String_To_Name_Buffer (Strval (Expr_Value_S (Ext_Nam)));
5088                   Nam := Name_Find;
5089                   E   := Entity_Id (Get_Name_Table_Info (Nam));
5090
5091                   if Nam /= Chars (Subprogram_Def)
5092                     and then Present (E)
5093                     and then not Is_Overloadable (E)
5094                     and then Is_Immediately_Visible (E)
5095                     and then not Is_Imported (E)
5096                     and then Ekind (Scope (E)) = E_Package
5097                   then
5098                      Par := Parent (E);
5099                      while Present (Par) loop
5100                         if Nkind (Par) = N_Package_Body then
5101                            Error_Msg_Sloc := Sloc (E);
5102                            Error_Msg_NE
5103                              ("imported entity is hidden by & declared#",
5104                               Ext_Arg, E);
5105                            exit;
5106                         end if;
5107
5108                         Par := Parent (Par);
5109                      end loop;
5110                   end if;
5111                end if;
5112             end;
5113          end if;
5114
5115          if Present (Link_Nam) then
5116             Check_Arg_Is_Static_Expression (Link_Nam, Standard_String);
5117             Check_Form_Of_Interface_Name (Link_Nam, Ext_Name_Case => False);
5118          end if;
5119
5120          --  If there is no link name, just set the external name
5121
5122          if No (Link_Nam) then
5123             Link_Nam := Adjust_External_Name_Case (Expr_Value_S (Ext_Nam));
5124
5125          --  For the Link_Name case, the given literal is preceded by an
5126          --  asterisk, which indicates to GCC that the given name should be
5127          --  taken literally, and in particular that no prepending of
5128          --  underlines should occur, even in systems where this is the
5129          --  normal default.
5130
5131          else
5132             Start_String;
5133
5134             if VM_Target = No_VM then
5135                Store_String_Char (Get_Char_Code ('*'));
5136             end if;
5137
5138             String_Val := Strval (Expr_Value_S (Link_Nam));
5139             Store_String_Chars (String_Val);
5140             Link_Nam :=
5141               Make_String_Literal (Sloc (Link_Nam),
5142                 Strval => End_String);
5143          end if;
5144
5145          --  Set the interface name. If the entity is a generic instance, use
5146          --  its alias, which is the callable entity.
5147
5148          if Is_Generic_Instance (Subprogram_Def) then
5149             Set_Encoded_Interface_Name
5150               (Alias (Get_Base_Subprogram (Subprogram_Def)), Link_Nam);
5151          else
5152             Set_Encoded_Interface_Name
5153               (Get_Base_Subprogram (Subprogram_Def), Link_Nam);
5154          end if;
5155
5156          --  We allow duplicated export names in CIL/Java, as they are always
5157          --  enclosed in a namespace that differentiates them, and overloaded
5158          --  entities are supported by the VM.
5159
5160          if Convention (Subprogram_Def) /= Convention_CIL
5161               and then
5162             Convention (Subprogram_Def) /= Convention_Java
5163          then
5164             Check_Duplicated_Export_Name (Link_Nam);
5165          end if;
5166       end Process_Interface_Name;
5167
5168       -----------------------------------------
5169       -- Process_Interrupt_Or_Attach_Handler --
5170       -----------------------------------------
5171
5172       procedure Process_Interrupt_Or_Attach_Handler is
5173          Arg1_X       : constant Node_Id   := Get_Pragma_Arg (Arg1);
5174          Handler_Proc : constant Entity_Id := Entity (Arg1_X);
5175          Proc_Scope   : constant Entity_Id := Scope (Handler_Proc);
5176
5177       begin
5178          Set_Is_Interrupt_Handler (Handler_Proc);
5179
5180          --  If the pragma is not associated with a handler procedure within a
5181          --  protected type, then it must be for a nonprotected procedure for
5182          --  the AAMP target, in which case we don't associate a representation
5183          --  item with the procedure's scope.
5184
5185          if Ekind (Proc_Scope) = E_Protected_Type then
5186             if Prag_Id = Pragma_Interrupt_Handler
5187                  or else
5188                Prag_Id = Pragma_Attach_Handler
5189             then
5190                Record_Rep_Item (Proc_Scope, N);
5191             end if;
5192          end if;
5193       end Process_Interrupt_Or_Attach_Handler;
5194
5195       --------------------------------------------------
5196       -- Process_Restrictions_Or_Restriction_Warnings --
5197       --------------------------------------------------
5198
5199       --  Note: some of the simple identifier cases were handled in par-prag,
5200       --  but it is harmless (and more straightforward) to simply handle all
5201       --  cases here, even if it means we repeat a bit of work in some cases.
5202
5203       procedure Process_Restrictions_Or_Restriction_Warnings
5204         (Warn : Boolean)
5205       is
5206          Arg   : Node_Id;
5207          R_Id  : Restriction_Id;
5208          Id    : Name_Id;
5209          Expr  : Node_Id;
5210          Val   : Uint;
5211
5212          procedure Check_Unit_Name (N : Node_Id);
5213          --  Checks unit name parameter for No_Dependence. Returns if it has
5214          --  an appropriate form, otherwise raises pragma argument error.
5215
5216          ---------------------
5217          -- Check_Unit_Name --
5218          ---------------------
5219
5220          procedure Check_Unit_Name (N : Node_Id) is
5221          begin
5222             if Nkind (N) = N_Selected_Component then
5223                Check_Unit_Name (Prefix (N));
5224                Check_Unit_Name (Selector_Name (N));
5225
5226             elsif Nkind (N) = N_Identifier then
5227                return;
5228
5229             else
5230                Error_Pragma_Arg
5231                  ("wrong form for unit name for No_Dependence", N);
5232             end if;
5233          end Check_Unit_Name;
5234
5235       --  Start of processing for Process_Restrictions_Or_Restriction_Warnings
5236
5237       begin
5238          --  Ignore all Restrictions pragma in CodePeer mode
5239
5240          if CodePeer_Mode then
5241             return;
5242          end if;
5243
5244          Check_Ada_83_Warning;
5245          Check_At_Least_N_Arguments (1);
5246          Check_Valid_Configuration_Pragma;
5247
5248          Arg := Arg1;
5249          while Present (Arg) loop
5250             Id := Chars (Arg);
5251             Expr := Get_Pragma_Arg (Arg);
5252
5253             --  Case of no restriction identifier present
5254
5255             if Id = No_Name then
5256                if Nkind (Expr) /= N_Identifier then
5257                   Error_Pragma_Arg
5258                     ("invalid form for restriction", Arg);
5259                end if;
5260
5261                R_Id :=
5262                  Get_Restriction_Id
5263                    (Process_Restriction_Synonyms (Expr));
5264
5265                if R_Id not in All_Boolean_Restrictions then
5266                   Error_Msg_Name_1 := Pname;
5267                   Error_Msg_N
5268                     ("invalid restriction identifier&", Get_Pragma_Arg (Arg));
5269
5270                   --  Check for possible misspelling
5271
5272                   for J in Restriction_Id loop
5273                      declare
5274                         Rnm : constant String := Restriction_Id'Image (J);
5275
5276                      begin
5277                         Name_Buffer (1 .. Rnm'Length) := Rnm;
5278                         Name_Len := Rnm'Length;
5279                         Set_Casing (All_Lower_Case);
5280
5281                         if Is_Bad_Spelling_Of (Chars (Expr), Name_Enter) then
5282                            Set_Casing
5283                              (Identifier_Casing (Current_Source_File));
5284                            Error_Msg_String (1 .. Rnm'Length) :=
5285                              Name_Buffer (1 .. Name_Len);
5286                            Error_Msg_Strlen := Rnm'Length;
5287                            Error_Msg_N -- CODEFIX
5288                              ("\possible misspelling of ""~""",
5289                               Get_Pragma_Arg (Arg));
5290                            exit;
5291                         end if;
5292                      end;
5293                   end loop;
5294
5295                   raise Pragma_Exit;
5296                end if;
5297
5298                if Implementation_Restriction (R_Id) then
5299                   Check_Restriction (No_Implementation_Restrictions, Arg);
5300                end if;
5301
5302                --  If this is a warning, then set the warning unless we already
5303                --  have a real restriction active (we never want a warning to
5304                --  override a real restriction).
5305
5306                if Warn then
5307                   if not Restriction_Active (R_Id) then
5308                      Set_Restriction (R_Id, N);
5309                      Restriction_Warnings (R_Id) := True;
5310                   end if;
5311
5312                --  If real restriction case, then set it and make sure that the
5313                --  restriction warning flag is off, since a real restriction
5314                --  always overrides a warning.
5315
5316                else
5317                   Set_Restriction (R_Id, N);
5318                   Restriction_Warnings (R_Id) := False;
5319                end if;
5320
5321                --  Check for obsolescent restrictions in Ada 2005 mode
5322
5323                if not Warn
5324                  and then Ada_Version >= Ada_2005
5325                  and then (R_Id = No_Asynchronous_Control
5326                             or else
5327                            R_Id = No_Unchecked_Deallocation
5328                             or else
5329                            R_Id = No_Unchecked_Conversion)
5330                then
5331                   Check_Restriction (No_Obsolescent_Features, N);
5332                end if;
5333
5334                --  A very special case that must be processed here: pragma
5335                --  Restrictions (No_Exceptions) turns off all run-time
5336                --  checking. This is a bit dubious in terms of the formal
5337                --  language definition, but it is what is intended by RM
5338                --  H.4(12). Restriction_Warnings never affects generated code
5339                --  so this is done only in the real restriction case.
5340
5341                --  Atomic_Synchronization is not a real check, so it is not
5342                --  affected by this processing).
5343
5344                if R_Id = No_Exceptions and then not Warn then
5345                   for J in Scope_Suppress'Range loop
5346                      if J /= Atomic_Synchronization then
5347                         Scope_Suppress (J) := True;
5348                      end if;
5349                   end loop;
5350                end if;
5351
5352             --  Case of No_Dependence => unit-name. Note that the parser
5353             --  already made the necessary entry in the No_Dependence table.
5354
5355             elsif Id = Name_No_Dependence then
5356                Check_Unit_Name (Expr);
5357
5358             --  Case of No_Specification_Of_Aspect => Identifier.
5359
5360             elsif Id = Name_No_Specification_Of_Aspect then
5361                declare
5362                   A_Id : Aspect_Id;
5363
5364                begin
5365                   if Nkind (Expr) /= N_Identifier then
5366                      A_Id := No_Aspect;
5367                   else
5368                      A_Id := Get_Aspect_Id (Chars (Expr));
5369                   end if;
5370
5371                   if A_Id = No_Aspect then
5372                      Error_Pragma_Arg ("invalid restriction name", Arg);
5373                   else
5374                      Set_Restriction_No_Specification_Of_Aspect (Expr, Warn);
5375                   end if;
5376                end;
5377
5378             --  All other cases of restriction identifier present
5379
5380             else
5381                R_Id := Get_Restriction_Id (Process_Restriction_Synonyms (Arg));
5382                Analyze_And_Resolve (Expr, Any_Integer);
5383
5384                if R_Id not in All_Parameter_Restrictions then
5385                   Error_Pragma_Arg
5386                     ("invalid restriction parameter identifier", Arg);
5387
5388                elsif not Is_OK_Static_Expression (Expr) then
5389                   Flag_Non_Static_Expr
5390                     ("value must be static expression!", Expr);
5391                   raise Pragma_Exit;
5392
5393                elsif not Is_Integer_Type (Etype (Expr))
5394                  or else Expr_Value (Expr) < 0
5395                then
5396                   Error_Pragma_Arg
5397                     ("value must be non-negative integer", Arg);
5398                end if;
5399
5400                --  Restriction pragma is active
5401
5402                Val := Expr_Value (Expr);
5403
5404                if not UI_Is_In_Int_Range (Val) then
5405                   Error_Pragma_Arg
5406                     ("pragma ignored, value too large?", Arg);
5407                end if;
5408
5409                --  Warning case. If the real restriction is active, then we
5410                --  ignore the request, since warning never overrides a real
5411                --  restriction. Otherwise we set the proper warning. Note that
5412                --  this circuit sets the warning again if it is already set,
5413                --  which is what we want, since the constant may have changed.
5414
5415                if Warn then
5416                   if not Restriction_Active (R_Id) then
5417                      Set_Restriction
5418                        (R_Id, N, Integer (UI_To_Int (Val)));
5419                      Restriction_Warnings (R_Id) := True;
5420                   end if;
5421
5422                --  Real restriction case, set restriction and make sure warning
5423                --  flag is off since real restriction always overrides warning.
5424
5425                else
5426                   Set_Restriction (R_Id, N, Integer (UI_To_Int (Val)));
5427                   Restriction_Warnings (R_Id) := False;
5428                end if;
5429             end if;
5430
5431             Next (Arg);
5432          end loop;
5433       end Process_Restrictions_Or_Restriction_Warnings;
5434
5435       ---------------------------------
5436       -- Process_Suppress_Unsuppress --
5437       ---------------------------------
5438
5439       --  Note: this procedure makes entries in the check suppress data
5440       --  structures managed by Sem. See spec of package Sem for full
5441       --  details on how we handle recording of check suppression.
5442
5443       procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean) is
5444          C    : Check_Id;
5445          E_Id : Node_Id;
5446          E    : Entity_Id;
5447
5448          In_Package_Spec : constant Boolean :=
5449                              Is_Package_Or_Generic_Package (Current_Scope)
5450                                and then not In_Package_Body (Current_Scope);
5451
5452          procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id);
5453          --  Used to suppress a single check on the given entity
5454
5455          --------------------------------
5456          -- Suppress_Unsuppress_Echeck --
5457          --------------------------------
5458
5459          procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id) is
5460          begin
5461             --  Check for error of trying to set atomic synchronization for
5462             --  a non-atomic variable.
5463
5464             if C = Atomic_Synchronization
5465               and then not Is_Atomic (E)
5466             then
5467                Error_Msg_N
5468                  ("pragma & requires atomic variable",
5469                   Pragma_Identifier (Original_Node (N)));
5470             end if;
5471
5472             Set_Checks_May_Be_Suppressed (E);
5473
5474             if In_Package_Spec then
5475                Push_Global_Suppress_Stack_Entry
5476                  (Entity   => E,
5477                   Check    => C,
5478                   Suppress => Suppress_Case);
5479             else
5480                Push_Local_Suppress_Stack_Entry
5481                  (Entity   => E,
5482                   Check    => C,
5483                   Suppress => Suppress_Case);
5484             end if;
5485
5486             --  If this is a first subtype, and the base type is distinct,
5487             --  then also set the suppress flags on the base type.
5488
5489             if Is_First_Subtype (E)
5490               and then Etype (E) /= E
5491             then
5492                Suppress_Unsuppress_Echeck (Etype (E), C);
5493             end if;
5494          end Suppress_Unsuppress_Echeck;
5495
5496       --  Start of processing for Process_Suppress_Unsuppress
5497
5498       begin
5499          --  Ignore pragma Suppress/Unsuppress in CodePeer and Alfa modes on
5500          --  user code: we want to generate checks for analysis purposes, as
5501          --  set respectively by -gnatC and -gnatd.F
5502
5503          if (CodePeer_Mode or Alfa_Mode)
5504            and then Comes_From_Source (N)
5505          then
5506             return;
5507          end if;
5508
5509          --  Suppress/Unsuppress can appear as a configuration pragma, or in a
5510          --  declarative part or a package spec (RM 11.5(5)).
5511
5512          if not Is_Configuration_Pragma then
5513             Check_Is_In_Decl_Part_Or_Package_Spec;
5514          end if;
5515
5516          Check_At_Least_N_Arguments (1);
5517          Check_At_Most_N_Arguments (2);
5518          Check_No_Identifier (Arg1);
5519          Check_Arg_Is_Identifier (Arg1);
5520
5521          C := Get_Check_Id (Chars (Get_Pragma_Arg (Arg1)));
5522
5523          if C = No_Check_Id then
5524             Error_Pragma_Arg
5525               ("argument of pragma% is not valid check name", Arg1);
5526          end if;
5527
5528          if not Suppress_Case
5529            and then (C = All_Checks or else C = Overflow_Check)
5530          then
5531             Opt.Overflow_Checks_Unsuppressed := True;
5532          end if;
5533
5534          if Arg_Count = 1 then
5535
5536             --  Make an entry in the local scope suppress table. This is the
5537             --  table that directly shows the current value of the scope
5538             --  suppress check for any check id value.
5539
5540             if C = All_Checks then
5541
5542                --  For All_Checks, we set all specific predefined checks with
5543                --  the exception of Elaboration_Check, which is handled
5544                --  specially because of not wanting All_Checks to have the
5545                --  effect of deactivating static elaboration order processing.
5546                --  Atomic_Synchronization is also not affected, since this is
5547                --  not a real check.
5548
5549                for J in Scope_Suppress'Range loop
5550                   if J /= Elaboration_Check
5551                     and then J /= Atomic_Synchronization
5552                   then
5553                      Scope_Suppress (J) := Suppress_Case;
5554                   end if;
5555                end loop;
5556
5557             --  If not All_Checks, and predefined check, then set appropriate
5558             --  scope entry. Note that we will set Elaboration_Check if this
5559             --  is explicitly specified. Atomic_Synchronization is allowed
5560             --  only if internally generated and entity is atomic.
5561
5562             elsif C in Predefined_Check_Id
5563               and then (not Comes_From_Source (N)
5564                          or else C /= Atomic_Synchronization)
5565             then
5566                Scope_Suppress (C) := Suppress_Case;
5567             end if;
5568
5569             --  Also make an entry in the Local_Entity_Suppress table
5570
5571             Push_Local_Suppress_Stack_Entry
5572               (Entity   => Empty,
5573                Check    => C,
5574                Suppress => Suppress_Case);
5575
5576          --  Case of two arguments present, where the check is suppressed for
5577          --  a specified entity (given as the second argument of the pragma)
5578
5579          else
5580             --  This is obsolescent in Ada 2005 mode
5581
5582             if Ada_Version >= Ada_2005 then
5583                Check_Restriction (No_Obsolescent_Features, Arg2);
5584             end if;
5585
5586             Check_Optional_Identifier (Arg2, Name_On);
5587             E_Id := Get_Pragma_Arg (Arg2);
5588             Analyze (E_Id);
5589
5590             if not Is_Entity_Name (E_Id) then
5591                Error_Pragma_Arg
5592                  ("second argument of pragma% must be entity name", Arg2);
5593             end if;
5594
5595             E := Entity (E_Id);
5596
5597             if E = Any_Id then
5598                return;
5599             end if;
5600
5601             --  Enforce RM 11.5(7) which requires that for a pragma that
5602             --  appears within a package spec, the named entity must be
5603             --  within the package spec. We allow the package name itself
5604             --  to be mentioned since that makes sense, although it is not
5605             --  strictly allowed by 11.5(7).
5606
5607             if In_Package_Spec
5608               and then E /= Current_Scope
5609               and then Scope (E) /= Current_Scope
5610             then
5611                Error_Pragma_Arg
5612                  ("entity in pragma% is not in package spec (RM 11.5(7))",
5613                   Arg2);
5614             end if;
5615
5616             --  Loop through homonyms. As noted below, in the case of a package
5617             --  spec, only homonyms within the package spec are considered.
5618
5619             loop
5620                Suppress_Unsuppress_Echeck (E, C);
5621
5622                if Is_Generic_Instance (E)
5623                  and then Is_Subprogram (E)
5624                  and then Present (Alias (E))
5625                then
5626                   Suppress_Unsuppress_Echeck (Alias (E), C);
5627                end if;
5628
5629                --  Move to next homonym if not aspect spec case
5630
5631                exit when From_Aspect_Specification (N);
5632                E := Homonym (E);
5633                exit when No (E);
5634
5635                --  If we are within a package specification, the pragma only
5636                --  applies to homonyms in the same scope.
5637
5638                exit when In_Package_Spec
5639                  and then Scope (E) /= Current_Scope;
5640             end loop;
5641          end if;
5642       end Process_Suppress_Unsuppress;
5643
5644       ------------------
5645       -- Set_Exported --
5646       ------------------
5647
5648       procedure Set_Exported (E : Entity_Id; Arg : Node_Id) is
5649       begin
5650          if Is_Imported (E) then
5651             Error_Pragma_Arg
5652               ("cannot export entity& that was previously imported", Arg);
5653
5654          elsif Present (Address_Clause (E)) and then not CodePeer_Mode then
5655             Error_Pragma_Arg
5656               ("cannot export entity& that has an address clause", Arg);
5657          end if;
5658
5659          Set_Is_Exported (E);
5660
5661          --  Generate a reference for entity explicitly, because the
5662          --  identifier may be overloaded and name resolution will not
5663          --  generate one.
5664
5665          Generate_Reference (E, Arg);
5666
5667          --  Deal with exporting non-library level entity
5668
5669          if not Is_Library_Level_Entity (E) then
5670
5671             --  Not allowed at all for subprograms
5672
5673             if Is_Subprogram (E) then
5674                Error_Pragma_Arg ("local subprogram& cannot be exported", Arg);
5675
5676             --  Otherwise set public and statically allocated
5677
5678             else
5679                Set_Is_Public (E);
5680                Set_Is_Statically_Allocated (E);
5681
5682                --  Warn if the corresponding W flag is set and the pragma comes
5683                --  from source. The latter may not be true e.g. on VMS where we
5684                --  expand export pragmas for exception codes associated with
5685                --  imported or exported exceptions. We do not want to generate
5686                --  a warning for something that the user did not write.
5687
5688                if Warn_On_Export_Import
5689                  and then Comes_From_Source (Arg)
5690                then
5691                   Error_Msg_NE
5692                     ("?& has been made static as a result of Export", Arg, E);
5693                   Error_Msg_N
5694                     ("\this usage is non-standard and non-portable", Arg);
5695                end if;
5696             end if;
5697          end if;
5698
5699          if Warn_On_Export_Import and then Is_Type (E) then
5700             Error_Msg_NE ("exporting a type has no effect?", Arg, E);
5701          end if;
5702
5703          if Warn_On_Export_Import and Inside_A_Generic then
5704             Error_Msg_NE
5705               ("all instances of& will have the same external name?", Arg, E);
5706          end if;
5707       end Set_Exported;
5708
5709       ----------------------------------------------
5710       -- Set_Extended_Import_Export_External_Name --
5711       ----------------------------------------------
5712
5713       procedure Set_Extended_Import_Export_External_Name
5714         (Internal_Ent : Entity_Id;
5715          Arg_External : Node_Id)
5716       is
5717          Old_Name : constant Node_Id := Interface_Name (Internal_Ent);
5718          New_Name : Node_Id;
5719
5720       begin
5721          if No (Arg_External) then
5722             return;
5723          end if;
5724
5725          Check_Arg_Is_External_Name (Arg_External);
5726
5727          if Nkind (Arg_External) = N_String_Literal then
5728             if String_Length (Strval (Arg_External)) = 0 then
5729                return;
5730             else
5731                New_Name := Adjust_External_Name_Case (Arg_External);
5732             end if;
5733
5734          elsif Nkind (Arg_External) = N_Identifier then
5735             New_Name := Get_Default_External_Name (Arg_External);
5736
5737          --  Check_Arg_Is_External_Name should let through only identifiers and
5738          --  string literals or static string expressions (which are folded to
5739          --  string literals).
5740
5741          else
5742             raise Program_Error;
5743          end if;
5744
5745          --  If we already have an external name set (by a prior normal Import
5746          --  or Export pragma), then the external names must match
5747
5748          if Present (Interface_Name (Internal_Ent)) then
5749             Check_Matching_Internal_Names : declare
5750                S1 : constant String_Id := Strval (Old_Name);
5751                S2 : constant String_Id := Strval (New_Name);
5752
5753                procedure Mismatch;
5754                --  Called if names do not match
5755
5756                --------------
5757                -- Mismatch --
5758                --------------
5759
5760                procedure Mismatch is
5761                begin
5762                   Error_Msg_Sloc := Sloc (Old_Name);
5763                   Error_Pragma_Arg
5764                     ("external name does not match that given #",
5765                      Arg_External);
5766                end Mismatch;
5767
5768             --  Start of processing for Check_Matching_Internal_Names
5769
5770             begin
5771                if String_Length (S1) /= String_Length (S2) then
5772                   Mismatch;
5773
5774                else
5775                   for J in 1 .. String_Length (S1) loop
5776                      if Get_String_Char (S1, J) /= Get_String_Char (S2, J) then
5777                         Mismatch;
5778                      end if;
5779                   end loop;
5780                end if;
5781             end Check_Matching_Internal_Names;
5782
5783          --  Otherwise set the given name
5784
5785          else
5786             Set_Encoded_Interface_Name (Internal_Ent, New_Name);
5787             Check_Duplicated_Export_Name (New_Name);
5788          end if;
5789       end Set_Extended_Import_Export_External_Name;
5790
5791       ------------------
5792       -- Set_Imported --
5793       ------------------
5794
5795       procedure Set_Imported (E : Entity_Id) is
5796       begin
5797          --  Error message if already imported or exported
5798
5799          if Is_Exported (E) or else Is_Imported (E) then
5800
5801             --  Error if being set Exported twice
5802
5803             if Is_Exported (E) then
5804                Error_Msg_NE ("entity& was previously exported", N, E);
5805
5806             --  OK if Import/Interface case
5807
5808             elsif Import_Interface_Present (N) then
5809                goto OK;
5810
5811             --  Error if being set Imported twice
5812
5813             else
5814                Error_Msg_NE ("entity& was previously imported", N, E);
5815             end if;
5816
5817             Error_Msg_Name_1 := Pname;
5818             Error_Msg_N
5819               ("\(pragma% applies to all previous entities)", N);
5820
5821             Error_Msg_Sloc  := Sloc (E);
5822             Error_Msg_NE ("\import not allowed for& declared#", N, E);
5823
5824          --  Here if not previously imported or exported, OK to import
5825
5826          else
5827             Set_Is_Imported (E);
5828
5829             --  If the entity is an object that is not at the library level,
5830             --  then it is statically allocated. We do not worry about objects
5831             --  with address clauses in this context since they are not really
5832             --  imported in the linker sense.
5833
5834             if Is_Object (E)
5835               and then not Is_Library_Level_Entity (E)
5836               and then No (Address_Clause (E))
5837             then
5838                Set_Is_Statically_Allocated (E);
5839             end if;
5840          end if;
5841
5842          <<OK>> null;
5843       end Set_Imported;
5844
5845       -------------------------
5846       -- Set_Mechanism_Value --
5847       -------------------------
5848
5849       --  Note: the mechanism name has not been analyzed (and cannot indeed be
5850       --  analyzed, since it is semantic nonsense), so we get it in the exact
5851       --  form created by the parser.
5852
5853       procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id) is
5854          Class        : Node_Id;
5855          Param        : Node_Id;
5856          Mech_Name_Id : Name_Id;
5857
5858          procedure Bad_Class;
5859          --  Signal bad descriptor class name
5860
5861          procedure Bad_Mechanism;
5862          --  Signal bad mechanism name
5863
5864          ---------------
5865          -- Bad_Class --
5866          ---------------
5867
5868          procedure Bad_Class is
5869          begin
5870             Error_Pragma_Arg ("unrecognized descriptor class name", Class);
5871          end Bad_Class;
5872
5873          -------------------------
5874          -- Bad_Mechanism_Value --
5875          -------------------------
5876
5877          procedure Bad_Mechanism is
5878          begin
5879             Error_Pragma_Arg ("unrecognized mechanism name", Mech_Name);
5880          end Bad_Mechanism;
5881
5882       --  Start of processing for Set_Mechanism_Value
5883
5884       begin
5885          if Mechanism (Ent) /= Default_Mechanism then
5886             Error_Msg_NE
5887               ("mechanism for & has already been set", Mech_Name, Ent);
5888          end if;
5889
5890          --  MECHANISM_NAME ::= value | reference | descriptor |
5891          --                     short_descriptor
5892
5893          if Nkind (Mech_Name) = N_Identifier then
5894             if Chars (Mech_Name) = Name_Value then
5895                Set_Mechanism (Ent, By_Copy);
5896                return;
5897
5898             elsif Chars (Mech_Name) = Name_Reference then
5899                Set_Mechanism (Ent, By_Reference);
5900                return;
5901
5902             elsif Chars (Mech_Name) = Name_Descriptor then
5903                Check_VMS (Mech_Name);
5904
5905                --  Descriptor => Short_Descriptor if pragma was given
5906
5907                if Short_Descriptors then
5908                   Set_Mechanism (Ent, By_Short_Descriptor);
5909                else
5910                   Set_Mechanism (Ent, By_Descriptor);
5911                end if;
5912
5913                return;
5914
5915             elsif Chars (Mech_Name) = Name_Short_Descriptor then
5916                Check_VMS (Mech_Name);
5917                Set_Mechanism (Ent, By_Short_Descriptor);
5918                return;
5919
5920             elsif Chars (Mech_Name) = Name_Copy then
5921                Error_Pragma_Arg
5922                  ("bad mechanism name, Value assumed", Mech_Name);
5923
5924             else
5925                Bad_Mechanism;
5926             end if;
5927
5928          --  MECHANISM_NAME ::= descriptor (CLASS_NAME) |
5929          --                     short_descriptor (CLASS_NAME)
5930          --  CLASS_NAME     ::= ubs | ubsb | uba | s | sb | a | nca
5931
5932          --  Note: this form is parsed as an indexed component
5933
5934          elsif Nkind (Mech_Name) = N_Indexed_Component then
5935             Class := First (Expressions (Mech_Name));
5936
5937             if Nkind (Prefix (Mech_Name)) /= N_Identifier
5938              or else not (Chars (Prefix (Mech_Name)) = Name_Descriptor or else
5939                           Chars (Prefix (Mech_Name)) = Name_Short_Descriptor)
5940              or else Present (Next (Class))
5941             then
5942                Bad_Mechanism;
5943             else
5944                Mech_Name_Id := Chars (Prefix (Mech_Name));
5945
5946                --  Change Descriptor => Short_Descriptor if pragma was given
5947
5948                if Mech_Name_Id = Name_Descriptor
5949                  and then Short_Descriptors
5950                then
5951                   Mech_Name_Id := Name_Short_Descriptor;
5952                end if;
5953             end if;
5954
5955          --  MECHANISM_NAME ::= descriptor (Class => CLASS_NAME) |
5956          --                     short_descriptor (Class => CLASS_NAME)
5957          --  CLASS_NAME     ::= ubs | ubsb | uba | s | sb | a | nca
5958
5959          --  Note: this form is parsed as a function call
5960
5961          elsif Nkind (Mech_Name) = N_Function_Call then
5962             Param := First (Parameter_Associations (Mech_Name));
5963
5964             if Nkind (Name (Mech_Name)) /= N_Identifier
5965               or else not (Chars (Name (Mech_Name)) = Name_Descriptor or else
5966                            Chars (Name (Mech_Name)) = Name_Short_Descriptor)
5967               or else Present (Next (Param))
5968               or else No (Selector_Name (Param))
5969               or else Chars (Selector_Name (Param)) /= Name_Class
5970             then
5971                Bad_Mechanism;
5972             else
5973                Class := Explicit_Actual_Parameter (Param);
5974                Mech_Name_Id := Chars (Name (Mech_Name));
5975             end if;
5976
5977          else
5978             Bad_Mechanism;
5979          end if;
5980
5981          --  Fall through here with Class set to descriptor class name
5982
5983          Check_VMS (Mech_Name);
5984
5985          if Nkind (Class) /= N_Identifier then
5986             Bad_Class;
5987
5988          elsif Mech_Name_Id = Name_Descriptor
5989            and then Chars (Class) = Name_UBS
5990          then
5991             Set_Mechanism (Ent, By_Descriptor_UBS);
5992
5993          elsif Mech_Name_Id = Name_Descriptor
5994            and then Chars (Class) = Name_UBSB
5995          then
5996             Set_Mechanism (Ent, By_Descriptor_UBSB);
5997
5998          elsif Mech_Name_Id = Name_Descriptor
5999            and then Chars (Class) = Name_UBA
6000          then
6001             Set_Mechanism (Ent, By_Descriptor_UBA);
6002
6003          elsif Mech_Name_Id = Name_Descriptor
6004            and then Chars (Class) = Name_S
6005          then
6006             Set_Mechanism (Ent, By_Descriptor_S);
6007
6008          elsif Mech_Name_Id = Name_Descriptor
6009            and then Chars (Class) = Name_SB
6010          then
6011             Set_Mechanism (Ent, By_Descriptor_SB);
6012
6013          elsif Mech_Name_Id = Name_Descriptor
6014            and then Chars (Class) = Name_A
6015          then
6016             Set_Mechanism (Ent, By_Descriptor_A);
6017
6018          elsif Mech_Name_Id = Name_Descriptor
6019            and then Chars (Class) = Name_NCA
6020          then
6021             Set_Mechanism (Ent, By_Descriptor_NCA);
6022
6023          elsif Mech_Name_Id = Name_Short_Descriptor
6024            and then Chars (Class) = Name_UBS
6025          then
6026             Set_Mechanism (Ent, By_Short_Descriptor_UBS);
6027
6028          elsif Mech_Name_Id = Name_Short_Descriptor
6029            and then Chars (Class) = Name_UBSB
6030          then
6031             Set_Mechanism (Ent, By_Short_Descriptor_UBSB);
6032
6033          elsif Mech_Name_Id = Name_Short_Descriptor
6034            and then Chars (Class) = Name_UBA
6035          then
6036             Set_Mechanism (Ent, By_Short_Descriptor_UBA);
6037
6038          elsif Mech_Name_Id = Name_Short_Descriptor
6039            and then Chars (Class) = Name_S
6040          then
6041             Set_Mechanism (Ent, By_Short_Descriptor_S);
6042
6043          elsif Mech_Name_Id = Name_Short_Descriptor
6044            and then Chars (Class) = Name_SB
6045          then
6046             Set_Mechanism (Ent, By_Short_Descriptor_SB);
6047
6048          elsif Mech_Name_Id = Name_Short_Descriptor
6049            and then Chars (Class) = Name_A
6050          then
6051             Set_Mechanism (Ent, By_Short_Descriptor_A);
6052
6053          elsif Mech_Name_Id = Name_Short_Descriptor
6054            and then Chars (Class) = Name_NCA
6055          then
6056             Set_Mechanism (Ent, By_Short_Descriptor_NCA);
6057
6058          else
6059             Bad_Class;
6060          end if;
6061       end Set_Mechanism_Value;
6062
6063       ---------------------------
6064       -- Set_Ravenscar_Profile --
6065       ---------------------------
6066
6067       --  The tasks to be done here are
6068
6069       --    Set required policies
6070
6071       --      pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
6072       --      pragma Locking_Policy (Ceiling_Locking)
6073
6074       --    Set Detect_Blocking mode
6075
6076       --    Set required restrictions (see System.Rident for detailed list)
6077
6078       --    Set the No_Dependence rules
6079       --      No_Dependence => Ada.Asynchronous_Task_Control
6080       --      No_Dependence => Ada.Calendar
6081       --      No_Dependence => Ada.Execution_Time.Group_Budget
6082       --      No_Dependence => Ada.Execution_Time.Timers
6083       --      No_Dependence => Ada.Task_Attributes
6084       --      No_Dependence => System.Multiprocessors.Dispatching_Domains
6085
6086       procedure Set_Ravenscar_Profile (N : Node_Id) is
6087          Prefix_Entity   : Entity_Id;
6088          Selector_Entity : Entity_Id;
6089          Prefix_Node     : Node_Id;
6090          Node            : Node_Id;
6091
6092       begin
6093          --  pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
6094
6095          if Task_Dispatching_Policy /= ' '
6096            and then Task_Dispatching_Policy /= 'F'
6097          then
6098             Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
6099             Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
6100
6101          --  Set the FIFO_Within_Priorities policy, but always preserve
6102          --  System_Location since we like the error message with the run time
6103          --  name.
6104
6105          else
6106             Task_Dispatching_Policy := 'F';
6107
6108             if Task_Dispatching_Policy_Sloc /= System_Location then
6109                Task_Dispatching_Policy_Sloc := Loc;
6110             end if;
6111          end if;
6112
6113          --  pragma Locking_Policy (Ceiling_Locking)
6114
6115          if Locking_Policy /= ' '
6116            and then Locking_Policy /= 'C'
6117          then
6118             Error_Msg_Sloc := Locking_Policy_Sloc;
6119             Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
6120
6121          --  Set the Ceiling_Locking policy, but preserve System_Location since
6122          --  we like the error message with the run time name.
6123
6124          else
6125             Locking_Policy := 'C';
6126
6127             if Locking_Policy_Sloc /= System_Location then
6128                Locking_Policy_Sloc := Loc;
6129             end if;
6130          end if;
6131
6132          --  pragma Detect_Blocking
6133
6134          Detect_Blocking := True;
6135
6136          --  Set the corresponding restrictions
6137
6138          Set_Profile_Restrictions
6139            (Ravenscar, N, Warn => Treat_Restrictions_As_Warnings);
6140
6141          --  Set the No_Dependence restrictions
6142
6143          --  The following No_Dependence restrictions:
6144          --    No_Dependence => Ada.Asynchronous_Task_Control
6145          --    No_Dependence => Ada.Calendar
6146          --    No_Dependence => Ada.Task_Attributes
6147          --  are already set by previous call to Set_Profile_Restrictions.
6148
6149          --  Set the following restrictions which were added to Ada 2005:
6150          --    No_Dependence => Ada.Execution_Time.Group_Budget
6151          --    No_Dependence => Ada.Execution_Time.Timers
6152
6153          if Ada_Version >= Ada_2005 then
6154             Name_Buffer (1 .. 3) := "ada";
6155             Name_Len := 3;
6156
6157             Prefix_Entity := Make_Identifier (Loc, Name_Find);
6158
6159             Name_Buffer (1 .. 14) := "execution_time";
6160             Name_Len := 14;
6161
6162             Selector_Entity := Make_Identifier (Loc, Name_Find);
6163
6164             Prefix_Node :=
6165               Make_Selected_Component
6166                 (Sloc          => Loc,
6167                  Prefix        => Prefix_Entity,
6168                  Selector_Name => Selector_Entity);
6169
6170             Name_Buffer (1 .. 13) := "group_budgets";
6171             Name_Len := 13;
6172
6173             Selector_Entity := Make_Identifier (Loc, Name_Find);
6174
6175             Node :=
6176               Make_Selected_Component
6177                 (Sloc          => Loc,
6178                  Prefix        => Prefix_Node,
6179                  Selector_Name => Selector_Entity);
6180
6181             Set_Restriction_No_Dependence
6182               (Unit    => Node,
6183                Warn    => Treat_Restrictions_As_Warnings,
6184                Profile => Ravenscar);
6185
6186             Name_Buffer (1 .. 6) := "timers";
6187             Name_Len := 6;
6188
6189             Selector_Entity := Make_Identifier (Loc, Name_Find);
6190
6191             Node :=
6192               Make_Selected_Component
6193                 (Sloc          => Loc,
6194                  Prefix        => Prefix_Node,
6195                  Selector_Name => Selector_Entity);
6196
6197             Set_Restriction_No_Dependence
6198               (Unit    => Node,
6199                Warn    => Treat_Restrictions_As_Warnings,
6200                Profile => Ravenscar);
6201          end if;
6202
6203          --  Set the following restrictions which was added to Ada 2012 (see
6204          --  AI-0171):
6205          --    No_Dependence => System.Multiprocessors.Dispatching_Domains
6206
6207          if Ada_Version >= Ada_2012 then
6208             Name_Buffer (1 .. 6) := "system";
6209             Name_Len := 6;
6210
6211             Prefix_Entity := Make_Identifier (Loc, Name_Find);
6212
6213             Name_Buffer (1 .. 15) := "multiprocessors";
6214             Name_Len := 15;
6215
6216             Selector_Entity := Make_Identifier (Loc, Name_Find);
6217
6218             Prefix_Node :=
6219               Make_Selected_Component
6220                 (Sloc          => Loc,
6221                  Prefix        => Prefix_Entity,
6222                  Selector_Name => Selector_Entity);
6223
6224             Name_Buffer (1 .. 19) := "dispatching_domains";
6225             Name_Len := 19;
6226
6227             Selector_Entity := Make_Identifier (Loc, Name_Find);
6228
6229             Node :=
6230               Make_Selected_Component
6231                 (Sloc          => Loc,
6232                  Prefix        => Prefix_Node,
6233                  Selector_Name => Selector_Entity);
6234
6235             Set_Restriction_No_Dependence
6236               (Unit    => Node,
6237                Warn    => Treat_Restrictions_As_Warnings,
6238                Profile => Ravenscar);
6239          end if;
6240       end Set_Ravenscar_Profile;
6241
6242    --  Start of processing for Analyze_Pragma
6243
6244    begin
6245       --  The following code is a defense against recursion. Not clear that
6246       --  this can happen legitimately, but perhaps some error situations
6247       --  can cause it, and we did see this recursion during testing.
6248
6249       if Analyzed (N) then
6250          return;
6251       else
6252          Set_Analyzed (N, True);
6253       end if;
6254
6255       --  Deal with unrecognized pragma
6256
6257       Pname := Pragma_Name (N);
6258
6259       if not Is_Pragma_Name (Pname) then
6260          if Warn_On_Unrecognized_Pragma then
6261             Error_Msg_Name_1 := Pname;
6262             Error_Msg_N ("?unrecognized pragma%!", Pragma_Identifier (N));
6263
6264             for PN in First_Pragma_Name .. Last_Pragma_Name loop
6265                if Is_Bad_Spelling_Of (Pname, PN) then
6266                   Error_Msg_Name_1 := PN;
6267                   Error_Msg_N -- CODEFIX
6268                     ("\?possible misspelling of %!", Pragma_Identifier (N));
6269                   exit;
6270                end if;
6271             end loop;
6272          end if;
6273
6274          return;
6275       end if;
6276
6277       --  Here to start processing for recognized pragma
6278
6279       Prag_Id := Get_Pragma_Id (Pname);
6280
6281       if Present (Corresponding_Aspect (N)) then
6282          Pname := Chars (Identifier (Corresponding_Aspect (N)));
6283       end if;
6284
6285       --  Preset arguments
6286
6287       Arg_Count := 0;
6288       Arg1      := Empty;
6289       Arg2      := Empty;
6290       Arg3      := Empty;
6291       Arg4      := Empty;
6292
6293       if Present (Pragma_Argument_Associations (N)) then
6294          Arg_Count := List_Length (Pragma_Argument_Associations (N));
6295          Arg1 := First (Pragma_Argument_Associations (N));
6296
6297          if Present (Arg1) then
6298             Arg2 := Next (Arg1);
6299
6300             if Present (Arg2) then
6301                Arg3 := Next (Arg2);
6302
6303                if Present (Arg3) then
6304                   Arg4 := Next (Arg3);
6305                end if;
6306             end if;
6307          end if;
6308       end if;
6309
6310       --  An enumeration type defines the pragmas that are supported by the
6311       --  implementation. Get_Pragma_Id (in package Prag) transforms a name
6312       --  into the corresponding enumeration value for the following case.
6313
6314       case Prag_Id is
6315
6316          -----------------
6317          -- Abort_Defer --
6318          -----------------
6319
6320          --  pragma Abort_Defer;
6321
6322          when Pragma_Abort_Defer =>
6323             GNAT_Pragma;
6324             Check_Arg_Count (0);
6325
6326             --  The only required semantic processing is to check the
6327             --  placement. This pragma must appear at the start of the
6328             --  statement sequence of a handled sequence of statements.
6329
6330             if Nkind (Parent (N)) /= N_Handled_Sequence_Of_Statements
6331               or else N /= First (Statements (Parent (N)))
6332             then
6333                Pragma_Misplaced;
6334             end if;
6335
6336          ------------
6337          -- Ada_83 --
6338          ------------
6339
6340          --  pragma Ada_83;
6341
6342          --  Note: this pragma also has some specific processing in Par.Prag
6343          --  because we want to set the Ada version mode during parsing.
6344
6345          when Pragma_Ada_83 =>
6346             GNAT_Pragma;
6347             Check_Arg_Count (0);
6348
6349             --  We really should check unconditionally for proper configuration
6350             --  pragma placement, since we really don't want mixed Ada modes
6351             --  within a single unit, and the GNAT reference manual has always
6352             --  said this was a configuration pragma, but we did not check and
6353             --  are hesitant to add the check now.
6354
6355             --  However, we really cannot tolerate mixing Ada 2005 or Ada 2012
6356             --  with Ada 83 or Ada 95, so we must check if we are in Ada 2005
6357             --  or Ada 2012 mode.
6358
6359             if Ada_Version >= Ada_2005 then
6360                Check_Valid_Configuration_Pragma;
6361             end if;
6362
6363             --  Now set Ada 83 mode
6364
6365             Ada_Version := Ada_83;
6366             Ada_Version_Explicit := Ada_Version;
6367
6368          ------------
6369          -- Ada_95 --
6370          ------------
6371
6372          --  pragma Ada_95;
6373
6374          --  Note: this pragma also has some specific processing in Par.Prag
6375          --  because we want to set the Ada 83 version mode during parsing.
6376
6377          when Pragma_Ada_95 =>
6378             GNAT_Pragma;
6379             Check_Arg_Count (0);
6380
6381             --  We really should check unconditionally for proper configuration
6382             --  pragma placement, since we really don't want mixed Ada modes
6383             --  within a single unit, and the GNAT reference manual has always
6384             --  said this was a configuration pragma, but we did not check and
6385             --  are hesitant to add the check now.
6386
6387             --  However, we really cannot tolerate mixing Ada 2005 with Ada 83
6388             --  or Ada 95, so we must check if we are in Ada 2005 mode.
6389
6390             if Ada_Version >= Ada_2005 then
6391                Check_Valid_Configuration_Pragma;
6392             end if;
6393
6394             --  Now set Ada 95 mode
6395
6396             Ada_Version := Ada_95;
6397             Ada_Version_Explicit := Ada_Version;
6398
6399          ---------------------
6400          -- Ada_05/Ada_2005 --
6401          ---------------------
6402
6403          --  pragma Ada_05;
6404          --  pragma Ada_05 (LOCAL_NAME);
6405
6406          --  pragma Ada_2005;
6407          --  pragma Ada_2005 (LOCAL_NAME):
6408
6409          --  Note: these pragmas also have some specific processing in Par.Prag
6410          --  because we want to set the Ada 2005 version mode during parsing.
6411
6412          when Pragma_Ada_05 | Pragma_Ada_2005 => declare
6413             E_Id : Node_Id;
6414
6415          begin
6416             GNAT_Pragma;
6417
6418             if Arg_Count = 1 then
6419                Check_Arg_Is_Local_Name (Arg1);
6420                E_Id := Get_Pragma_Arg (Arg1);
6421
6422                if Etype (E_Id) = Any_Type then
6423                   return;
6424                end if;
6425
6426                Set_Is_Ada_2005_Only (Entity (E_Id));
6427
6428             else
6429                Check_Arg_Count (0);
6430
6431                --  For Ada_2005 we unconditionally enforce the documented
6432                --  configuration pragma placement, since we do not want to
6433                --  tolerate mixed modes in a unit involving Ada 2005. That
6434                --  would cause real difficulties for those cases where there
6435                --  are incompatibilities between Ada 95 and Ada 2005.
6436
6437                Check_Valid_Configuration_Pragma;
6438
6439                --  Now set appropriate Ada mode
6440
6441                Ada_Version          := Ada_2005;
6442                Ada_Version_Explicit := Ada_2005;
6443             end if;
6444          end;
6445
6446          ---------------------
6447          -- Ada_12/Ada_2012 --
6448          ---------------------
6449
6450          --  pragma Ada_12;
6451          --  pragma Ada_12 (LOCAL_NAME);
6452
6453          --  pragma Ada_2012;
6454          --  pragma Ada_2012 (LOCAL_NAME):
6455
6456          --  Note: these pragmas also have some specific processing in Par.Prag
6457          --  because we want to set the Ada 2012 version mode during parsing.
6458
6459          when Pragma_Ada_12 | Pragma_Ada_2012 => declare
6460             E_Id : Node_Id;
6461
6462          begin
6463             GNAT_Pragma;
6464
6465             if Arg_Count = 1 then
6466                Check_Arg_Is_Local_Name (Arg1);
6467                E_Id := Get_Pragma_Arg (Arg1);
6468
6469                if Etype (E_Id) = Any_Type then
6470                   return;
6471                end if;
6472
6473                Set_Is_Ada_2012_Only (Entity (E_Id));
6474
6475             else
6476                Check_Arg_Count (0);
6477
6478                --  For Ada_2012 we unconditionally enforce the documented
6479                --  configuration pragma placement, since we do not want to
6480                --  tolerate mixed modes in a unit involving Ada 2012. That
6481                --  would cause real difficulties for those cases where there
6482                --  are incompatibilities between Ada 95 and Ada 2012. We could
6483                --  allow mixing of Ada 2005 and Ada 2012 but it's not worth it.
6484
6485                Check_Valid_Configuration_Pragma;
6486
6487                --  Now set appropriate Ada mode
6488
6489                Ada_Version          := Ada_2012;
6490                Ada_Version_Explicit := Ada_2012;
6491             end if;
6492          end;
6493
6494          ----------------------
6495          -- All_Calls_Remote --
6496          ----------------------
6497
6498          --  pragma All_Calls_Remote [(library_package_NAME)];
6499
6500          when Pragma_All_Calls_Remote => All_Calls_Remote : declare
6501             Lib_Entity : Entity_Id;
6502
6503          begin
6504             Check_Ada_83_Warning;
6505             Check_Valid_Library_Unit_Pragma;
6506
6507             if Nkind (N) = N_Null_Statement then
6508                return;
6509             end if;
6510
6511             Lib_Entity := Find_Lib_Unit_Name;
6512
6513             --  This pragma should only apply to a RCI unit (RM E.2.3(23))
6514
6515             if Present (Lib_Entity)
6516               and then not Debug_Flag_U
6517             then
6518                if not Is_Remote_Call_Interface (Lib_Entity) then
6519                   Error_Pragma ("pragma% only apply to rci unit");
6520
6521                --  Set flag for entity of the library unit
6522
6523                else
6524                   Set_Has_All_Calls_Remote (Lib_Entity);
6525                end if;
6526
6527             end if;
6528          end All_Calls_Remote;
6529
6530          --------------
6531          -- Annotate --
6532          --------------
6533
6534          --  pragma Annotate (IDENTIFIER [, IDENTIFIER {, ARG}]);
6535          --  ARG ::= NAME | EXPRESSION
6536
6537          --  The first two arguments are by convention intended to refer to an
6538          --  external tool and a tool-specific function. These arguments are
6539          --  not analyzed.
6540
6541          when Pragma_Annotate => Annotate : declare
6542             Arg : Node_Id;
6543             Exp : Node_Id;
6544
6545          begin
6546             GNAT_Pragma;
6547             Check_At_Least_N_Arguments (1);
6548             Check_Arg_Is_Identifier (Arg1);
6549             Check_No_Identifiers;
6550             Store_Note (N);
6551
6552             --  Second parameter is optional, it is never analyzed
6553
6554             if No (Arg2) then
6555                null;
6556
6557             --  Here if we have a second parameter
6558
6559             else
6560                --  Second parameter must be identifier
6561
6562                Check_Arg_Is_Identifier (Arg2);
6563
6564                --  Process remaining parameters if any
6565
6566                Arg := Next (Arg2);
6567                while Present (Arg) loop
6568                   Exp := Get_Pragma_Arg (Arg);
6569                   Analyze (Exp);
6570
6571                   if Is_Entity_Name (Exp) then
6572                      null;
6573
6574                   --  For string literals, we assume Standard_String as the
6575                   --  type, unless the string contains wide or wide_wide
6576                   --  characters.
6577
6578                   elsif Nkind (Exp) = N_String_Literal then
6579                      if Has_Wide_Wide_Character (Exp) then
6580                         Resolve (Exp, Standard_Wide_Wide_String);
6581                      elsif Has_Wide_Character (Exp) then
6582                         Resolve (Exp, Standard_Wide_String);
6583                      else
6584                         Resolve (Exp, Standard_String);
6585                      end if;
6586
6587                   elsif Is_Overloaded (Exp) then
6588                         Error_Pragma_Arg
6589                           ("ambiguous argument for pragma%", Exp);
6590
6591                   else
6592                      Resolve (Exp);
6593                   end if;
6594
6595                   Next (Arg);
6596                end loop;
6597             end if;
6598          end Annotate;
6599
6600          ------------
6601          -- Assert --
6602          ------------
6603
6604          --  pragma Assert ([Check =>] Boolean_EXPRESSION
6605          --                 [, [Message =>] Static_String_EXPRESSION]);
6606
6607          when Pragma_Assert => Assert : declare
6608             Expr : Node_Id;
6609             Newa : List_Id;
6610
6611          begin
6612             Ada_2005_Pragma;
6613             Check_At_Least_N_Arguments (1);
6614             Check_At_Most_N_Arguments (2);
6615             Check_Arg_Order ((Name_Check, Name_Message));
6616             Check_Optional_Identifier (Arg1, Name_Check);
6617
6618             --  We treat pragma Assert as equivalent to:
6619
6620             --    pragma Check (Assertion, condition [, msg]);
6621
6622             --  So rewrite pragma in this manner, and analyze the result
6623
6624             Expr := Get_Pragma_Arg (Arg1);
6625             Newa := New_List (
6626               Make_Pragma_Argument_Association (Loc,
6627                 Expression => Make_Identifier (Loc, Name_Assertion)),
6628
6629               Make_Pragma_Argument_Association (Sloc (Expr),
6630                 Expression => Expr));
6631
6632             if Arg_Count > 1 then
6633                Check_Optional_Identifier (Arg2, Name_Message);
6634                Analyze_And_Resolve (Get_Pragma_Arg (Arg2), Standard_String);
6635                Append_To (Newa, Relocate_Node (Arg2));
6636             end if;
6637
6638             Rewrite (N,
6639               Make_Pragma (Loc,
6640                 Chars                        => Name_Check,
6641                 Pragma_Argument_Associations => Newa));
6642             Analyze (N);
6643          end Assert;
6644
6645          ----------------------
6646          -- Assertion_Policy --
6647          ----------------------
6648
6649          --  pragma Assertion_Policy (Check | Disable |Ignore)
6650
6651          when Pragma_Assertion_Policy => Assertion_Policy : declare
6652             Policy : Node_Id;
6653
6654          begin
6655             Ada_2005_Pragma;
6656             Check_Valid_Configuration_Pragma;
6657             Check_Arg_Count (1);
6658             Check_No_Identifiers;
6659             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Disable, Name_Ignore);
6660
6661             --  We treat pragma Assertion_Policy as equivalent to:
6662
6663             --    pragma Check_Policy (Assertion, policy)
6664
6665             --  So rewrite the pragma in that manner and link on to the chain
6666             --  of Check_Policy pragmas, marking the pragma as analyzed.
6667
6668             Policy := Get_Pragma_Arg (Arg1);
6669
6670             Rewrite (N,
6671               Make_Pragma (Loc,
6672                 Chars => Name_Check_Policy,
6673
6674                 Pragma_Argument_Associations => New_List (
6675                   Make_Pragma_Argument_Association (Loc,
6676                     Expression => Make_Identifier (Loc, Name_Assertion)),
6677
6678                   Make_Pragma_Argument_Association (Loc,
6679                     Expression =>
6680                       Make_Identifier (Sloc (Policy), Chars (Policy))))));
6681
6682             Set_Analyzed (N);
6683             Set_Next_Pragma (N, Opt.Check_Policy_List);
6684             Opt.Check_Policy_List := N;
6685          end Assertion_Policy;
6686
6687          ------------------------------
6688          -- Assume_No_Invalid_Values --
6689          ------------------------------
6690
6691          --  pragma Assume_No_Invalid_Values (On | Off);
6692
6693          when Pragma_Assume_No_Invalid_Values =>
6694             GNAT_Pragma;
6695             Check_Valid_Configuration_Pragma;
6696             Check_Arg_Count (1);
6697             Check_No_Identifiers;
6698             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
6699
6700             if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
6701                Assume_No_Invalid_Values := True;
6702             else
6703                Assume_No_Invalid_Values := False;
6704             end if;
6705
6706          ---------------
6707          -- AST_Entry --
6708          ---------------
6709
6710          --  pragma AST_Entry (entry_IDENTIFIER);
6711
6712          when Pragma_AST_Entry => AST_Entry : declare
6713             Ent : Node_Id;
6714
6715          begin
6716             GNAT_Pragma;
6717             Check_VMS (N);
6718             Check_Arg_Count (1);
6719             Check_No_Identifiers;
6720             Check_Arg_Is_Local_Name (Arg1);
6721             Ent := Entity (Get_Pragma_Arg (Arg1));
6722
6723             --  Note: the implementation of the AST_Entry pragma could handle
6724             --  the entry family case fine, but for now we are consistent with
6725             --  the DEC rules, and do not allow the pragma, which of course
6726             --  has the effect of also forbidding the attribute.
6727
6728             if Ekind (Ent) /= E_Entry then
6729                Error_Pragma_Arg
6730                  ("pragma% argument must be simple entry name", Arg1);
6731
6732             elsif Is_AST_Entry (Ent) then
6733                Error_Pragma_Arg
6734                  ("duplicate % pragma for entry", Arg1);
6735
6736             elsif Has_Homonym (Ent) then
6737                Error_Pragma_Arg
6738                  ("pragma% argument cannot specify overloaded entry", Arg1);
6739
6740             else
6741                declare
6742                   FF : constant Entity_Id := First_Formal (Ent);
6743
6744                begin
6745                   if Present (FF) then
6746                      if Present (Next_Formal (FF)) then
6747                         Error_Pragma_Arg
6748                           ("entry for pragma% can have only one argument",
6749                            Arg1);
6750
6751                      elsif Parameter_Mode (FF) /= E_In_Parameter then
6752                         Error_Pragma_Arg
6753                           ("entry parameter for pragma% must have mode IN",
6754                            Arg1);
6755                      end if;
6756                   end if;
6757                end;
6758
6759                Set_Is_AST_Entry (Ent);
6760             end if;
6761          end AST_Entry;
6762
6763          ------------------
6764          -- Asynchronous --
6765          ------------------
6766
6767          --  pragma Asynchronous (LOCAL_NAME);
6768
6769          when Pragma_Asynchronous => Asynchronous : declare
6770             Nm     : Entity_Id;
6771             C_Ent  : Entity_Id;
6772             L      : List_Id;
6773             S      : Node_Id;
6774             N      : Node_Id;
6775             Formal : Entity_Id;
6776
6777             procedure Process_Async_Pragma;
6778             --  Common processing for procedure and access-to-procedure case
6779
6780             --------------------------
6781             -- Process_Async_Pragma --
6782             --------------------------
6783
6784             procedure Process_Async_Pragma is
6785             begin
6786                if No (L) then
6787                   Set_Is_Asynchronous (Nm);
6788                   return;
6789                end if;
6790
6791                --  The formals should be of mode IN (RM E.4.1(6))
6792
6793                S := First (L);
6794                while Present (S) loop
6795                   Formal := Defining_Identifier (S);
6796
6797                   if Nkind (Formal) = N_Defining_Identifier
6798                     and then Ekind (Formal) /= E_In_Parameter
6799                   then
6800                      Error_Pragma_Arg
6801                        ("pragma% procedure can only have IN parameter",
6802                         Arg1);
6803                   end if;
6804
6805                   Next (S);
6806                end loop;
6807
6808                Set_Is_Asynchronous (Nm);
6809             end Process_Async_Pragma;
6810
6811          --  Start of processing for pragma Asynchronous
6812
6813          begin
6814             Check_Ada_83_Warning;
6815             Check_No_Identifiers;
6816             Check_Arg_Count (1);
6817             Check_Arg_Is_Local_Name (Arg1);
6818
6819             if Debug_Flag_U then
6820                return;
6821             end if;
6822
6823             C_Ent := Cunit_Entity (Current_Sem_Unit);
6824             Analyze (Get_Pragma_Arg (Arg1));
6825             Nm := Entity (Get_Pragma_Arg (Arg1));
6826
6827             if not Is_Remote_Call_Interface (C_Ent)
6828               and then not Is_Remote_Types (C_Ent)
6829             then
6830                --  This pragma should only appear in an RCI or Remote Types
6831                --  unit (RM E.4.1(4)).
6832
6833                Error_Pragma
6834                  ("pragma% not in Remote_Call_Interface or " &
6835                   "Remote_Types unit");
6836             end if;
6837
6838             if Ekind (Nm) = E_Procedure
6839               and then Nkind (Parent (Nm)) = N_Procedure_Specification
6840             then
6841                if not Is_Remote_Call_Interface (Nm) then
6842                   Error_Pragma_Arg
6843                     ("pragma% cannot be applied on non-remote procedure",
6844                      Arg1);
6845                end if;
6846
6847                L := Parameter_Specifications (Parent (Nm));
6848                Process_Async_Pragma;
6849                return;
6850
6851             elsif Ekind (Nm) = E_Function then
6852                Error_Pragma_Arg
6853                  ("pragma% cannot be applied to function", Arg1);
6854
6855             elsif Is_Remote_Access_To_Subprogram_Type (Nm) then
6856                   if Is_Record_Type (Nm) then
6857
6858                   --  A record type that is the Equivalent_Type for a remote
6859                   --  access-to-subprogram type.
6860
6861                      N := Declaration_Node (Corresponding_Remote_Type (Nm));
6862
6863                   else
6864                      --  A non-expanded RAS type (distribution is not enabled)
6865
6866                      N := Declaration_Node (Nm);
6867                   end if;
6868
6869                if Nkind (N) = N_Full_Type_Declaration
6870                  and then Nkind (Type_Definition (N)) =
6871                                      N_Access_Procedure_Definition
6872                then
6873                   L := Parameter_Specifications (Type_Definition (N));
6874                   Process_Async_Pragma;
6875
6876                   if Is_Asynchronous (Nm)
6877                     and then Expander_Active
6878                     and then Get_PCS_Name /= Name_No_DSA
6879                   then
6880                      RACW_Type_Is_Asynchronous (Underlying_RACW_Type (Nm));
6881                   end if;
6882
6883                else
6884                   Error_Pragma_Arg
6885                     ("pragma% cannot reference access-to-function type",
6886                     Arg1);
6887                end if;
6888
6889             --  Only other possibility is Access-to-class-wide type
6890
6891             elsif Is_Access_Type (Nm)
6892               and then Is_Class_Wide_Type (Designated_Type (Nm))
6893             then
6894                Check_First_Subtype (Arg1);
6895                Set_Is_Asynchronous (Nm);
6896                if Expander_Active then
6897                   RACW_Type_Is_Asynchronous (Nm);
6898                end if;
6899
6900             else
6901                Error_Pragma_Arg ("inappropriate argument for pragma%", Arg1);
6902             end if;
6903          end Asynchronous;
6904
6905          ------------
6906          -- Atomic --
6907          ------------
6908
6909          --  pragma Atomic (LOCAL_NAME);
6910
6911          when Pragma_Atomic =>
6912             Process_Atomic_Shared_Volatile;
6913
6914          -----------------------
6915          -- Atomic_Components --
6916          -----------------------
6917
6918          --  pragma Atomic_Components (array_LOCAL_NAME);
6919
6920          --  This processing is shared by Volatile_Components
6921
6922          when Pragma_Atomic_Components   |
6923               Pragma_Volatile_Components =>
6924
6925          Atomic_Components : declare
6926             E_Id : Node_Id;
6927             E    : Entity_Id;
6928             D    : Node_Id;
6929             K    : Node_Kind;
6930
6931          begin
6932             Check_Ada_83_Warning;
6933             Check_No_Identifiers;
6934             Check_Arg_Count (1);
6935             Check_Arg_Is_Local_Name (Arg1);
6936             E_Id := Get_Pragma_Arg (Arg1);
6937
6938             if Etype (E_Id) = Any_Type then
6939                return;
6940             end if;
6941
6942             E := Entity (E_Id);
6943
6944             Check_Duplicate_Pragma (E);
6945
6946             if Rep_Item_Too_Early (E, N)
6947                  or else
6948                Rep_Item_Too_Late (E, N)
6949             then
6950                return;
6951             end if;
6952
6953             D := Declaration_Node (E);
6954             K := Nkind (D);
6955
6956             if (K = N_Full_Type_Declaration and then Is_Array_Type (E))
6957               or else
6958                 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
6959                    and then Nkind (D) = N_Object_Declaration
6960                    and then Nkind (Object_Definition (D)) =
6961                                        N_Constrained_Array_Definition)
6962             then
6963                --  The flag is set on the object, or on the base type
6964
6965                if Nkind (D) /= N_Object_Declaration then
6966                   E := Base_Type (E);
6967                end if;
6968
6969                Set_Has_Volatile_Components (E);
6970
6971                if Prag_Id = Pragma_Atomic_Components then
6972                   Set_Has_Atomic_Components (E);
6973                end if;
6974
6975             else
6976                Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
6977             end if;
6978          end Atomic_Components;
6979          --------------------
6980          -- Attach_Handler --
6981          --------------------
6982
6983          --  pragma Attach_Handler (handler_NAME, EXPRESSION);
6984
6985          when Pragma_Attach_Handler =>
6986             Check_Ada_83_Warning;
6987             Check_No_Identifiers;
6988             Check_Arg_Count (2);
6989
6990             if No_Run_Time_Mode then
6991                Error_Msg_CRT ("Attach_Handler pragma", N);
6992             else
6993                Check_Interrupt_Or_Attach_Handler;
6994
6995                --  The expression that designates the attribute may depend on a
6996                --  discriminant, and is therefore a per- object expression, to
6997                --  be expanded in the init proc. If expansion is enabled, then
6998                --  perform semantic checks on a copy only.
6999
7000                if Expander_Active then
7001                   declare
7002                      Temp : constant Node_Id :=
7003                               New_Copy_Tree (Get_Pragma_Arg (Arg2));
7004                   begin
7005                      Set_Parent (Temp, N);
7006                      Preanalyze_And_Resolve (Temp, RTE (RE_Interrupt_ID));
7007                   end;
7008
7009                else
7010                   Analyze (Get_Pragma_Arg (Arg2));
7011                   Resolve (Get_Pragma_Arg (Arg2), RTE (RE_Interrupt_ID));
7012                end if;
7013
7014                Process_Interrupt_Or_Attach_Handler;
7015             end if;
7016
7017          --------------------
7018          -- C_Pass_By_Copy --
7019          --------------------
7020
7021          --  pragma C_Pass_By_Copy ([Max_Size =>] static_integer_EXPRESSION);
7022
7023          when Pragma_C_Pass_By_Copy => C_Pass_By_Copy : declare
7024             Arg : Node_Id;
7025             Val : Uint;
7026
7027          begin
7028             GNAT_Pragma;
7029             Check_Valid_Configuration_Pragma;
7030             Check_Arg_Count (1);
7031             Check_Optional_Identifier (Arg1, "max_size");
7032
7033             Arg := Get_Pragma_Arg (Arg1);
7034             Check_Arg_Is_Static_Expression (Arg, Any_Integer);
7035
7036             Val := Expr_Value (Arg);
7037
7038             if Val <= 0 then
7039                Error_Pragma_Arg
7040                  ("maximum size for pragma% must be positive", Arg1);
7041
7042             elsif UI_Is_In_Int_Range (Val) then
7043                Default_C_Record_Mechanism := UI_To_Int (Val);
7044
7045             --  If a giant value is given, Int'Last will do well enough.
7046             --  If sometime someone complains that a record larger than
7047             --  two gigabytes is not copied, we will worry about it then!
7048
7049             else
7050                Default_C_Record_Mechanism := Mechanism_Type'Last;
7051             end if;
7052          end C_Pass_By_Copy;
7053
7054          -----------
7055          -- Check --
7056          -----------
7057
7058          --  pragma Check ([Name    =>] IDENTIFIER,
7059          --                [Check   =>] Boolean_EXPRESSION
7060          --              [,[Message =>] String_EXPRESSION]);
7061
7062          when Pragma_Check => Check : declare
7063             Expr : Node_Id;
7064             Eloc : Source_Ptr;
7065
7066             Check_On : Boolean;
7067             --  Set True if category of assertions referenced by Name enabled
7068
7069          begin
7070             GNAT_Pragma;
7071             Check_At_Least_N_Arguments (2);
7072             Check_At_Most_N_Arguments (3);
7073             Check_Optional_Identifier (Arg1, Name_Name);
7074             Check_Optional_Identifier (Arg2, Name_Check);
7075
7076             if Arg_Count = 3 then
7077                Check_Optional_Identifier (Arg3, Name_Message);
7078                Analyze_And_Resolve (Get_Pragma_Arg (Arg3), Standard_String);
7079             end if;
7080
7081             Check_Arg_Is_Identifier (Arg1);
7082
7083             --  Completely ignore if disabled
7084
7085             if Check_Disabled (Chars (Get_Pragma_Arg (Arg1))) then
7086                Rewrite (N, Make_Null_Statement (Loc));
7087                Analyze (N);
7088                return;
7089             end if;
7090
7091             --  Indicate if pragma is enabled. The Original_Node reference here
7092             --  is to deal with pragma Assert rewritten as a Check pragma.
7093
7094             Check_On := Check_Enabled (Chars (Get_Pragma_Arg (Arg1)));
7095
7096             if Check_On then
7097                Set_SCO_Pragma_Enabled (Loc);
7098             end if;
7099
7100             --  If expansion is active and the check is not enabled then we
7101             --  rewrite the Check as:
7102
7103             --    if False and then condition then
7104             --       null;
7105             --    end if;
7106
7107             --  The reason we do this rewriting during semantic analysis rather
7108             --  than as part of normal expansion is that we cannot analyze and
7109             --  expand the code for the boolean expression directly, or it may
7110             --  cause insertion of actions that would escape the attempt to
7111             --  suppress the check code.
7112
7113             --  Note that the Sloc for the if statement corresponds to the
7114             --  argument condition, not the pragma itself. The reason for this
7115             --  is that we may generate a warning if the condition is False at
7116             --  compile time, and we do not want to delete this warning when we
7117             --  delete the if statement.
7118
7119             Expr := Get_Pragma_Arg (Arg2);
7120
7121             if Expander_Active and then not Check_On then
7122                Eloc := Sloc (Expr);
7123
7124                Rewrite (N,
7125                  Make_If_Statement (Eloc,
7126                    Condition =>
7127                      Make_And_Then (Eloc,
7128                        Left_Opnd  => New_Occurrence_Of (Standard_False, Eloc),
7129                        Right_Opnd => Expr),
7130                    Then_Statements => New_List (
7131                      Make_Null_Statement (Eloc))));
7132
7133                Analyze (N);
7134
7135             --  Check is active
7136
7137             else
7138                Analyze_And_Resolve (Expr, Any_Boolean);
7139             end if;
7140          end Check;
7141
7142          ----------------
7143          -- Check_Name --
7144          ----------------
7145
7146          --  pragma Check_Name (check_IDENTIFIER);
7147
7148          when Pragma_Check_Name =>
7149             Check_No_Identifiers;
7150             GNAT_Pragma;
7151             Check_Valid_Configuration_Pragma;
7152             Check_Arg_Count (1);
7153             Check_Arg_Is_Identifier (Arg1);
7154
7155             declare
7156                Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
7157
7158             begin
7159                for J in Check_Names.First .. Check_Names.Last loop
7160                   if Check_Names.Table (J) = Nam then
7161                      return;
7162                   end if;
7163                end loop;
7164
7165                Check_Names.Append (Nam);
7166             end;
7167
7168          ------------------
7169          -- Check_Policy --
7170          ------------------
7171
7172          --  pragma Check_Policy (
7173          --    [Name   =>] IDENTIFIER,
7174          --    [Policy =>] POLICY_IDENTIFIER);
7175
7176          --  POLICY_IDENTIFIER ::= ON | OFF | CHECK | DISABLE | IGNORE
7177
7178          --  Note: this is a configuration pragma, but it is allowed to appear
7179          --  anywhere else.
7180
7181          when Pragma_Check_Policy =>
7182             GNAT_Pragma;
7183             Check_Arg_Count (2);
7184             Check_Optional_Identifier (Arg1, Name_Name);
7185             Check_Optional_Identifier (Arg2, Name_Policy);
7186             Check_Arg_Is_One_Of
7187               (Arg2, Name_On, Name_Off, Name_Check, Name_Disable, Name_Ignore);
7188
7189             --  A Check_Policy pragma can appear either as a configuration
7190             --  pragma, or in a declarative part or a package spec (see RM
7191             --  11.5(5) for rules for Suppress/Unsuppress which are also
7192             --  followed for Check_Policy).
7193
7194             if not Is_Configuration_Pragma then
7195                Check_Is_In_Decl_Part_Or_Package_Spec;
7196             end if;
7197
7198             Set_Next_Pragma (N, Opt.Check_Policy_List);
7199             Opt.Check_Policy_List := N;
7200
7201          ---------------------
7202          -- CIL_Constructor --
7203          ---------------------
7204
7205          --  pragma CIL_Constructor ([Entity =>] LOCAL_NAME);
7206
7207          --  Processing for this pragma is shared with Java_Constructor
7208
7209          -------------
7210          -- Comment --
7211          -------------
7212
7213          --  pragma Comment (static_string_EXPRESSION)
7214
7215          --  Processing for pragma Comment shares the circuitry for pragma
7216          --  Ident. The only differences are that Ident enforces a limit of 31
7217          --  characters on its argument, and also enforces limitations on
7218          --  placement for DEC compatibility. Pragma Comment shares neither of
7219          --  these restrictions.
7220
7221          -------------------
7222          -- Common_Object --
7223          -------------------
7224
7225          --  pragma Common_Object (
7226          --        [Internal =>] LOCAL_NAME
7227          --     [, [External =>] EXTERNAL_SYMBOL]
7228          --     [, [Size     =>] EXTERNAL_SYMBOL]);
7229
7230          --  Processing for this pragma is shared with Psect_Object
7231
7232          ------------------------
7233          -- Compile_Time_Error --
7234          ------------------------
7235
7236          --  pragma Compile_Time_Error
7237          --    (boolean_EXPRESSION, static_string_EXPRESSION);
7238
7239          when Pragma_Compile_Time_Error =>
7240             GNAT_Pragma;
7241             Process_Compile_Time_Warning_Or_Error;
7242
7243          --------------------------
7244          -- Compile_Time_Warning --
7245          --------------------------
7246
7247          --  pragma Compile_Time_Warning
7248          --    (boolean_EXPRESSION, static_string_EXPRESSION);
7249
7250          when Pragma_Compile_Time_Warning =>
7251             GNAT_Pragma;
7252             Process_Compile_Time_Warning_Or_Error;
7253
7254          -------------------
7255          -- Compiler_Unit --
7256          -------------------
7257
7258          when Pragma_Compiler_Unit =>
7259             GNAT_Pragma;
7260             Check_Arg_Count (0);
7261             Set_Is_Compiler_Unit (Get_Source_Unit (N));
7262
7263          -----------------------------
7264          -- Complete_Representation --
7265          -----------------------------
7266
7267          --  pragma Complete_Representation;
7268
7269          when Pragma_Complete_Representation =>
7270             GNAT_Pragma;
7271             Check_Arg_Count (0);
7272
7273             if Nkind (Parent (N)) /= N_Record_Representation_Clause then
7274                Error_Pragma
7275                  ("pragma & must appear within record representation clause");
7276             end if;
7277
7278          ----------------------------
7279          -- Complex_Representation --
7280          ----------------------------
7281
7282          --  pragma Complex_Representation ([Entity =>] LOCAL_NAME);
7283
7284          when Pragma_Complex_Representation => Complex_Representation : declare
7285             E_Id : Entity_Id;
7286             E    : Entity_Id;
7287             Ent  : Entity_Id;
7288
7289          begin
7290             GNAT_Pragma;
7291             Check_Arg_Count (1);
7292             Check_Optional_Identifier (Arg1, Name_Entity);
7293             Check_Arg_Is_Local_Name (Arg1);
7294             E_Id := Get_Pragma_Arg (Arg1);
7295
7296             if Etype (E_Id) = Any_Type then
7297                return;
7298             end if;
7299
7300             E := Entity (E_Id);
7301
7302             if not Is_Record_Type (E) then
7303                Error_Pragma_Arg
7304                  ("argument for pragma% must be record type", Arg1);
7305             end if;
7306
7307             Ent := First_Entity (E);
7308
7309             if No (Ent)
7310               or else No (Next_Entity (Ent))
7311               or else Present (Next_Entity (Next_Entity (Ent)))
7312               or else not Is_Floating_Point_Type (Etype (Ent))
7313               or else Etype (Ent) /= Etype (Next_Entity (Ent))
7314             then
7315                Error_Pragma_Arg
7316                  ("record for pragma% must have two fields of the same "
7317                   & "floating-point type", Arg1);
7318
7319             else
7320                Set_Has_Complex_Representation (Base_Type (E));
7321
7322                --  We need to treat the type has having a non-standard
7323                --  representation, for back-end purposes, even though in
7324                --  general a complex will have the default representation
7325                --  of a record with two real components.
7326
7327                Set_Has_Non_Standard_Rep (Base_Type (E));
7328             end if;
7329          end Complex_Representation;
7330
7331          -------------------------
7332          -- Component_Alignment --
7333          -------------------------
7334
7335          --  pragma Component_Alignment (
7336          --        [Form =>] ALIGNMENT_CHOICE
7337          --     [, [Name =>] type_LOCAL_NAME]);
7338          --
7339          --   ALIGNMENT_CHOICE ::=
7340          --     Component_Size
7341          --   | Component_Size_4
7342          --   | Storage_Unit
7343          --   | Default
7344
7345          when Pragma_Component_Alignment => Component_AlignmentP : declare
7346             Args  : Args_List (1 .. 2);
7347             Names : constant Name_List (1 .. 2) := (
7348                       Name_Form,
7349                       Name_Name);
7350
7351             Form  : Node_Id renames Args (1);
7352             Name  : Node_Id renames Args (2);
7353
7354             Atype : Component_Alignment_Kind;
7355             Typ   : Entity_Id;
7356
7357          begin
7358             GNAT_Pragma;
7359             Gather_Associations (Names, Args);
7360
7361             if No (Form) then
7362                Error_Pragma ("missing Form argument for pragma%");
7363             end if;
7364
7365             Check_Arg_Is_Identifier (Form);
7366
7367             --  Get proper alignment, note that Default = Component_Size on all
7368             --  machines we have so far, and we want to set this value rather
7369             --  than the default value to indicate that it has been explicitly
7370             --  set (and thus will not get overridden by the default component
7371             --  alignment for the current scope)
7372
7373             if Chars (Form) = Name_Component_Size then
7374                Atype := Calign_Component_Size;
7375
7376             elsif Chars (Form) = Name_Component_Size_4 then
7377                Atype := Calign_Component_Size_4;
7378
7379             elsif Chars (Form) = Name_Default then
7380                Atype := Calign_Component_Size;
7381
7382             elsif Chars (Form) = Name_Storage_Unit then
7383                Atype := Calign_Storage_Unit;
7384
7385             else
7386                Error_Pragma_Arg
7387                  ("invalid Form parameter for pragma%", Form);
7388             end if;
7389
7390             --  Case with no name, supplied, affects scope table entry
7391
7392             if No (Name) then
7393                Scope_Stack.Table
7394                  (Scope_Stack.Last).Component_Alignment_Default := Atype;
7395
7396             --  Case of name supplied
7397
7398             else
7399                Check_Arg_Is_Local_Name (Name);
7400                Find_Type (Name);
7401                Typ := Entity (Name);
7402
7403                if Typ = Any_Type
7404                  or else Rep_Item_Too_Early (Typ, N)
7405                then
7406                   return;
7407                else
7408                   Typ := Underlying_Type (Typ);
7409                end if;
7410
7411                if not Is_Record_Type (Typ)
7412                  and then not Is_Array_Type (Typ)
7413                then
7414                   Error_Pragma_Arg
7415                     ("Name parameter of pragma% must identify record or " &
7416                      "array type", Name);
7417                end if;
7418
7419                --  An explicit Component_Alignment pragma overrides an
7420                --  implicit pragma Pack, but not an explicit one.
7421
7422                if not Has_Pragma_Pack (Base_Type (Typ)) then
7423                   Set_Is_Packed (Base_Type (Typ), False);
7424                   Set_Component_Alignment (Base_Type (Typ), Atype);
7425                end if;
7426             end if;
7427          end Component_AlignmentP;
7428
7429          ----------------
7430          -- Controlled --
7431          ----------------
7432
7433          --  pragma Controlled (first_subtype_LOCAL_NAME);
7434
7435          when Pragma_Controlled => Controlled : declare
7436             Arg : Node_Id;
7437
7438          begin
7439             Check_No_Identifiers;
7440             Check_Arg_Count (1);
7441             Check_Arg_Is_Local_Name (Arg1);
7442             Arg := Get_Pragma_Arg (Arg1);
7443
7444             if not Is_Entity_Name (Arg)
7445               or else not Is_Access_Type (Entity (Arg))
7446             then
7447                Error_Pragma_Arg ("pragma% requires access type", Arg1);
7448             else
7449                Set_Has_Pragma_Controlled (Base_Type (Entity (Arg)));
7450             end if;
7451          end Controlled;
7452
7453          ----------------
7454          -- Convention --
7455          ----------------
7456
7457          --  pragma Convention ([Convention =>] convention_IDENTIFIER,
7458          --    [Entity =>] LOCAL_NAME);
7459
7460          when Pragma_Convention => Convention : declare
7461             C : Convention_Id;
7462             E : Entity_Id;
7463             pragma Warnings (Off, C);
7464             pragma Warnings (Off, E);
7465          begin
7466             Check_Arg_Order ((Name_Convention, Name_Entity));
7467             Check_Ada_83_Warning;
7468             Check_Arg_Count (2);
7469             Process_Convention (C, E);
7470          end Convention;
7471
7472          ---------------------------
7473          -- Convention_Identifier --
7474          ---------------------------
7475
7476          --  pragma Convention_Identifier ([Name =>] IDENTIFIER,
7477          --    [Convention =>] convention_IDENTIFIER);
7478
7479          when Pragma_Convention_Identifier => Convention_Identifier : declare
7480             Idnam : Name_Id;
7481             Cname : Name_Id;
7482
7483          begin
7484             GNAT_Pragma;
7485             Check_Arg_Order ((Name_Name, Name_Convention));
7486             Check_Arg_Count (2);
7487             Check_Optional_Identifier (Arg1, Name_Name);
7488             Check_Optional_Identifier (Arg2, Name_Convention);
7489             Check_Arg_Is_Identifier (Arg1);
7490             Check_Arg_Is_Identifier (Arg2);
7491             Idnam := Chars (Get_Pragma_Arg (Arg1));
7492             Cname := Chars (Get_Pragma_Arg (Arg2));
7493
7494             if Is_Convention_Name (Cname) then
7495                Record_Convention_Identifier
7496                  (Idnam, Get_Convention_Id (Cname));
7497             else
7498                Error_Pragma_Arg
7499                  ("second arg for % pragma must be convention", Arg2);
7500             end if;
7501          end Convention_Identifier;
7502
7503          ---------------
7504          -- CPP_Class --
7505          ---------------
7506
7507          --  pragma CPP_Class ([Entity =>] local_NAME)
7508
7509          when Pragma_CPP_Class => CPP_Class : declare
7510             Arg : Node_Id;
7511             Typ : Entity_Id;
7512
7513          begin
7514             if Warn_On_Obsolescent_Feature then
7515                Error_Msg_N
7516                  ("'G'N'A'T pragma cpp'_class is now obsolete; replace it" &
7517                   " by pragma import?", N);
7518             end if;
7519
7520             GNAT_Pragma;
7521             Check_Arg_Count (1);
7522             Check_Optional_Identifier (Arg1, Name_Entity);
7523             Check_Arg_Is_Local_Name (Arg1);
7524
7525             Arg := Get_Pragma_Arg (Arg1);
7526             Analyze (Arg);
7527
7528             if Etype (Arg) = Any_Type then
7529                return;
7530             end if;
7531
7532             if not Is_Entity_Name (Arg)
7533               or else not Is_Type (Entity (Arg))
7534             then
7535                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
7536             end if;
7537
7538             Typ := Entity (Arg);
7539
7540             if not Is_Tagged_Type (Typ) then
7541                Error_Pragma_Arg ("pragma% applicable to tagged types ", Arg1);
7542             end if;
7543
7544             --  Types treated as CPP classes must be declared limited (note:
7545             --  this used to be a warning but there is no real benefit to it
7546             --  since we did effectively intend to treat the type as limited
7547             --  anyway).
7548
7549             if not Is_Limited_Type (Typ) then
7550                Error_Msg_N
7551                  ("imported 'C'P'P type must be limited",
7552                   Get_Pragma_Arg (Arg1));
7553             end if;
7554
7555             Set_Is_CPP_Class      (Typ);
7556             Set_Convention        (Typ, Convention_CPP);
7557
7558             --  Imported CPP types must not have discriminants (because C++
7559             --  classes do not have discriminants).
7560
7561             if Has_Discriminants (Typ) then
7562                Error_Msg_N
7563                  ("imported 'C'P'P type cannot have discriminants",
7564                   First (Discriminant_Specifications
7565                           (Declaration_Node (Typ))));
7566             end if;
7567
7568             --  Components of imported CPP types must not have default
7569             --  expressions because the constructor (if any) is in the
7570             --  C++ side.
7571
7572             if Is_Incomplete_Or_Private_Type (Typ)
7573               and then No (Underlying_Type (Typ))
7574             then
7575                --  It should be an error to apply pragma CPP to a private
7576                --  type if the underlying type is not visible (as it is
7577                --  for any representation item). For now, for backward
7578                --  compatibility we do nothing but we cannot check components
7579                --  because they are not available at this stage. All this code
7580                --  will be removed when we cleanup this obsolete GNAT pragma???
7581
7582                null;
7583
7584             else
7585                declare
7586                   Tdef  : constant Node_Id :=
7587                             Type_Definition (Declaration_Node (Typ));
7588                   Clist : Node_Id;
7589                   Comp  : Node_Id;
7590
7591                begin
7592                   if Nkind (Tdef) = N_Record_Definition then
7593                      Clist := Component_List (Tdef);
7594                   else
7595                      pragma Assert (Nkind (Tdef) = N_Derived_Type_Definition);
7596                      Clist := Component_List (Record_Extension_Part (Tdef));
7597                   end if;
7598
7599                   if Present (Clist) then
7600                      Comp := First (Component_Items (Clist));
7601                      while Present (Comp) loop
7602                         if Present (Expression (Comp)) then
7603                            Error_Msg_N
7604                              ("component of imported 'C'P'P type cannot have" &
7605                               " default expression", Expression (Comp));
7606                         end if;
7607
7608                         Next (Comp);
7609                      end loop;
7610                   end if;
7611                end;
7612             end if;
7613          end CPP_Class;
7614
7615          ---------------------
7616          -- CPP_Constructor --
7617          ---------------------
7618
7619          --  pragma CPP_Constructor ([Entity =>] LOCAL_NAME
7620          --    [, [External_Name =>] static_string_EXPRESSION ]
7621          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
7622
7623          when Pragma_CPP_Constructor => CPP_Constructor : declare
7624             Elmt    : Elmt_Id;
7625             Id      : Entity_Id;
7626             Def_Id  : Entity_Id;
7627             Tag_Typ : Entity_Id;
7628
7629          begin
7630             GNAT_Pragma;
7631             Check_At_Least_N_Arguments (1);
7632             Check_At_Most_N_Arguments (3);
7633             Check_Optional_Identifier (Arg1, Name_Entity);
7634             Check_Arg_Is_Local_Name (Arg1);
7635
7636             Id := Get_Pragma_Arg (Arg1);
7637             Find_Program_Unit_Name (Id);
7638
7639             --  If we did not find the name, we are done
7640
7641             if Etype (Id) = Any_Type then
7642                return;
7643             end if;
7644
7645             Def_Id := Entity (Id);
7646
7647             --  Check if already defined as constructor
7648
7649             if Is_Constructor (Def_Id) then
7650                Error_Msg_N
7651                  ("?duplicate argument for pragma 'C'P'P_Constructor", Arg1);
7652                return;
7653             end if;
7654
7655             if Ekind (Def_Id) = E_Function
7656               and then (Is_CPP_Class (Etype (Def_Id))
7657                          or else (Is_Class_Wide_Type (Etype (Def_Id))
7658                                    and then
7659                                   Is_CPP_Class (Root_Type (Etype (Def_Id)))))
7660             then
7661                if Arg_Count >= 2 then
7662                   Set_Imported (Def_Id);
7663                   Set_Is_Public (Def_Id);
7664                   Process_Interface_Name (Def_Id, Arg2, Arg3);
7665                end if;
7666
7667                Set_Has_Completion (Def_Id);
7668                Set_Is_Constructor (Def_Id);
7669
7670                --  Imported C++ constructors are not dispatching primitives
7671                --  because in C++ they don't have a dispatch table slot.
7672                --  However, in Ada the constructor has the profile of a
7673                --  function that returns a tagged type and therefore it has
7674                --  been treated as a primitive operation during semantic
7675                --  analysis. We now remove it from the list of primitive
7676                --  operations of the type.
7677
7678                if Is_Tagged_Type (Etype (Def_Id))
7679                  and then not Is_Class_Wide_Type (Etype (Def_Id))
7680                then
7681                   pragma Assert (Is_Dispatching_Operation (Def_Id));
7682                   Tag_Typ := Etype (Def_Id);
7683
7684                   Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
7685                   while Present (Elmt) and then Node (Elmt) /= Def_Id loop
7686                      Next_Elmt (Elmt);
7687                   end loop;
7688
7689                   Remove_Elmt (Primitive_Operations (Tag_Typ), Elmt);
7690                   Set_Is_Dispatching_Operation (Def_Id, False);
7691                end if;
7692
7693                --  For backward compatibility, if the constructor returns a
7694                --  class wide type, and we internally change the return type to
7695                --  the corresponding root type.
7696
7697                if Is_Class_Wide_Type (Etype (Def_Id)) then
7698                   Set_Etype (Def_Id, Root_Type (Etype (Def_Id)));
7699                end if;
7700             else
7701                Error_Pragma_Arg
7702                  ("pragma% requires function returning a 'C'P'P_Class type",
7703                    Arg1);
7704             end if;
7705          end CPP_Constructor;
7706
7707          -----------------
7708          -- CPP_Virtual --
7709          -----------------
7710
7711          when Pragma_CPP_Virtual => CPP_Virtual : declare
7712          begin
7713             GNAT_Pragma;
7714
7715             if Warn_On_Obsolescent_Feature then
7716                Error_Msg_N
7717                  ("'G'N'A'T pragma cpp'_virtual is now obsolete and has " &
7718                   "no effect?", N);
7719             end if;
7720          end CPP_Virtual;
7721
7722          ----------------
7723          -- CPP_Vtable --
7724          ----------------
7725
7726          when Pragma_CPP_Vtable => CPP_Vtable : declare
7727          begin
7728             GNAT_Pragma;
7729
7730             if Warn_On_Obsolescent_Feature then
7731                Error_Msg_N
7732                  ("'G'N'A'T pragma cpp'_vtable is now obsolete and has " &
7733                   "no effect?", N);
7734             end if;
7735          end CPP_Vtable;
7736
7737          ---------
7738          -- CPU --
7739          ---------
7740
7741          --  pragma CPU (EXPRESSION);
7742
7743          when Pragma_CPU => CPU : declare
7744             P   : constant Node_Id := Parent (N);
7745             Arg : Node_Id;
7746
7747          begin
7748             Ada_2012_Pragma;
7749             Check_No_Identifiers;
7750             Check_Arg_Count (1);
7751
7752             --  Subprogram case
7753
7754             if Nkind (P) = N_Subprogram_Body then
7755                Check_In_Main_Program;
7756
7757                Arg := Get_Pragma_Arg (Arg1);
7758                Analyze_And_Resolve (Arg, Any_Integer);
7759
7760                --  Must be static
7761
7762                if not Is_Static_Expression (Arg) then
7763                   Flag_Non_Static_Expr
7764                     ("main subprogram affinity is not static!", Arg);
7765                   raise Pragma_Exit;
7766
7767                --  If constraint error, then we already signalled an error
7768
7769                elsif Raises_Constraint_Error (Arg) then
7770                   null;
7771
7772                --  Otherwise check in range
7773
7774                else
7775                   declare
7776                      CPU_Id : constant Entity_Id := RTE (RE_CPU_Range);
7777                      --  This is the entity System.Multiprocessors.CPU_Range;
7778
7779                      Val : constant Uint := Expr_Value (Arg);
7780
7781                   begin
7782                      if Val < Expr_Value (Type_Low_Bound (CPU_Id))
7783                           or else
7784                         Val > Expr_Value (Type_High_Bound (CPU_Id))
7785                      then
7786                         Error_Pragma_Arg
7787                           ("main subprogram CPU is out of range", Arg1);
7788                      end if;
7789                   end;
7790                end if;
7791
7792                Set_Main_CPU
7793                     (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
7794
7795             --  Task case
7796
7797             elsif Nkind (P) = N_Task_Definition then
7798                Arg := Get_Pragma_Arg (Arg1);
7799
7800                --  The expression must be analyzed in the special manner
7801                --  described in "Handling of Default and Per-Object
7802                --  Expressions" in sem.ads.
7803
7804                Preanalyze_Spec_Expression (Arg, RTE (RE_CPU_Range));
7805
7806             --  Anything else is incorrect
7807
7808             else
7809                Pragma_Misplaced;
7810             end if;
7811
7812             if Has_Pragma_CPU (P) then
7813                Error_Pragma ("duplicate pragma% not allowed");
7814             else
7815                Set_Has_Pragma_CPU (P, True);
7816
7817                if Nkind (P) = N_Task_Definition then
7818                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
7819                end if;
7820             end if;
7821          end CPU;
7822
7823          -----------
7824          -- Debug --
7825          -----------
7826
7827          --  pragma Debug ([boolean_EXPRESSION,] PROCEDURE_CALL_STATEMENT);
7828
7829          when Pragma_Debug => Debug : declare
7830             Cond : Node_Id;
7831             Call : Node_Id;
7832
7833          begin
7834             GNAT_Pragma;
7835
7836             --  Skip analysis if disabled
7837
7838             if Debug_Pragmas_Disabled then
7839                Rewrite (N, Make_Null_Statement (Loc));
7840                Analyze (N);
7841                return;
7842             end if;
7843
7844             Cond :=
7845               New_Occurrence_Of
7846                 (Boolean_Literals (Debug_Pragmas_Enabled and Expander_Active),
7847                  Loc);
7848
7849             if Debug_Pragmas_Enabled then
7850                Set_SCO_Pragma_Enabled (Loc);
7851             end if;
7852
7853             if Arg_Count = 2 then
7854                Cond :=
7855                  Make_And_Then (Loc,
7856                    Left_Opnd  => Relocate_Node (Cond),
7857                    Right_Opnd => Get_Pragma_Arg (Arg1));
7858                Call := Get_Pragma_Arg (Arg2);
7859             else
7860                Call := Get_Pragma_Arg (Arg1);
7861             end if;
7862
7863             if Nkind_In (Call,
7864                  N_Indexed_Component,
7865                  N_Function_Call,
7866                  N_Identifier,
7867                  N_Selected_Component)
7868             then
7869                --  If this pragma Debug comes from source, its argument was
7870                --  parsed as a name form (which is syntactically identical).
7871                --  Change it to a procedure call statement now.
7872
7873                Change_Name_To_Procedure_Call_Statement (Call);
7874
7875             elsif Nkind (Call) = N_Procedure_Call_Statement then
7876
7877                --  Already in the form of a procedure call statement: nothing
7878                --  to do (could happen in case of an internally generated
7879                --  pragma Debug).
7880
7881                null;
7882
7883             else
7884                --  All other cases: diagnose error
7885
7886                Error_Msg
7887                  ("argument of pragma ""Debug"" is not procedure call",
7888                   Sloc (Call));
7889                return;
7890             end if;
7891
7892             --  Rewrite into a conditional with an appropriate condition. We
7893             --  wrap the procedure call in a block so that overhead from e.g.
7894             --  use of the secondary stack does not generate execution overhead
7895             --  for suppressed conditions.
7896
7897             Rewrite (N, Make_Implicit_If_Statement (N,
7898               Condition => Cond,
7899                  Then_Statements => New_List (
7900                    Make_Block_Statement (Loc,
7901                      Handled_Statement_Sequence =>
7902                        Make_Handled_Sequence_Of_Statements (Loc,
7903                          Statements => New_List (Relocate_Node (Call)))))));
7904             Analyze (N);
7905          end Debug;
7906
7907          ------------------
7908          -- Debug_Policy --
7909          ------------------
7910
7911          --  pragma Debug_Policy (Check | Ignore)
7912
7913          when Pragma_Debug_Policy =>
7914             GNAT_Pragma;
7915             Check_Arg_Count (1);
7916             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Disable, Name_Ignore);
7917             Debug_Pragmas_Enabled :=
7918               Chars (Get_Pragma_Arg (Arg1)) = Name_Check;
7919             Debug_Pragmas_Disabled :=
7920               Chars (Get_Pragma_Arg (Arg1)) = Name_Disable;
7921
7922          ---------------------
7923          -- Detect_Blocking --
7924          ---------------------
7925
7926          --  pragma Detect_Blocking;
7927
7928          when Pragma_Detect_Blocking =>
7929             Ada_2005_Pragma;
7930             Check_Arg_Count (0);
7931             Check_Valid_Configuration_Pragma;
7932             Detect_Blocking := True;
7933
7934          --------------------------
7935          -- Default_Storage_Pool --
7936          --------------------------
7937
7938          --  pragma Default_Storage_Pool (storage_pool_NAME | null);
7939
7940          when Pragma_Default_Storage_Pool =>
7941             Ada_2012_Pragma;
7942             Check_Arg_Count (1);
7943
7944             --  Default_Storage_Pool can appear as a configuration pragma, or
7945             --  in a declarative part or a package spec.
7946
7947             if not Is_Configuration_Pragma then
7948                Check_Is_In_Decl_Part_Or_Package_Spec;
7949             end if;
7950
7951             --  Case of Default_Storage_Pool (null);
7952
7953             if Nkind (Expression (Arg1)) = N_Null then
7954                Analyze (Expression (Arg1));
7955
7956                --  This is an odd case, this is not really an expression, so
7957                --  we don't have a type for it. So just set the type to Empty.
7958
7959                Set_Etype (Expression (Arg1), Empty);
7960
7961             --  Case of Default_Storage_Pool (storage_pool_NAME);
7962
7963             else
7964                --  If it's a configuration pragma, then the only allowed
7965                --  argument is "null".
7966
7967                if Is_Configuration_Pragma then
7968                   Error_Pragma_Arg ("NULL expected", Arg1);
7969                end if;
7970
7971                --  The expected type for a non-"null" argument is
7972                --  Root_Storage_Pool'Class.
7973
7974                Analyze_And_Resolve
7975                  (Get_Pragma_Arg (Arg1),
7976                   Typ => Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
7977             end if;
7978
7979             --  Finally, record the pool name (or null). Freeze.Freeze_Entity
7980             --  for an access type will use this information to set the
7981             --  appropriate attributes of the access type.
7982
7983             Default_Pool := Expression (Arg1);
7984
7985          ---------------
7986          -- Dimension --
7987          ---------------
7988
7989          when Pragma_Dimension =>
7990             GNAT_Pragma;
7991             Check_Arg_Count (4);
7992             Check_No_Identifiers;
7993             Check_Arg_Is_Local_Name (Arg1);
7994
7995             if not Is_Type (Arg1) then
7996                Error_Pragma ("first argument for pragma% must be subtype");
7997             end if;
7998
7999             Check_Arg_Is_Static_Expression (Arg2, Standard_Integer);
8000             Check_Arg_Is_Static_Expression (Arg3, Standard_Integer);
8001             Check_Arg_Is_Static_Expression (Arg4, Standard_Integer);
8002
8003          ------------------------------------
8004          -- Disable_Atomic_Synchronization --
8005          ------------------------------------
8006
8007          --  pragma Disable_Atomic_Synchronization [(Entity)];
8008
8009          when Pragma_Disable_Atomic_Synchronization =>
8010             Process_Disable_Enable_Atomic_Sync (Name_Suppress);
8011
8012          -------------------
8013          -- Discard_Names --
8014          -------------------
8015
8016          --  pragma Discard_Names [([On =>] LOCAL_NAME)];
8017
8018          when Pragma_Discard_Names => Discard_Names : declare
8019             E    : Entity_Id;
8020             E_Id : Entity_Id;
8021
8022          begin
8023             Check_Ada_83_Warning;
8024
8025             --  Deal with configuration pragma case
8026
8027             if Arg_Count = 0 and then Is_Configuration_Pragma then
8028                Global_Discard_Names := True;
8029                return;
8030
8031             --  Otherwise, check correct appropriate context
8032
8033             else
8034                Check_Is_In_Decl_Part_Or_Package_Spec;
8035
8036                if Arg_Count = 0 then
8037
8038                   --  If there is no parameter, then from now on this pragma
8039                   --  applies to any enumeration, exception or tagged type
8040                   --  defined in the current declarative part, and recursively
8041                   --  to any nested scope.
8042
8043                   Set_Discard_Names (Current_Scope);
8044                   return;
8045
8046                else
8047                   Check_Arg_Count (1);
8048                   Check_Optional_Identifier (Arg1, Name_On);
8049                   Check_Arg_Is_Local_Name (Arg1);
8050
8051                   E_Id := Get_Pragma_Arg (Arg1);
8052
8053                   if Etype (E_Id) = Any_Type then
8054                      return;
8055                   else
8056                      E := Entity (E_Id);
8057                   end if;
8058
8059                   if (Is_First_Subtype (E)
8060                       and then
8061                         (Is_Enumeration_Type (E) or else Is_Tagged_Type (E)))
8062                     or else Ekind (E) = E_Exception
8063                   then
8064                      Set_Discard_Names (E);
8065                   else
8066                      Error_Pragma_Arg
8067                        ("inappropriate entity for pragma%", Arg1);
8068                   end if;
8069
8070                end if;
8071             end if;
8072          end Discard_Names;
8073
8074          ------------------------
8075          -- Dispatching_Domain --
8076          ------------------------
8077
8078          --  pragma Dispatching_Domain (EXPRESSION);
8079
8080          when Pragma_Dispatching_Domain => Dispatching_Domain : declare
8081             P   : constant Node_Id := Parent (N);
8082             Arg : Node_Id;
8083
8084          begin
8085             Ada_2012_Pragma;
8086             Check_No_Identifiers;
8087             Check_Arg_Count (1);
8088
8089             --  This pragma is born obsolete, but not the aspect
8090
8091             if not From_Aspect_Specification (N) then
8092                Check_Restriction
8093                  (No_Obsolescent_Features, Pragma_Identifier (N));
8094             end if;
8095
8096             if Nkind (P) = N_Task_Definition then
8097                Arg := Get_Pragma_Arg (Arg1);
8098
8099                --  The expression must be analyzed in the special manner
8100                --  described in "Handling of Default and Per-Object
8101                --  Expressions" in sem.ads.
8102
8103                Preanalyze_Spec_Expression (Arg, RTE (RE_Dispatching_Domain));
8104
8105             --  Anything else is incorrect
8106
8107             else
8108                Pragma_Misplaced;
8109             end if;
8110
8111             if Has_Pragma_Dispatching_Domain (P) then
8112                Error_Pragma ("duplicate pragma% not allowed");
8113             else
8114                Set_Has_Pragma_Dispatching_Domain (P, True);
8115
8116                if Nkind (P) = N_Task_Definition then
8117                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
8118                end if;
8119             end if;
8120          end Dispatching_Domain;
8121
8122          ---------------
8123          -- Elaborate --
8124          ---------------
8125
8126          --  pragma Elaborate (library_unit_NAME {, library_unit_NAME});
8127
8128          when Pragma_Elaborate => Elaborate : declare
8129             Arg   : Node_Id;
8130             Citem : Node_Id;
8131
8132          begin
8133             --  Pragma must be in context items list of a compilation unit
8134
8135             if not Is_In_Context_Clause then
8136                Pragma_Misplaced;
8137             end if;
8138
8139             --  Must be at least one argument
8140
8141             if Arg_Count = 0 then
8142                Error_Pragma ("pragma% requires at least one argument");
8143             end if;
8144
8145             --  In Ada 83 mode, there can be no items following it in the
8146             --  context list except other pragmas and implicit with clauses
8147             --  (e.g. those added by use of Rtsfind). In Ada 95 mode, this
8148             --  placement rule does not apply.
8149
8150             if Ada_Version = Ada_83 and then Comes_From_Source (N) then
8151                Citem := Next (N);
8152                while Present (Citem) loop
8153                   if Nkind (Citem) = N_Pragma
8154                     or else (Nkind (Citem) = N_With_Clause
8155                               and then Implicit_With (Citem))
8156                   then
8157                      null;
8158                   else
8159                      Error_Pragma
8160                        ("(Ada 83) pragma% must be at end of context clause");
8161                   end if;
8162
8163                   Next (Citem);
8164                end loop;
8165             end if;
8166
8167             --  Finally, the arguments must all be units mentioned in a with
8168             --  clause in the same context clause. Note we already checked (in
8169             --  Par.Prag) that the arguments are all identifiers or selected
8170             --  components.
8171
8172             Arg := Arg1;
8173             Outer : while Present (Arg) loop
8174                Citem := First (List_Containing (N));
8175                Inner : while Citem /= N loop
8176                   if Nkind (Citem) = N_With_Clause
8177                     and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
8178                   then
8179                      Set_Elaborate_Present (Citem, True);
8180                      Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
8181                      Generate_Reference (Entity (Name (Citem)), Citem);
8182
8183                      --  With the pragma present, elaboration calls on
8184                      --  subprograms from the named unit need no further
8185                      --  checks, as long as the pragma appears in the current
8186                      --  compilation unit. If the pragma appears in some unit
8187                      --  in the context, there might still be a need for an
8188                      --  Elaborate_All_Desirable from the current compilation
8189                      --  to the named unit, so we keep the check enabled.
8190
8191                      if In_Extended_Main_Source_Unit (N) then
8192                         Set_Suppress_Elaboration_Warnings
8193                           (Entity (Name (Citem)));
8194                      end if;
8195
8196                      exit Inner;
8197                   end if;
8198
8199                   Next (Citem);
8200                end loop Inner;
8201
8202                if Citem = N then
8203                   Error_Pragma_Arg
8204                     ("argument of pragma% is not with'ed unit", Arg);
8205                end if;
8206
8207                Next (Arg);
8208             end loop Outer;
8209
8210             --  Give a warning if operating in static mode with -gnatwl
8211             --  (elaboration warnings enabled) switch set.
8212
8213             if Elab_Warnings and not Dynamic_Elaboration_Checks then
8214                Error_Msg_N
8215                  ("?use of pragma Elaborate may not be safe", N);
8216                Error_Msg_N
8217                  ("?use pragma Elaborate_All instead if possible", N);
8218             end if;
8219          end Elaborate;
8220
8221          -------------------
8222          -- Elaborate_All --
8223          -------------------
8224
8225          --  pragma Elaborate_All (library_unit_NAME {, library_unit_NAME});
8226
8227          when Pragma_Elaborate_All => Elaborate_All : declare
8228             Arg   : Node_Id;
8229             Citem : Node_Id;
8230
8231          begin
8232             Check_Ada_83_Warning;
8233
8234             --  Pragma must be in context items list of a compilation unit
8235
8236             if not Is_In_Context_Clause then
8237                Pragma_Misplaced;
8238             end if;
8239
8240             --  Must be at least one argument
8241
8242             if Arg_Count = 0 then
8243                Error_Pragma ("pragma% requires at least one argument");
8244             end if;
8245
8246             --  Note: unlike pragma Elaborate, pragma Elaborate_All does not
8247             --  have to appear at the end of the context clause, but may
8248             --  appear mixed in with other items, even in Ada 83 mode.
8249
8250             --  Final check: the arguments must all be units mentioned in
8251             --  a with clause in the same context clause. Note that we
8252             --  already checked (in Par.Prag) that all the arguments are
8253             --  either identifiers or selected components.
8254
8255             Arg := Arg1;
8256             Outr : while Present (Arg) loop
8257                Citem := First (List_Containing (N));
8258                Innr : while Citem /= N loop
8259                   if Nkind (Citem) = N_With_Clause
8260                     and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
8261                   then
8262                      Set_Elaborate_All_Present (Citem, True);
8263                      Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
8264
8265                      --  Suppress warnings and elaboration checks on the named
8266                      --  unit if the pragma is in the current compilation, as
8267                      --  for pragma Elaborate.
8268
8269                      if In_Extended_Main_Source_Unit (N) then
8270                         Set_Suppress_Elaboration_Warnings
8271                           (Entity (Name (Citem)));
8272                      end if;
8273                      exit Innr;
8274                   end if;
8275
8276                   Next (Citem);
8277                end loop Innr;
8278
8279                if Citem = N then
8280                   Set_Error_Posted (N);
8281                   Error_Pragma_Arg
8282                     ("argument of pragma% is not with'ed unit", Arg);
8283                end if;
8284
8285                Next (Arg);
8286             end loop Outr;
8287          end Elaborate_All;
8288
8289          --------------------
8290          -- Elaborate_Body --
8291          --------------------
8292
8293          --  pragma Elaborate_Body [( library_unit_NAME )];
8294
8295          when Pragma_Elaborate_Body => Elaborate_Body : declare
8296             Cunit_Node : Node_Id;
8297             Cunit_Ent  : Entity_Id;
8298
8299          begin
8300             Check_Ada_83_Warning;
8301             Check_Valid_Library_Unit_Pragma;
8302
8303             if Nkind (N) = N_Null_Statement then
8304                return;
8305             end if;
8306
8307             Cunit_Node := Cunit (Current_Sem_Unit);
8308             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
8309
8310             if Nkind_In (Unit (Cunit_Node), N_Package_Body,
8311                                             N_Subprogram_Body)
8312             then
8313                Error_Pragma ("pragma% must refer to a spec, not a body");
8314             else
8315                Set_Body_Required (Cunit_Node, True);
8316                Set_Has_Pragma_Elaborate_Body (Cunit_Ent);
8317
8318                --  If we are in dynamic elaboration mode, then we suppress
8319                --  elaboration warnings for the unit, since it is definitely
8320                --  fine NOT to do dynamic checks at the first level (and such
8321                --  checks will be suppressed because no elaboration boolean
8322                --  is created for Elaborate_Body packages).
8323
8324                --  But in the static model of elaboration, Elaborate_Body is
8325                --  definitely NOT good enough to ensure elaboration safety on
8326                --  its own, since the body may WITH other units that are not
8327                --  safe from an elaboration point of view, so a client must
8328                --  still do an Elaborate_All on such units.
8329
8330                --  Debug flag -gnatdD restores the old behavior of 3.13, where
8331                --  Elaborate_Body always suppressed elab warnings.
8332
8333                if Dynamic_Elaboration_Checks or Debug_Flag_DD then
8334                   Set_Suppress_Elaboration_Warnings (Cunit_Ent);
8335                end if;
8336             end if;
8337          end Elaborate_Body;
8338
8339          ------------------------
8340          -- Elaboration_Checks --
8341          ------------------------
8342
8343          --  pragma Elaboration_Checks (Static | Dynamic);
8344
8345          when Pragma_Elaboration_Checks =>
8346             GNAT_Pragma;
8347             Check_Arg_Count (1);
8348             Check_Arg_Is_One_Of (Arg1, Name_Static, Name_Dynamic);
8349             Dynamic_Elaboration_Checks :=
8350               (Chars (Get_Pragma_Arg (Arg1)) = Name_Dynamic);
8351
8352          ---------------
8353          -- Eliminate --
8354          ---------------
8355
8356          --  pragma Eliminate (
8357          --      [Unit_Name  =>] IDENTIFIER | SELECTED_COMPONENT,
8358          --    [,[Entity     =>] IDENTIFIER |
8359          --                      SELECTED_COMPONENT |
8360          --                      STRING_LITERAL]
8361          --    [,                OVERLOADING_RESOLUTION]);
8362
8363          --  OVERLOADING_RESOLUTION ::= PARAMETER_AND_RESULT_TYPE_PROFILE |
8364          --                             SOURCE_LOCATION
8365
8366          --  PARAMETER_AND_RESULT_TYPE_PROFILE ::= PROCEDURE_PROFILE |
8367          --                                        FUNCTION_PROFILE
8368
8369          --  PROCEDURE_PROFILE ::= Parameter_Types => PARAMETER_TYPES
8370
8371          --  FUNCTION_PROFILE ::= [Parameter_Types => PARAMETER_TYPES,]
8372          --                       Result_Type => result_SUBTYPE_NAME]
8373
8374          --  PARAMETER_TYPES ::= (SUBTYPE_NAME {, SUBTYPE_NAME})
8375          --  SUBTYPE_NAME    ::= STRING_LITERAL
8376
8377          --  SOURCE_LOCATION ::= Source_Location => SOURCE_TRACE
8378          --  SOURCE_TRACE    ::= STRING_LITERAL
8379
8380          when Pragma_Eliminate => Eliminate : declare
8381             Args  : Args_List (1 .. 5);
8382             Names : constant Name_List (1 .. 5) := (
8383                       Name_Unit_Name,
8384                       Name_Entity,
8385                       Name_Parameter_Types,
8386                       Name_Result_Type,
8387                       Name_Source_Location);
8388
8389             Unit_Name       : Node_Id renames Args (1);
8390             Entity          : Node_Id renames Args (2);
8391             Parameter_Types : Node_Id renames Args (3);
8392             Result_Type     : Node_Id renames Args (4);
8393             Source_Location : Node_Id renames Args (5);
8394
8395          begin
8396             GNAT_Pragma;
8397             Check_Valid_Configuration_Pragma;
8398             Gather_Associations (Names, Args);
8399
8400             if No (Unit_Name) then
8401                Error_Pragma ("missing Unit_Name argument for pragma%");
8402             end if;
8403
8404             if No (Entity)
8405               and then (Present (Parameter_Types)
8406                           or else
8407                         Present (Result_Type)
8408                           or else
8409                         Present (Source_Location))
8410             then
8411                Error_Pragma ("missing Entity argument for pragma%");
8412             end if;
8413
8414             if (Present (Parameter_Types)
8415                   or else
8416                 Present (Result_Type))
8417               and then
8418                 Present (Source_Location)
8419             then
8420                Error_Pragma
8421                  ("parameter profile and source location cannot " &
8422                   "be used together in pragma%");
8423             end if;
8424
8425             Process_Eliminate_Pragma
8426               (N,
8427                Unit_Name,
8428                Entity,
8429                Parameter_Types,
8430                Result_Type,
8431                Source_Location);
8432          end Eliminate;
8433
8434          -----------------------------------
8435          -- Enable_Atomic_Synchronization --
8436          -----------------------------------
8437
8438          --  pragma Enable_Atomic_Synchronization [(Entity)];
8439
8440          when Pragma_Enable_Atomic_Synchronization =>
8441             Process_Disable_Enable_Atomic_Sync (Name_Unsuppress);
8442
8443          ------------
8444          -- Export --
8445          ------------
8446
8447          --  pragma Export (
8448          --    [   Convention    =>] convention_IDENTIFIER,
8449          --    [   Entity        =>] local_NAME
8450          --    [, [External_Name =>] static_string_EXPRESSION ]
8451          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
8452
8453          when Pragma_Export => Export : declare
8454             C      : Convention_Id;
8455             Def_Id : Entity_Id;
8456
8457             pragma Warnings (Off, C);
8458
8459          begin
8460             Check_Ada_83_Warning;
8461             Check_Arg_Order
8462               ((Name_Convention,
8463                 Name_Entity,
8464                 Name_External_Name,
8465                 Name_Link_Name));
8466             Check_At_Least_N_Arguments (2);
8467             Check_At_Most_N_Arguments  (4);
8468             Process_Convention (C, Def_Id);
8469
8470             if Ekind (Def_Id) /= E_Constant then
8471                Note_Possible_Modification
8472                  (Get_Pragma_Arg (Arg2), Sure => False);
8473             end if;
8474
8475             Process_Interface_Name (Def_Id, Arg3, Arg4);
8476             Set_Exported (Def_Id, Arg2);
8477
8478             --  If the entity is a deferred constant, propagate the information
8479             --  to the full view, because gigi elaborates the full view only.
8480
8481             if Ekind (Def_Id) = E_Constant
8482               and then Present (Full_View (Def_Id))
8483             then
8484                declare
8485                   Id2 : constant Entity_Id := Full_View (Def_Id);
8486                begin
8487                   Set_Is_Exported    (Id2, Is_Exported          (Def_Id));
8488                   Set_First_Rep_Item (Id2, First_Rep_Item       (Def_Id));
8489                   Set_Interface_Name (Id2, Einfo.Interface_Name (Def_Id));
8490                end;
8491             end if;
8492          end Export;
8493
8494          ----------------------
8495          -- Export_Exception --
8496          ----------------------
8497
8498          --  pragma Export_Exception (
8499          --        [Internal         =>] LOCAL_NAME
8500          --     [, [External         =>] EXTERNAL_SYMBOL]
8501          --     [, [Form     =>] Ada | VMS]
8502          --     [, [Code     =>] static_integer_EXPRESSION]);
8503
8504          when Pragma_Export_Exception => Export_Exception : declare
8505             Args  : Args_List (1 .. 4);
8506             Names : constant Name_List (1 .. 4) := (
8507                       Name_Internal,
8508                       Name_External,
8509                       Name_Form,
8510                       Name_Code);
8511
8512             Internal : Node_Id renames Args (1);
8513             External : Node_Id renames Args (2);
8514             Form     : Node_Id renames Args (3);
8515             Code     : Node_Id renames Args (4);
8516
8517          begin
8518             GNAT_Pragma;
8519
8520             if Inside_A_Generic then
8521                Error_Pragma ("pragma% cannot be used for generic entities");
8522             end if;
8523
8524             Gather_Associations (Names, Args);
8525             Process_Extended_Import_Export_Exception_Pragma (
8526               Arg_Internal => Internal,
8527               Arg_External => External,
8528               Arg_Form     => Form,
8529               Arg_Code     => Code);
8530
8531             if not Is_VMS_Exception (Entity (Internal)) then
8532                Set_Exported (Entity (Internal), Internal);
8533             end if;
8534          end Export_Exception;
8535
8536          ---------------------
8537          -- Export_Function --
8538          ---------------------
8539
8540          --  pragma Export_Function (
8541          --        [Internal         =>] LOCAL_NAME
8542          --     [, [External         =>] EXTERNAL_SYMBOL]
8543          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8544          --     [, [Result_Type      =>] TYPE_DESIGNATOR]
8545          --     [, [Mechanism        =>] MECHANISM]
8546          --     [, [Result_Mechanism =>] MECHANISM_NAME]);
8547
8548          --  EXTERNAL_SYMBOL ::=
8549          --    IDENTIFIER
8550          --  | static_string_EXPRESSION
8551
8552          --  PARAMETER_TYPES ::=
8553          --    null
8554          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8555
8556          --  TYPE_DESIGNATOR ::=
8557          --    subtype_NAME
8558          --  | subtype_Name ' Access
8559
8560          --  MECHANISM ::=
8561          --    MECHANISM_NAME
8562          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8563
8564          --  MECHANISM_ASSOCIATION ::=
8565          --    [formal_parameter_NAME =>] MECHANISM_NAME
8566
8567          --  MECHANISM_NAME ::=
8568          --    Value
8569          --  | Reference
8570          --  | Descriptor [([Class =>] CLASS_NAME)]
8571
8572          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8573
8574          when Pragma_Export_Function => Export_Function : declare
8575             Args  : Args_List (1 .. 6);
8576             Names : constant Name_List (1 .. 6) := (
8577                       Name_Internal,
8578                       Name_External,
8579                       Name_Parameter_Types,
8580                       Name_Result_Type,
8581                       Name_Mechanism,
8582                       Name_Result_Mechanism);
8583
8584             Internal         : Node_Id renames Args (1);
8585             External         : Node_Id renames Args (2);
8586             Parameter_Types  : Node_Id renames Args (3);
8587             Result_Type      : Node_Id renames Args (4);
8588             Mechanism        : Node_Id renames Args (5);
8589             Result_Mechanism : Node_Id renames Args (6);
8590
8591          begin
8592             GNAT_Pragma;
8593             Gather_Associations (Names, Args);
8594             Process_Extended_Import_Export_Subprogram_Pragma (
8595               Arg_Internal         => Internal,
8596               Arg_External         => External,
8597               Arg_Parameter_Types  => Parameter_Types,
8598               Arg_Result_Type      => Result_Type,
8599               Arg_Mechanism        => Mechanism,
8600               Arg_Result_Mechanism => Result_Mechanism);
8601          end Export_Function;
8602
8603          -------------------
8604          -- Export_Object --
8605          -------------------
8606
8607          --  pragma Export_Object (
8608          --        [Internal =>] LOCAL_NAME
8609          --     [, [External =>] EXTERNAL_SYMBOL]
8610          --     [, [Size     =>] EXTERNAL_SYMBOL]);
8611
8612          --  EXTERNAL_SYMBOL ::=
8613          --    IDENTIFIER
8614          --  | static_string_EXPRESSION
8615
8616          --  PARAMETER_TYPES ::=
8617          --    null
8618          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8619
8620          --  TYPE_DESIGNATOR ::=
8621          --    subtype_NAME
8622          --  | subtype_Name ' Access
8623
8624          --  MECHANISM ::=
8625          --    MECHANISM_NAME
8626          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8627
8628          --  MECHANISM_ASSOCIATION ::=
8629          --    [formal_parameter_NAME =>] MECHANISM_NAME
8630
8631          --  MECHANISM_NAME ::=
8632          --    Value
8633          --  | Reference
8634          --  | Descriptor [([Class =>] CLASS_NAME)]
8635
8636          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8637
8638          when Pragma_Export_Object => Export_Object : declare
8639             Args  : Args_List (1 .. 3);
8640             Names : constant Name_List (1 .. 3) := (
8641                       Name_Internal,
8642                       Name_External,
8643                       Name_Size);
8644
8645             Internal : Node_Id renames Args (1);
8646             External : Node_Id renames Args (2);
8647             Size     : Node_Id renames Args (3);
8648
8649          begin
8650             GNAT_Pragma;
8651             Gather_Associations (Names, Args);
8652             Process_Extended_Import_Export_Object_Pragma (
8653               Arg_Internal => Internal,
8654               Arg_External => External,
8655               Arg_Size     => Size);
8656          end Export_Object;
8657
8658          ----------------------
8659          -- Export_Procedure --
8660          ----------------------
8661
8662          --  pragma Export_Procedure (
8663          --        [Internal         =>] LOCAL_NAME
8664          --     [, [External         =>] EXTERNAL_SYMBOL]
8665          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8666          --     [, [Mechanism        =>] MECHANISM]);
8667
8668          --  EXTERNAL_SYMBOL ::=
8669          --    IDENTIFIER
8670          --  | static_string_EXPRESSION
8671
8672          --  PARAMETER_TYPES ::=
8673          --    null
8674          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8675
8676          --  TYPE_DESIGNATOR ::=
8677          --    subtype_NAME
8678          --  | subtype_Name ' Access
8679
8680          --  MECHANISM ::=
8681          --    MECHANISM_NAME
8682          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8683
8684          --  MECHANISM_ASSOCIATION ::=
8685          --    [formal_parameter_NAME =>] MECHANISM_NAME
8686
8687          --  MECHANISM_NAME ::=
8688          --    Value
8689          --  | Reference
8690          --  | Descriptor [([Class =>] CLASS_NAME)]
8691
8692          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8693
8694          when Pragma_Export_Procedure => Export_Procedure : declare
8695             Args  : Args_List (1 .. 4);
8696             Names : constant Name_List (1 .. 4) := (
8697                       Name_Internal,
8698                       Name_External,
8699                       Name_Parameter_Types,
8700                       Name_Mechanism);
8701
8702             Internal        : Node_Id renames Args (1);
8703             External        : Node_Id renames Args (2);
8704             Parameter_Types : Node_Id renames Args (3);
8705             Mechanism       : Node_Id renames Args (4);
8706
8707          begin
8708             GNAT_Pragma;
8709             Gather_Associations (Names, Args);
8710             Process_Extended_Import_Export_Subprogram_Pragma (
8711               Arg_Internal        => Internal,
8712               Arg_External        => External,
8713               Arg_Parameter_Types => Parameter_Types,
8714               Arg_Mechanism       => Mechanism);
8715          end Export_Procedure;
8716
8717          ------------------
8718          -- Export_Value --
8719          ------------------
8720
8721          --  pragma Export_Value (
8722          --     [Value     =>] static_integer_EXPRESSION,
8723          --     [Link_Name =>] static_string_EXPRESSION);
8724
8725          when Pragma_Export_Value =>
8726             GNAT_Pragma;
8727             Check_Arg_Order ((Name_Value, Name_Link_Name));
8728             Check_Arg_Count (2);
8729
8730             Check_Optional_Identifier (Arg1, Name_Value);
8731             Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
8732
8733             Check_Optional_Identifier (Arg2, Name_Link_Name);
8734             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
8735
8736          -----------------------------
8737          -- Export_Valued_Procedure --
8738          -----------------------------
8739
8740          --  pragma Export_Valued_Procedure (
8741          --        [Internal         =>] LOCAL_NAME
8742          --     [, [External         =>] EXTERNAL_SYMBOL,]
8743          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8744          --     [, [Mechanism        =>] MECHANISM]);
8745
8746          --  EXTERNAL_SYMBOL ::=
8747          --    IDENTIFIER
8748          --  | static_string_EXPRESSION
8749
8750          --  PARAMETER_TYPES ::=
8751          --    null
8752          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8753
8754          --  TYPE_DESIGNATOR ::=
8755          --    subtype_NAME
8756          --  | subtype_Name ' Access
8757
8758          --  MECHANISM ::=
8759          --    MECHANISM_NAME
8760          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8761
8762          --  MECHANISM_ASSOCIATION ::=
8763          --    [formal_parameter_NAME =>] MECHANISM_NAME
8764
8765          --  MECHANISM_NAME ::=
8766          --    Value
8767          --  | Reference
8768          --  | Descriptor [([Class =>] CLASS_NAME)]
8769
8770          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8771
8772          when Pragma_Export_Valued_Procedure =>
8773          Export_Valued_Procedure : declare
8774             Args  : Args_List (1 .. 4);
8775             Names : constant Name_List (1 .. 4) := (
8776                       Name_Internal,
8777                       Name_External,
8778                       Name_Parameter_Types,
8779                       Name_Mechanism);
8780
8781             Internal        : Node_Id renames Args (1);
8782             External        : Node_Id renames Args (2);
8783             Parameter_Types : Node_Id renames Args (3);
8784             Mechanism       : Node_Id renames Args (4);
8785
8786          begin
8787             GNAT_Pragma;
8788             Gather_Associations (Names, Args);
8789             Process_Extended_Import_Export_Subprogram_Pragma (
8790               Arg_Internal        => Internal,
8791               Arg_External        => External,
8792               Arg_Parameter_Types => Parameter_Types,
8793               Arg_Mechanism       => Mechanism);
8794          end Export_Valued_Procedure;
8795
8796          -------------------
8797          -- Extend_System --
8798          -------------------
8799
8800          --  pragma Extend_System ([Name =>] Identifier);
8801
8802          when Pragma_Extend_System => Extend_System : declare
8803          begin
8804             GNAT_Pragma;
8805             Check_Valid_Configuration_Pragma;
8806             Check_Arg_Count (1);
8807             Check_Optional_Identifier (Arg1, Name_Name);
8808             Check_Arg_Is_Identifier (Arg1);
8809
8810             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
8811
8812             if Name_Len > 4
8813               and then Name_Buffer (1 .. 4) = "aux_"
8814             then
8815                if Present (System_Extend_Pragma_Arg) then
8816                   if Chars (Get_Pragma_Arg (Arg1)) =
8817                      Chars (Expression (System_Extend_Pragma_Arg))
8818                   then
8819                      null;
8820                   else
8821                      Error_Msg_Sloc := Sloc (System_Extend_Pragma_Arg);
8822                      Error_Pragma ("pragma% conflicts with that #");
8823                   end if;
8824
8825                else
8826                   System_Extend_Pragma_Arg := Arg1;
8827
8828                   if not GNAT_Mode then
8829                      System_Extend_Unit := Arg1;
8830                   end if;
8831                end if;
8832             else
8833                Error_Pragma ("incorrect name for pragma%, must be Aux_xxx");
8834             end if;
8835          end Extend_System;
8836
8837          ------------------------
8838          -- Extensions_Allowed --
8839          ------------------------
8840
8841          --  pragma Extensions_Allowed (ON | OFF);
8842
8843          when Pragma_Extensions_Allowed =>
8844             GNAT_Pragma;
8845             Check_Arg_Count (1);
8846             Check_No_Identifiers;
8847             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
8848
8849             if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
8850                Extensions_Allowed := True;
8851                Ada_Version := Ada_Version_Type'Last;
8852
8853             else
8854                Extensions_Allowed := False;
8855                Ada_Version := Ada_Version_Explicit;
8856             end if;
8857
8858          --------------
8859          -- External --
8860          --------------
8861
8862          --  pragma External (
8863          --    [   Convention    =>] convention_IDENTIFIER,
8864          --    [   Entity        =>] local_NAME
8865          --    [, [External_Name =>] static_string_EXPRESSION ]
8866          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
8867
8868          when Pragma_External => External : declare
8869                Def_Id : Entity_Id;
8870
8871                C : Convention_Id;
8872                pragma Warnings (Off, C);
8873
8874          begin
8875             GNAT_Pragma;
8876             Check_Arg_Order
8877               ((Name_Convention,
8878                 Name_Entity,
8879                 Name_External_Name,
8880                 Name_Link_Name));
8881             Check_At_Least_N_Arguments (2);
8882             Check_At_Most_N_Arguments  (4);
8883             Process_Convention (C, Def_Id);
8884             Note_Possible_Modification
8885               (Get_Pragma_Arg (Arg2), Sure => False);
8886             Process_Interface_Name (Def_Id, Arg3, Arg4);
8887             Set_Exported (Def_Id, Arg2);
8888          end External;
8889
8890          --------------------------
8891          -- External_Name_Casing --
8892          --------------------------
8893
8894          --  pragma External_Name_Casing (
8895          --    UPPERCASE | LOWERCASE
8896          --    [, AS_IS | UPPERCASE | LOWERCASE]);
8897
8898          when Pragma_External_Name_Casing => External_Name_Casing : declare
8899          begin
8900             GNAT_Pragma;
8901             Check_No_Identifiers;
8902
8903             if Arg_Count = 2 then
8904                Check_Arg_Is_One_Of
8905                  (Arg2, Name_As_Is, Name_Uppercase, Name_Lowercase);
8906
8907                case Chars (Get_Pragma_Arg (Arg2)) is
8908                   when Name_As_Is     =>
8909                      Opt.External_Name_Exp_Casing := As_Is;
8910
8911                   when Name_Uppercase =>
8912                      Opt.External_Name_Exp_Casing := Uppercase;
8913
8914                   when Name_Lowercase =>
8915                      Opt.External_Name_Exp_Casing := Lowercase;
8916
8917                   when others =>
8918                      null;
8919                end case;
8920
8921             else
8922                Check_Arg_Count (1);
8923             end if;
8924
8925             Check_Arg_Is_One_Of (Arg1, Name_Uppercase, Name_Lowercase);
8926
8927             case Chars (Get_Pragma_Arg (Arg1)) is
8928                when Name_Uppercase =>
8929                   Opt.External_Name_Imp_Casing := Uppercase;
8930
8931                when Name_Lowercase =>
8932                   Opt.External_Name_Imp_Casing := Lowercase;
8933
8934                when others =>
8935                   null;
8936             end case;
8937          end External_Name_Casing;
8938
8939          --------------------------
8940          -- Favor_Top_Level --
8941          --------------------------
8942
8943          --  pragma Favor_Top_Level (type_NAME);
8944
8945          when Pragma_Favor_Top_Level => Favor_Top_Level : declare
8946                Named_Entity : Entity_Id;
8947
8948          begin
8949             GNAT_Pragma;
8950             Check_No_Identifiers;
8951             Check_Arg_Count (1);
8952             Check_Arg_Is_Local_Name (Arg1);
8953             Named_Entity := Entity (Get_Pragma_Arg (Arg1));
8954
8955             --  If it's an access-to-subprogram type (in particular, not a
8956             --  subtype), set the flag on that type.
8957
8958             if Is_Access_Subprogram_Type (Named_Entity) then
8959                Set_Can_Use_Internal_Rep (Named_Entity, False);
8960
8961             --  Otherwise it's an error (name denotes the wrong sort of entity)
8962
8963             else
8964                Error_Pragma_Arg
8965                  ("access-to-subprogram type expected",
8966                   Get_Pragma_Arg (Arg1));
8967             end if;
8968          end Favor_Top_Level;
8969
8970          ---------------
8971          -- Fast_Math --
8972          ---------------
8973
8974          --  pragma Fast_Math;
8975
8976          when Pragma_Fast_Math =>
8977             GNAT_Pragma;
8978             Check_No_Identifiers;
8979             Check_Valid_Configuration_Pragma;
8980             Fast_Math := True;
8981
8982          ---------------------------
8983          -- Finalize_Storage_Only --
8984          ---------------------------
8985
8986          --  pragma Finalize_Storage_Only (first_subtype_LOCAL_NAME);
8987
8988          when Pragma_Finalize_Storage_Only => Finalize_Storage : declare
8989             Assoc   : constant Node_Id := Arg1;
8990             Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
8991             Typ     : Entity_Id;
8992
8993          begin
8994             GNAT_Pragma;
8995             Check_No_Identifiers;
8996             Check_Arg_Count (1);
8997             Check_Arg_Is_Local_Name (Arg1);
8998
8999             Find_Type (Type_Id);
9000             Typ := Entity (Type_Id);
9001
9002             if Typ = Any_Type
9003               or else Rep_Item_Too_Early (Typ, N)
9004             then
9005                return;
9006             else
9007                Typ := Underlying_Type (Typ);
9008             end if;
9009
9010             if not Is_Controlled (Typ) then
9011                Error_Pragma ("pragma% must specify controlled type");
9012             end if;
9013
9014             Check_First_Subtype (Arg1);
9015
9016             if Finalize_Storage_Only (Typ) then
9017                Error_Pragma ("duplicate pragma%, only one allowed");
9018
9019             elsif not Rep_Item_Too_Late (Typ, N) then
9020                Set_Finalize_Storage_Only (Base_Type (Typ), True);
9021             end if;
9022          end Finalize_Storage;
9023
9024          --------------------------
9025          -- Float_Representation --
9026          --------------------------
9027
9028          --  pragma Float_Representation (FLOAT_REP[, float_type_LOCAL_NAME]);
9029
9030          --  FLOAT_REP ::= VAX_Float | IEEE_Float
9031
9032          when Pragma_Float_Representation => Float_Representation : declare
9033             Argx : Node_Id;
9034             Digs : Nat;
9035             Ent  : Entity_Id;
9036
9037          begin
9038             GNAT_Pragma;
9039
9040             if Arg_Count = 1 then
9041                Check_Valid_Configuration_Pragma;
9042             else
9043                Check_Arg_Count (2);
9044                Check_Optional_Identifier (Arg2, Name_Entity);
9045                Check_Arg_Is_Local_Name (Arg2);
9046             end if;
9047
9048             Check_No_Identifier (Arg1);
9049             Check_Arg_Is_One_Of (Arg1, Name_VAX_Float, Name_IEEE_Float);
9050
9051             if not OpenVMS_On_Target then
9052                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9053                   Error_Pragma
9054                     ("?pragma% ignored (applies only to Open'V'M'S)");
9055                end if;
9056
9057                return;
9058             end if;
9059
9060             --  One argument case
9061
9062             if Arg_Count = 1 then
9063                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9064                   if Opt.Float_Format = 'I' then
9065                      Error_Pragma ("'I'E'E'E format previously specified");
9066                   end if;
9067
9068                   Opt.Float_Format := 'V';
9069
9070                else
9071                   if Opt.Float_Format = 'V' then
9072                      Error_Pragma ("'V'A'X format previously specified");
9073                   end if;
9074
9075                   Opt.Float_Format := 'I';
9076                end if;
9077
9078                Set_Standard_Fpt_Formats;
9079
9080             --  Two argument case
9081
9082             else
9083                Argx := Get_Pragma_Arg (Arg2);
9084
9085                if not Is_Entity_Name (Argx)
9086                  or else not Is_Floating_Point_Type (Entity (Argx))
9087                then
9088                   Error_Pragma_Arg
9089                     ("second argument of% pragma must be floating-point type",
9090                      Arg2);
9091                end if;
9092
9093                Ent  := Entity (Argx);
9094                Digs := UI_To_Int (Digits_Value (Ent));
9095
9096                --  Two arguments, VAX_Float case
9097
9098                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9099                   case Digs is
9100                      when  6 => Set_F_Float (Ent);
9101                      when  9 => Set_D_Float (Ent);
9102                      when 15 => Set_G_Float (Ent);
9103
9104                      when others =>
9105                         Error_Pragma_Arg
9106                           ("wrong digits value, must be 6,9 or 15", Arg2);
9107                   end case;
9108
9109                --  Two arguments, IEEE_Float case
9110
9111                else
9112                   case Digs is
9113                      when  6 => Set_IEEE_Short (Ent);
9114                      when 15 => Set_IEEE_Long  (Ent);
9115
9116                      when others =>
9117                         Error_Pragma_Arg
9118                           ("wrong digits value, must be 6 or 15", Arg2);
9119                   end case;
9120                end if;
9121             end if;
9122          end Float_Representation;
9123
9124          -----------
9125          -- Ident --
9126          -----------
9127
9128          --  pragma Ident (static_string_EXPRESSION)
9129
9130          --  Note: pragma Comment shares this processing. Pragma Comment is
9131          --  identical to Ident, except that the restriction of the argument to
9132          --  31 characters and the placement restrictions are not enforced for
9133          --  pragma Comment.
9134
9135          when Pragma_Ident | Pragma_Comment => Ident : declare
9136             Str : Node_Id;
9137
9138          begin
9139             GNAT_Pragma;
9140             Check_Arg_Count (1);
9141             Check_No_Identifiers;
9142             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
9143             Store_Note (N);
9144
9145             --  For pragma Ident, preserve DEC compatibility by requiring the
9146             --  pragma to appear in a declarative part or package spec.
9147
9148             if Prag_Id = Pragma_Ident then
9149                Check_Is_In_Decl_Part_Or_Package_Spec;
9150             end if;
9151
9152             Str := Expr_Value_S (Get_Pragma_Arg (Arg1));
9153
9154             declare
9155                CS : Node_Id;
9156                GP : Node_Id;
9157
9158             begin
9159                GP := Parent (Parent (N));
9160
9161                if Nkind_In (GP, N_Package_Declaration,
9162                                 N_Generic_Package_Declaration)
9163                then
9164                   GP := Parent (GP);
9165                end if;
9166
9167                --  If we have a compilation unit, then record the ident value,
9168                --  checking for improper duplication.
9169
9170                if Nkind (GP) = N_Compilation_Unit then
9171                   CS := Ident_String (Current_Sem_Unit);
9172
9173                   if Present (CS) then
9174
9175                      --  For Ident, we do not permit multiple instances
9176
9177                      if Prag_Id = Pragma_Ident then
9178                         Error_Pragma ("duplicate% pragma not permitted");
9179
9180                      --  For Comment, we concatenate the string, unless we want
9181                      --  to preserve the tree structure for ASIS.
9182
9183                      elsif not ASIS_Mode then
9184                         Start_String (Strval (CS));
9185                         Store_String_Char (' ');
9186                         Store_String_Chars (Strval (Str));
9187                         Set_Strval (CS, End_String);
9188                      end if;
9189
9190                   else
9191                      --  In VMS, the effect of IDENT is achieved by passing
9192                      --  --identification=name as a --for-linker switch.
9193
9194                      if OpenVMS_On_Target then
9195                         Start_String;
9196                         Store_String_Chars
9197                           ("--for-linker=--identification=");
9198                         String_To_Name_Buffer (Strval (Str));
9199                         Store_String_Chars (Name_Buffer (1 .. Name_Len));
9200
9201                         --  Only the last processed IDENT is saved. The main
9202                         --  purpose is so an IDENT associated with a main
9203                         --  procedure will be used in preference to an IDENT
9204                         --  associated with a with'd package.
9205
9206                         Replace_Linker_Option_String
9207                           (End_String, "--for-linker=--identification=");
9208                      end if;
9209
9210                      Set_Ident_String (Current_Sem_Unit, Str);
9211                   end if;
9212
9213                --  For subunits, we just ignore the Ident, since in GNAT these
9214                --  are not separate object files, and hence not separate units
9215                --  in the unit table.
9216
9217                elsif Nkind (GP) = N_Subunit then
9218                   null;
9219
9220                --  Otherwise we have a misplaced pragma Ident, but we ignore
9221                --  this if we are in an instantiation, since it comes from
9222                --  a generic, and has no relevance to the instantiation.
9223
9224                elsif Prag_Id = Pragma_Ident then
9225                   if Instantiation_Location (Loc) = No_Location then
9226                      Error_Pragma ("pragma% only allowed at outer level");
9227                   end if;
9228                end if;
9229             end;
9230          end Ident;
9231
9232          ----------------------------
9233          -- Implementation_Defined --
9234          ----------------------------
9235
9236          --  pragma Implementation_Defined (local_NAME);
9237
9238          --  Marks previously declared entity as implementation defined. For
9239          --  an overloaded entity, applies to the most recent homonym.
9240
9241          --  pragma Implementation_Defined;
9242
9243          --  The form with no arguments appears anywhere within a scope, most
9244          --  typically a package spec, and indicates that all entities that are
9245          --  defined within the package spec are Implementation_Defined.
9246
9247          when Pragma_Implementation_Defined => Implementation_Defined : declare
9248             Ent : Entity_Id;
9249
9250          begin
9251             Check_No_Identifiers;
9252
9253             --  Form with no arguments
9254
9255             if Arg_Count = 0 then
9256                Set_Is_Implementation_Defined (Current_Scope);
9257
9258             --  Form with one argument
9259
9260             else
9261                Check_Arg_Count (1);
9262                Check_Arg_Is_Local_Name (Arg1);
9263                Ent := Entity (Get_Pragma_Arg (Arg1));
9264                Set_Is_Implementation_Defined (Ent);
9265             end if;
9266          end Implementation_Defined;
9267
9268          -----------------
9269          -- Implemented --
9270          -----------------
9271
9272          --  pragma Implemented (procedure_LOCAL_NAME, implementation_kind);
9273          --  implementation_kind ::= By_Entry | By_Protected_Procedure | By_Any
9274
9275          when Pragma_Implemented => Implemented : declare
9276             Proc_Id : Entity_Id;
9277             Typ     : Entity_Id;
9278
9279          begin
9280             Ada_2012_Pragma;
9281             Check_Arg_Count (2);
9282             Check_No_Identifiers;
9283             Check_Arg_Is_Identifier (Arg1);
9284             Check_Arg_Is_Local_Name (Arg1);
9285             Check_Arg_Is_One_Of
9286               (Arg2, Name_By_Any, Name_By_Entry, Name_By_Protected_Procedure);
9287
9288             --  Extract the name of the local procedure
9289
9290             Proc_Id := Entity (Get_Pragma_Arg (Arg1));
9291
9292             --  Ada 2012 (AI05-0030): The procedure_LOCAL_NAME must denote a
9293             --  primitive procedure of a synchronized tagged type.
9294
9295             if Ekind (Proc_Id) = E_Procedure
9296               and then Is_Primitive (Proc_Id)
9297               and then Present (First_Formal (Proc_Id))
9298             then
9299                Typ := Etype (First_Formal (Proc_Id));
9300
9301                if Is_Tagged_Type (Typ)
9302                  and then
9303
9304                   --  Check for a protected, a synchronized or a task interface
9305
9306                    ((Is_Interface (Typ)
9307                        and then Is_Synchronized_Interface (Typ))
9308
9309                   --  Check for a protected type or a task type that implements
9310                   --  an interface.
9311
9312                    or else
9313                     (Is_Concurrent_Record_Type (Typ)
9314                        and then Present (Interfaces (Typ)))
9315
9316                   --  Check for a private record extension with keyword
9317                   --  "synchronized".
9318
9319                    or else
9320                     (Ekind_In (Typ, E_Record_Type_With_Private,
9321                                     E_Record_Subtype_With_Private)
9322                        and then Synchronized_Present (Parent (Typ))))
9323                then
9324                   null;
9325                else
9326                   Error_Pragma_Arg
9327                     ("controlling formal must be of synchronized " &
9328                      "tagged type", Arg1);
9329                   return;
9330                end if;
9331
9332             --  Procedures declared inside a protected type must be accepted
9333
9334             elsif Ekind (Proc_Id) = E_Procedure
9335               and then Is_Protected_Type (Scope (Proc_Id))
9336             then
9337                null;
9338
9339             --  The first argument is not a primitive procedure
9340
9341             else
9342                Error_Pragma_Arg
9343                  ("pragma % must be applied to a primitive procedure", Arg1);
9344                return;
9345             end if;
9346
9347             --  Ada 2012 (AI05-0030): Cannot apply the implementation_kind
9348             --  By_Protected_Procedure to the primitive procedure of a task
9349             --  interface.
9350
9351             if Chars (Arg2) = Name_By_Protected_Procedure
9352               and then Is_Interface (Typ)
9353               and then Is_Task_Interface (Typ)
9354             then
9355                Error_Pragma_Arg
9356                  ("implementation kind By_Protected_Procedure cannot be " &
9357                   "applied to a task interface primitive", Arg2);
9358                return;
9359             end if;
9360
9361             Record_Rep_Item (Proc_Id, N);
9362          end Implemented;
9363
9364          ----------------------
9365          -- Implicit_Packing --
9366          ----------------------
9367
9368          --  pragma Implicit_Packing;
9369
9370          when Pragma_Implicit_Packing =>
9371             GNAT_Pragma;
9372             Check_Arg_Count (0);
9373             Implicit_Packing := True;
9374
9375          ------------
9376          -- Import --
9377          ------------
9378
9379          --  pragma Import (
9380          --       [Convention    =>] convention_IDENTIFIER,
9381          --       [Entity        =>] local_NAME
9382          --    [, [External_Name =>] static_string_EXPRESSION ]
9383          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
9384
9385          when Pragma_Import =>
9386             Check_Ada_83_Warning;
9387             Check_Arg_Order
9388               ((Name_Convention,
9389                 Name_Entity,
9390                 Name_External_Name,
9391                 Name_Link_Name));
9392             Check_At_Least_N_Arguments (2);
9393             Check_At_Most_N_Arguments  (4);
9394             Process_Import_Or_Interface;
9395
9396          ----------------------
9397          -- Import_Exception --
9398          ----------------------
9399
9400          --  pragma Import_Exception (
9401          --        [Internal         =>] LOCAL_NAME
9402          --     [, [External         =>] EXTERNAL_SYMBOL]
9403          --     [, [Form     =>] Ada | VMS]
9404          --     [, [Code     =>] static_integer_EXPRESSION]);
9405
9406          when Pragma_Import_Exception => Import_Exception : declare
9407             Args  : Args_List (1 .. 4);
9408             Names : constant Name_List (1 .. 4) := (
9409                       Name_Internal,
9410                       Name_External,
9411                       Name_Form,
9412                       Name_Code);
9413
9414             Internal : Node_Id renames Args (1);
9415             External : Node_Id renames Args (2);
9416             Form     : Node_Id renames Args (3);
9417             Code     : Node_Id renames Args (4);
9418
9419          begin
9420             GNAT_Pragma;
9421             Gather_Associations (Names, Args);
9422
9423             if Present (External) and then Present (Code) then
9424                Error_Pragma
9425                  ("cannot give both External and Code options for pragma%");
9426             end if;
9427
9428             Process_Extended_Import_Export_Exception_Pragma (
9429               Arg_Internal => Internal,
9430               Arg_External => External,
9431               Arg_Form     => Form,
9432               Arg_Code     => Code);
9433
9434             if not Is_VMS_Exception (Entity (Internal)) then
9435                Set_Imported (Entity (Internal));
9436             end if;
9437          end Import_Exception;
9438
9439          ---------------------
9440          -- Import_Function --
9441          ---------------------
9442
9443          --  pragma Import_Function (
9444          --        [Internal                 =>] LOCAL_NAME,
9445          --     [, [External                 =>] EXTERNAL_SYMBOL]
9446          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9447          --     [, [Result_Type              =>] SUBTYPE_MARK]
9448          --     [, [Mechanism                =>] MECHANISM]
9449          --     [, [Result_Mechanism         =>] MECHANISM_NAME]
9450          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9451
9452          --  EXTERNAL_SYMBOL ::=
9453          --    IDENTIFIER
9454          --  | static_string_EXPRESSION
9455
9456          --  PARAMETER_TYPES ::=
9457          --    null
9458          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9459
9460          --  TYPE_DESIGNATOR ::=
9461          --    subtype_NAME
9462          --  | subtype_Name ' Access
9463
9464          --  MECHANISM ::=
9465          --    MECHANISM_NAME
9466          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9467
9468          --  MECHANISM_ASSOCIATION ::=
9469          --    [formal_parameter_NAME =>] MECHANISM_NAME
9470
9471          --  MECHANISM_NAME ::=
9472          --    Value
9473          --  | Reference
9474          --  | Descriptor [([Class =>] CLASS_NAME)]
9475
9476          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9477
9478          when Pragma_Import_Function => Import_Function : declare
9479             Args  : Args_List (1 .. 7);
9480             Names : constant Name_List (1 .. 7) := (
9481                       Name_Internal,
9482                       Name_External,
9483                       Name_Parameter_Types,
9484                       Name_Result_Type,
9485                       Name_Mechanism,
9486                       Name_Result_Mechanism,
9487                       Name_First_Optional_Parameter);
9488
9489             Internal                 : Node_Id renames Args (1);
9490             External                 : Node_Id renames Args (2);
9491             Parameter_Types          : Node_Id renames Args (3);
9492             Result_Type              : Node_Id renames Args (4);
9493             Mechanism                : Node_Id renames Args (5);
9494             Result_Mechanism         : Node_Id renames Args (6);
9495             First_Optional_Parameter : Node_Id renames Args (7);
9496
9497          begin
9498             GNAT_Pragma;
9499             Gather_Associations (Names, Args);
9500             Process_Extended_Import_Export_Subprogram_Pragma (
9501               Arg_Internal                 => Internal,
9502               Arg_External                 => External,
9503               Arg_Parameter_Types          => Parameter_Types,
9504               Arg_Result_Type              => Result_Type,
9505               Arg_Mechanism                => Mechanism,
9506               Arg_Result_Mechanism         => Result_Mechanism,
9507               Arg_First_Optional_Parameter => First_Optional_Parameter);
9508          end Import_Function;
9509
9510          -------------------
9511          -- Import_Object --
9512          -------------------
9513
9514          --  pragma Import_Object (
9515          --        [Internal =>] LOCAL_NAME
9516          --     [, [External =>] EXTERNAL_SYMBOL]
9517          --     [, [Size     =>] EXTERNAL_SYMBOL]);
9518
9519          --  EXTERNAL_SYMBOL ::=
9520          --    IDENTIFIER
9521          --  | static_string_EXPRESSION
9522
9523          when Pragma_Import_Object => Import_Object : declare
9524             Args  : Args_List (1 .. 3);
9525             Names : constant Name_List (1 .. 3) := (
9526                       Name_Internal,
9527                       Name_External,
9528                       Name_Size);
9529
9530             Internal : Node_Id renames Args (1);
9531             External : Node_Id renames Args (2);
9532             Size     : Node_Id renames Args (3);
9533
9534          begin
9535             GNAT_Pragma;
9536             Gather_Associations (Names, Args);
9537             Process_Extended_Import_Export_Object_Pragma (
9538               Arg_Internal => Internal,
9539               Arg_External => External,
9540               Arg_Size     => Size);
9541          end Import_Object;
9542
9543          ----------------------
9544          -- Import_Procedure --
9545          ----------------------
9546
9547          --  pragma Import_Procedure (
9548          --        [Internal                 =>] LOCAL_NAME
9549          --     [, [External                 =>] EXTERNAL_SYMBOL]
9550          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9551          --     [, [Mechanism                =>] MECHANISM]
9552          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9553
9554          --  EXTERNAL_SYMBOL ::=
9555          --    IDENTIFIER
9556          --  | static_string_EXPRESSION
9557
9558          --  PARAMETER_TYPES ::=
9559          --    null
9560          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9561
9562          --  TYPE_DESIGNATOR ::=
9563          --    subtype_NAME
9564          --  | subtype_Name ' Access
9565
9566          --  MECHANISM ::=
9567          --    MECHANISM_NAME
9568          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9569
9570          --  MECHANISM_ASSOCIATION ::=
9571          --    [formal_parameter_NAME =>] MECHANISM_NAME
9572
9573          --  MECHANISM_NAME ::=
9574          --    Value
9575          --  | Reference
9576          --  | Descriptor [([Class =>] CLASS_NAME)]
9577
9578          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9579
9580          when Pragma_Import_Procedure => Import_Procedure : declare
9581             Args  : Args_List (1 .. 5);
9582             Names : constant Name_List (1 .. 5) := (
9583                       Name_Internal,
9584                       Name_External,
9585                       Name_Parameter_Types,
9586                       Name_Mechanism,
9587                       Name_First_Optional_Parameter);
9588
9589             Internal                 : Node_Id renames Args (1);
9590             External                 : Node_Id renames Args (2);
9591             Parameter_Types          : Node_Id renames Args (3);
9592             Mechanism                : Node_Id renames Args (4);
9593             First_Optional_Parameter : Node_Id renames Args (5);
9594
9595          begin
9596             GNAT_Pragma;
9597             Gather_Associations (Names, Args);
9598             Process_Extended_Import_Export_Subprogram_Pragma (
9599               Arg_Internal                 => Internal,
9600               Arg_External                 => External,
9601               Arg_Parameter_Types          => Parameter_Types,
9602               Arg_Mechanism                => Mechanism,
9603               Arg_First_Optional_Parameter => First_Optional_Parameter);
9604          end Import_Procedure;
9605
9606          -----------------------------
9607          -- Import_Valued_Procedure --
9608          -----------------------------
9609
9610          --  pragma Import_Valued_Procedure (
9611          --        [Internal                 =>] LOCAL_NAME
9612          --     [, [External                 =>] EXTERNAL_SYMBOL]
9613          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9614          --     [, [Mechanism                =>] MECHANISM]
9615          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9616
9617          --  EXTERNAL_SYMBOL ::=
9618          --    IDENTIFIER
9619          --  | static_string_EXPRESSION
9620
9621          --  PARAMETER_TYPES ::=
9622          --    null
9623          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9624
9625          --  TYPE_DESIGNATOR ::=
9626          --    subtype_NAME
9627          --  | subtype_Name ' Access
9628
9629          --  MECHANISM ::=
9630          --    MECHANISM_NAME
9631          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9632
9633          --  MECHANISM_ASSOCIATION ::=
9634          --    [formal_parameter_NAME =>] MECHANISM_NAME
9635
9636          --  MECHANISM_NAME ::=
9637          --    Value
9638          --  | Reference
9639          --  | Descriptor [([Class =>] CLASS_NAME)]
9640
9641          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9642
9643          when Pragma_Import_Valued_Procedure =>
9644          Import_Valued_Procedure : declare
9645             Args  : Args_List (1 .. 5);
9646             Names : constant Name_List (1 .. 5) := (
9647                       Name_Internal,
9648                       Name_External,
9649                       Name_Parameter_Types,
9650                       Name_Mechanism,
9651                       Name_First_Optional_Parameter);
9652
9653             Internal                 : Node_Id renames Args (1);
9654             External                 : Node_Id renames Args (2);
9655             Parameter_Types          : Node_Id renames Args (3);
9656             Mechanism                : Node_Id renames Args (4);
9657             First_Optional_Parameter : Node_Id renames Args (5);
9658
9659          begin
9660             GNAT_Pragma;
9661             Gather_Associations (Names, Args);
9662             Process_Extended_Import_Export_Subprogram_Pragma (
9663               Arg_Internal                 => Internal,
9664               Arg_External                 => External,
9665               Arg_Parameter_Types          => Parameter_Types,
9666               Arg_Mechanism                => Mechanism,
9667               Arg_First_Optional_Parameter => First_Optional_Parameter);
9668          end Import_Valued_Procedure;
9669
9670          -----------------
9671          -- Independent --
9672          -----------------
9673
9674          --  pragma Independent (LOCAL_NAME);
9675
9676          when Pragma_Independent => Independent : declare
9677             E_Id : Node_Id;
9678             E    : Entity_Id;
9679             D    : Node_Id;
9680             K    : Node_Kind;
9681
9682          begin
9683             Check_Ada_83_Warning;
9684             Ada_2012_Pragma;
9685             Check_No_Identifiers;
9686             Check_Arg_Count (1);
9687             Check_Arg_Is_Local_Name (Arg1);
9688             E_Id := Get_Pragma_Arg (Arg1);
9689
9690             if Etype (E_Id) = Any_Type then
9691                return;
9692             end if;
9693
9694             E := Entity (E_Id);
9695             D := Declaration_Node (E);
9696             K := Nkind (D);
9697
9698             --  Check duplicate before we chain ourselves!
9699
9700             Check_Duplicate_Pragma (E);
9701
9702             --  Check appropriate entity
9703
9704             if Is_Type (E) then
9705                if Rep_Item_Too_Early (E, N)
9706                     or else
9707                   Rep_Item_Too_Late (E, N)
9708                then
9709                   return;
9710                else
9711                   Check_First_Subtype (Arg1);
9712                end if;
9713
9714             elsif K = N_Object_Declaration
9715               or else (K = N_Component_Declaration
9716                        and then Original_Record_Component (E) = E)
9717             then
9718                if Rep_Item_Too_Late (E, N) then
9719                   return;
9720                end if;
9721
9722             else
9723                Error_Pragma_Arg
9724                  ("inappropriate entity for pragma%", Arg1);
9725             end if;
9726
9727             Independence_Checks.Append ((N, E));
9728          end Independent;
9729
9730          ----------------------------
9731          -- Independent_Components --
9732          ----------------------------
9733
9734          --  pragma Atomic_Components (array_LOCAL_NAME);
9735
9736          --  This processing is shared by Volatile_Components
9737
9738          when Pragma_Independent_Components => Independent_Components : declare
9739             E_Id : Node_Id;
9740             E    : Entity_Id;
9741             D    : Node_Id;
9742             K    : Node_Kind;
9743
9744          begin
9745             Check_Ada_83_Warning;
9746             Ada_2012_Pragma;
9747             Check_No_Identifiers;
9748             Check_Arg_Count (1);
9749             Check_Arg_Is_Local_Name (Arg1);
9750             E_Id := Get_Pragma_Arg (Arg1);
9751
9752             if Etype (E_Id) = Any_Type then
9753                return;
9754             end if;
9755
9756             E := Entity (E_Id);
9757
9758             --  Check duplicate before we chain ourselves!
9759
9760             Check_Duplicate_Pragma (E);
9761
9762             --  Check appropriate entity
9763
9764             if Rep_Item_Too_Early (E, N)
9765                  or else
9766                Rep_Item_Too_Late (E, N)
9767             then
9768                return;
9769             end if;
9770
9771             D := Declaration_Node (E);
9772             K := Nkind (D);
9773
9774             if (K = N_Full_Type_Declaration
9775                  and then (Is_Array_Type (E) or else Is_Record_Type (E)))
9776               or else
9777                 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
9778                    and then Nkind (D) = N_Object_Declaration
9779                    and then Nkind (Object_Definition (D)) =
9780                                        N_Constrained_Array_Definition)
9781             then
9782                Independence_Checks.Append ((N, E));
9783
9784             else
9785                Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
9786             end if;
9787          end Independent_Components;
9788
9789          ------------------------
9790          -- Initialize_Scalars --
9791          ------------------------
9792
9793          --  pragma Initialize_Scalars;
9794
9795          when Pragma_Initialize_Scalars =>
9796             GNAT_Pragma;
9797             Check_Arg_Count (0);
9798             Check_Valid_Configuration_Pragma;
9799             Check_Restriction (No_Initialize_Scalars, N);
9800
9801             --  Initialize_Scalars creates false positives in CodePeer, and
9802             --  incorrect negative results in Alfa mode, so ignore this pragma
9803             --  in these modes.
9804
9805             if not Restriction_Active (No_Initialize_Scalars)
9806               and then not (CodePeer_Mode or Alfa_Mode)
9807             then
9808                Init_Or_Norm_Scalars := True;
9809                Initialize_Scalars := True;
9810             end if;
9811
9812          ------------
9813          -- Inline --
9814          ------------
9815
9816          --  pragma Inline ( NAME {, NAME} );
9817
9818          when Pragma_Inline =>
9819
9820             --  Pragma is active if inlining option is active
9821
9822             Process_Inline (Inline_Active);
9823
9824          -------------------
9825          -- Inline_Always --
9826          -------------------
9827
9828          --  pragma Inline_Always ( NAME {, NAME} );
9829
9830          when Pragma_Inline_Always =>
9831             GNAT_Pragma;
9832
9833             --  Pragma always active unless in CodePeer or Alfa mode, since
9834             --  this causes walk order issues.
9835
9836             if not (CodePeer_Mode or Alfa_Mode) then
9837                Process_Inline (True);
9838             end if;
9839
9840          --------------------
9841          -- Inline_Generic --
9842          --------------------
9843
9844          --  pragma Inline_Generic (NAME {, NAME});
9845
9846          when Pragma_Inline_Generic =>
9847             GNAT_Pragma;
9848             Process_Generic_List;
9849
9850          ----------------------
9851          -- Inspection_Point --
9852          ----------------------
9853
9854          --  pragma Inspection_Point [(object_NAME {, object_NAME})];
9855
9856          when Pragma_Inspection_Point => Inspection_Point : declare
9857             Arg : Node_Id;
9858             Exp : Node_Id;
9859
9860          begin
9861             if Arg_Count > 0 then
9862                Arg := Arg1;
9863                loop
9864                   Exp := Get_Pragma_Arg (Arg);
9865                   Analyze (Exp);
9866
9867                   if not Is_Entity_Name (Exp)
9868                     or else not Is_Object (Entity (Exp))
9869                   then
9870                      Error_Pragma_Arg ("object name required", Arg);
9871                   end if;
9872
9873                   Next (Arg);
9874                   exit when No (Arg);
9875                end loop;
9876             end if;
9877          end Inspection_Point;
9878
9879          ---------------
9880          -- Interface --
9881          ---------------
9882
9883          --  pragma Interface (
9884          --    [   Convention    =>] convention_IDENTIFIER,
9885          --    [   Entity        =>] local_NAME
9886          --    [, [External_Name =>] static_string_EXPRESSION ]
9887          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
9888
9889          when Pragma_Interface =>
9890             GNAT_Pragma;
9891             Check_Arg_Order
9892               ((Name_Convention,
9893                 Name_Entity,
9894                 Name_External_Name,
9895                 Name_Link_Name));
9896             Check_At_Least_N_Arguments (2);
9897             Check_At_Most_N_Arguments  (4);
9898             Process_Import_Or_Interface;
9899
9900             --  In Ada 2005, the permission to use Interface (a reserved word)
9901             --  as a pragma name is considered an obsolescent feature.
9902
9903             if Ada_Version >= Ada_2005 then
9904                Check_Restriction
9905                  (No_Obsolescent_Features, Pragma_Identifier (N));
9906             end if;
9907
9908          --------------------
9909          -- Interface_Name --
9910          --------------------
9911
9912          --  pragma Interface_Name (
9913          --    [  Entity        =>] local_NAME
9914          --    [,[External_Name =>] static_string_EXPRESSION ]
9915          --    [,[Link_Name     =>] static_string_EXPRESSION ]);
9916
9917          when Pragma_Interface_Name => Interface_Name : declare
9918             Id     : Node_Id;
9919             Def_Id : Entity_Id;
9920             Hom_Id : Entity_Id;
9921             Found  : Boolean;
9922
9923          begin
9924             GNAT_Pragma;
9925             Check_Arg_Order
9926               ((Name_Entity, Name_External_Name, Name_Link_Name));
9927             Check_At_Least_N_Arguments (2);
9928             Check_At_Most_N_Arguments  (3);
9929             Id := Get_Pragma_Arg (Arg1);
9930             Analyze (Id);
9931
9932             if not Is_Entity_Name (Id) then
9933                Error_Pragma_Arg
9934                  ("first argument for pragma% must be entity name", Arg1);
9935             elsif Etype (Id) = Any_Type then
9936                return;
9937             else
9938                Def_Id := Entity (Id);
9939             end if;
9940
9941             --  Special DEC-compatible processing for the object case, forces
9942             --  object to be imported.
9943
9944             if Ekind (Def_Id) = E_Variable then
9945                Kill_Size_Check_Code (Def_Id);
9946                Note_Possible_Modification (Id, Sure => False);
9947
9948                --  Initialization is not allowed for imported variable
9949
9950                if Present (Expression (Parent (Def_Id)))
9951                  and then Comes_From_Source (Expression (Parent (Def_Id)))
9952                then
9953                   Error_Msg_Sloc := Sloc (Def_Id);
9954                   Error_Pragma_Arg
9955                     ("no initialization allowed for declaration of& #",
9956                      Arg2);
9957
9958                else
9959                   --  For compatibility, support VADS usage of providing both
9960                   --  pragmas Interface and Interface_Name to obtain the effect
9961                   --  of a single Import pragma.
9962
9963                   if Is_Imported (Def_Id)
9964                     and then Present (First_Rep_Item (Def_Id))
9965                     and then Nkind (First_Rep_Item (Def_Id)) = N_Pragma
9966                     and then
9967                       Pragma_Name (First_Rep_Item (Def_Id)) = Name_Interface
9968                   then
9969                      null;
9970                   else
9971                      Set_Imported (Def_Id);
9972                   end if;
9973
9974                   Set_Is_Public (Def_Id);
9975                   Process_Interface_Name (Def_Id, Arg2, Arg3);
9976                end if;
9977
9978             --  Otherwise must be subprogram
9979
9980             elsif not Is_Subprogram (Def_Id) then
9981                Error_Pragma_Arg
9982                  ("argument of pragma% is not subprogram", Arg1);
9983
9984             else
9985                Check_At_Most_N_Arguments (3);
9986                Hom_Id := Def_Id;
9987                Found := False;
9988
9989                --  Loop through homonyms
9990
9991                loop
9992                   Def_Id := Get_Base_Subprogram (Hom_Id);
9993
9994                   if Is_Imported (Def_Id) then
9995                      Process_Interface_Name (Def_Id, Arg2, Arg3);
9996                      Found := True;
9997                   end if;
9998
9999                   exit when From_Aspect_Specification (N);
10000                   Hom_Id := Homonym (Hom_Id);
10001
10002                   exit when No (Hom_Id)
10003                     or else Scope (Hom_Id) /= Current_Scope;
10004                end loop;
10005
10006                if not Found then
10007                   Error_Pragma_Arg
10008                     ("argument of pragma% is not imported subprogram",
10009                      Arg1);
10010                end if;
10011             end if;
10012          end Interface_Name;
10013
10014          -----------------------
10015          -- Interrupt_Handler --
10016          -----------------------
10017
10018          --  pragma Interrupt_Handler (handler_NAME);
10019
10020          when Pragma_Interrupt_Handler =>
10021             Check_Ada_83_Warning;
10022             Check_Arg_Count (1);
10023             Check_No_Identifiers;
10024
10025             if No_Run_Time_Mode then
10026                Error_Msg_CRT ("Interrupt_Handler pragma", N);
10027             else
10028                Check_Interrupt_Or_Attach_Handler;
10029                Process_Interrupt_Or_Attach_Handler;
10030             end if;
10031
10032          ------------------------
10033          -- Interrupt_Priority --
10034          ------------------------
10035
10036          --  pragma Interrupt_Priority [(EXPRESSION)];
10037
10038          when Pragma_Interrupt_Priority => Interrupt_Priority : declare
10039             P   : constant Node_Id := Parent (N);
10040             Arg : Node_Id;
10041
10042          begin
10043             Check_Ada_83_Warning;
10044
10045             if Arg_Count /= 0 then
10046                Arg := Get_Pragma_Arg (Arg1);
10047                Check_Arg_Count (1);
10048                Check_No_Identifiers;
10049
10050                --  The expression must be analyzed in the special manner
10051                --  described in "Handling of Default and Per-Object
10052                --  Expressions" in sem.ads.
10053
10054                Preanalyze_Spec_Expression (Arg, RTE (RE_Interrupt_Priority));
10055             end if;
10056
10057             if not Nkind_In (P, N_Task_Definition, N_Protected_Definition) then
10058                Pragma_Misplaced;
10059                return;
10060
10061             elsif Has_Pragma_Priority (P) then
10062                Error_Pragma ("duplicate pragma% not allowed");
10063
10064             else
10065                Set_Has_Pragma_Priority (P, True);
10066                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
10067             end if;
10068          end Interrupt_Priority;
10069
10070          ---------------------
10071          -- Interrupt_State --
10072          ---------------------
10073
10074          --  pragma Interrupt_State (
10075          --    [Name  =>] INTERRUPT_ID,
10076          --    [State =>] INTERRUPT_STATE);
10077
10078          --  INTERRUPT_ID => IDENTIFIER | static_integer_EXPRESSION
10079          --  INTERRUPT_STATE => System | Runtime | User
10080
10081          --  Note: if the interrupt id is given as an identifier, then it must
10082          --  be one of the identifiers in Ada.Interrupts.Names. Otherwise it is
10083          --  given as a static integer expression which must be in the range of
10084          --  Ada.Interrupts.Interrupt_ID.
10085
10086          when Pragma_Interrupt_State => Interrupt_State : declare
10087
10088             Int_Id : constant Entity_Id := RTE (RE_Interrupt_ID);
10089             --  This is the entity Ada.Interrupts.Interrupt_ID;
10090
10091             State_Type : Character;
10092             --  Set to 's'/'r'/'u' for System/Runtime/User
10093
10094             IST_Num : Pos;
10095             --  Index to entry in Interrupt_States table
10096
10097             Int_Val : Uint;
10098             --  Value of interrupt
10099
10100             Arg1X : constant Node_Id := Get_Pragma_Arg (Arg1);
10101             --  The first argument to the pragma
10102
10103             Int_Ent : Entity_Id;
10104             --  Interrupt entity in Ada.Interrupts.Names
10105
10106          begin
10107             GNAT_Pragma;
10108             Check_Arg_Order ((Name_Name, Name_State));
10109             Check_Arg_Count (2);
10110
10111             Check_Optional_Identifier (Arg1, Name_Name);
10112             Check_Optional_Identifier (Arg2, Name_State);
10113             Check_Arg_Is_Identifier (Arg2);
10114
10115             --  First argument is identifier
10116
10117             if Nkind (Arg1X) = N_Identifier then
10118
10119                --  Search list of names in Ada.Interrupts.Names
10120
10121                Int_Ent := First_Entity (RTE (RE_Names));
10122                loop
10123                   if No (Int_Ent) then
10124                      Error_Pragma_Arg ("invalid interrupt name", Arg1);
10125
10126                   elsif Chars (Int_Ent) = Chars (Arg1X) then
10127                      Int_Val := Expr_Value (Constant_Value (Int_Ent));
10128                      exit;
10129                   end if;
10130
10131                   Next_Entity (Int_Ent);
10132                end loop;
10133
10134             --  First argument is not an identifier, so it must be a static
10135             --  expression of type Ada.Interrupts.Interrupt_ID.
10136
10137             else
10138                Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
10139                Int_Val := Expr_Value (Arg1X);
10140
10141                if Int_Val < Expr_Value (Type_Low_Bound (Int_Id))
10142                     or else
10143                   Int_Val > Expr_Value (Type_High_Bound (Int_Id))
10144                then
10145                   Error_Pragma_Arg
10146                     ("value not in range of type " &
10147                      """Ada.Interrupts.Interrupt_'I'D""", Arg1);
10148                end if;
10149             end if;
10150
10151             --  Check OK state
10152
10153             case Chars (Get_Pragma_Arg (Arg2)) is
10154                when Name_Runtime => State_Type := 'r';
10155                when Name_System  => State_Type := 's';
10156                when Name_User    => State_Type := 'u';
10157
10158                when others =>
10159                   Error_Pragma_Arg ("invalid interrupt state", Arg2);
10160             end case;
10161
10162             --  Check if entry is already stored
10163
10164             IST_Num := Interrupt_States.First;
10165             loop
10166                --  If entry not found, add it
10167
10168                if IST_Num > Interrupt_States.Last then
10169                   Interrupt_States.Append
10170                     ((Interrupt_Number => UI_To_Int (Int_Val),
10171                       Interrupt_State  => State_Type,
10172                       Pragma_Loc       => Loc));
10173                   exit;
10174
10175                --  Case of entry for the same entry
10176
10177                elsif Int_Val = Interrupt_States.Table (IST_Num).
10178                                                            Interrupt_Number
10179                then
10180                   --  If state matches, done, no need to make redundant entry
10181
10182                   exit when
10183                     State_Type = Interrupt_States.Table (IST_Num).
10184                                                            Interrupt_State;
10185
10186                   --  Otherwise if state does not match, error
10187
10188                   Error_Msg_Sloc :=
10189                     Interrupt_States.Table (IST_Num).Pragma_Loc;
10190                   Error_Pragma_Arg
10191                     ("state conflicts with that given #", Arg2);
10192                   exit;
10193                end if;
10194
10195                IST_Num := IST_Num + 1;
10196             end loop;
10197          end Interrupt_State;
10198
10199          ---------------
10200          -- Invariant --
10201          ---------------
10202
10203          --  pragma Invariant
10204          --    ([Entity =>]    type_LOCAL_NAME,
10205          --     [Check  =>]    EXPRESSION
10206          --     [,[Message =>] String_Expression]);
10207
10208          when Pragma_Invariant => Invariant : declare
10209             Type_Id : Node_Id;
10210             Typ     : Entity_Id;
10211
10212             Discard : Boolean;
10213             pragma Unreferenced (Discard);
10214
10215          begin
10216             GNAT_Pragma;
10217             Check_At_Least_N_Arguments (2);
10218             Check_At_Most_N_Arguments (3);
10219             Check_Optional_Identifier (Arg1, Name_Entity);
10220             Check_Optional_Identifier (Arg2, Name_Check);
10221
10222             if Arg_Count = 3 then
10223                Check_Optional_Identifier (Arg3, Name_Message);
10224                Check_Arg_Is_Static_Expression (Arg3, Standard_String);
10225             end if;
10226
10227             Check_Arg_Is_Local_Name (Arg1);
10228
10229             Type_Id := Get_Pragma_Arg (Arg1);
10230             Find_Type (Type_Id);
10231             Typ := Entity (Type_Id);
10232
10233             if Typ = Any_Type then
10234                return;
10235
10236             --  An invariant must apply to a private type, or appear in the
10237             --  private part of a package spec and apply to a completion.
10238
10239             elsif Ekind_In (Typ, E_Private_Type,
10240                                  E_Record_Type_With_Private,
10241                                  E_Limited_Private_Type)
10242             then
10243                null;
10244
10245             elsif In_Private_Part (Current_Scope)
10246               and then Has_Private_Declaration (Typ)
10247             then
10248                null;
10249
10250             elsif In_Private_Part (Current_Scope) then
10251                Error_Pragma_Arg
10252                  ("pragma% only allowed for private type " &
10253                   "declared in visible part", Arg1);
10254
10255             else
10256                Error_Pragma_Arg
10257                  ("pragma% only allowed for private type", Arg1);
10258             end if;
10259
10260             --  Note that the type has at least one invariant, and also that
10261             --  it has inheritable invariants if we have Invariant'Class.
10262
10263             Set_Has_Invariants (Typ);
10264
10265             if Class_Present (N) then
10266                Set_Has_Inheritable_Invariants (Typ);
10267             end if;
10268
10269             --  The remaining processing is simply to link the pragma on to
10270             --  the rep item chain, for processing when the type is frozen.
10271             --  This is accomplished by a call to Rep_Item_Too_Late.
10272
10273             Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
10274          end Invariant;
10275
10276          ----------------------
10277          -- Java_Constructor --
10278          ----------------------
10279
10280          --  pragma Java_Constructor ([Entity =>] LOCAL_NAME);
10281
10282          --  Also handles pragma CIL_Constructor
10283
10284          when Pragma_CIL_Constructor | Pragma_Java_Constructor =>
10285          Java_Constructor : declare
10286             Convention  : Convention_Id;
10287             Def_Id      : Entity_Id;
10288             Hom_Id      : Entity_Id;
10289             Id          : Entity_Id;
10290             This_Formal : Entity_Id;
10291
10292          begin
10293             GNAT_Pragma;
10294             Check_Arg_Count (1);
10295             Check_Optional_Identifier (Arg1, Name_Entity);
10296             Check_Arg_Is_Local_Name (Arg1);
10297
10298             Id := Get_Pragma_Arg (Arg1);
10299             Find_Program_Unit_Name (Id);
10300
10301             --  If we did not find the name, we are done
10302
10303             if Etype (Id) = Any_Type then
10304                return;
10305             end if;
10306
10307             --  Check wrong use of pragma in wrong VM target
10308
10309             if VM_Target = No_VM then
10310                return;
10311
10312             elsif VM_Target = CLI_Target
10313               and then Prag_Id = Pragma_Java_Constructor
10314             then
10315                Error_Pragma ("must use pragma 'C'I'L_'Constructor");
10316
10317             elsif VM_Target = JVM_Target
10318               and then Prag_Id = Pragma_CIL_Constructor
10319             then
10320                Error_Pragma ("must use pragma 'Java_'Constructor");
10321             end if;
10322
10323             case Prag_Id is
10324                when Pragma_CIL_Constructor  => Convention := Convention_CIL;
10325                when Pragma_Java_Constructor => Convention := Convention_Java;
10326                when others                  => null;
10327             end case;
10328
10329             Hom_Id := Entity (Id);
10330
10331             --  Loop through homonyms
10332
10333             loop
10334                Def_Id := Get_Base_Subprogram (Hom_Id);
10335
10336                --  The constructor is required to be a function
10337
10338                if Ekind (Def_Id) /= E_Function then
10339                   if VM_Target = JVM_Target then
10340                      Error_Pragma_Arg
10341                        ("pragma% requires function returning a " &
10342                         "'Java access type", Def_Id);
10343                   else
10344                      Error_Pragma_Arg
10345                        ("pragma% requires function returning a " &
10346                         "'C'I'L access type", Def_Id);
10347                   end if;
10348                end if;
10349
10350                --  Check arguments: For tagged type the first formal must be
10351                --  named "this" and its type must be a named access type
10352                --  designating a class-wide tagged type that has convention
10353                --  CIL/Java. The first formal must also have a null default
10354                --  value. For example:
10355
10356                --      type Typ is tagged ...
10357                --      type Ref is access all Typ;
10358                --      pragma Convention (CIL, Typ);
10359
10360                --      function New_Typ (This : Ref) return Ref;
10361                --      function New_Typ (This : Ref; I : Integer) return Ref;
10362                --      pragma Cil_Constructor (New_Typ);
10363
10364                --  Reason: The first formal must NOT be a primitive of the
10365                --  tagged type.
10366
10367                --  This rule also applies to constructors of delegates used
10368                --  to interface with standard target libraries. For example:
10369
10370                --      type Delegate is access procedure ...
10371                --      pragma Import (CIL, Delegate, ...);
10372
10373                --      function new_Delegate
10374                --        (This : Delegate := null; ... ) return Delegate;
10375
10376                --  For value-types this rule does not apply.
10377
10378                if not Is_Value_Type (Etype (Def_Id)) then
10379                   if No (First_Formal (Def_Id)) then
10380                      Error_Msg_Name_1 := Pname;
10381                      Error_Msg_N ("% function must have parameters", Def_Id);
10382                      return;
10383                   end if;
10384
10385                   --  In the JRE library we have several occurrences in which
10386                   --  the "this" parameter is not the first formal.
10387
10388                   This_Formal := First_Formal (Def_Id);
10389
10390                   --  In the JRE library we have several occurrences in which
10391                   --  the "this" parameter is not the first formal. Search for
10392                   --  it.
10393
10394                   if VM_Target = JVM_Target then
10395                      while Present (This_Formal)
10396                        and then Get_Name_String (Chars (This_Formal)) /= "this"
10397                      loop
10398                         Next_Formal (This_Formal);
10399                      end loop;
10400
10401                      if No (This_Formal) then
10402                         This_Formal := First_Formal (Def_Id);
10403                      end if;
10404                   end if;
10405
10406                   --  Warning: The first parameter should be named "this".
10407                   --  We temporarily allow it because we have the following
10408                   --  case in the Java runtime (file s-osinte.ads) ???
10409
10410                   --    function new_Thread
10411                   --      (Self_Id : System.Address) return Thread_Id;
10412                   --    pragma Java_Constructor (new_Thread);
10413
10414                   if VM_Target = JVM_Target
10415                     and then Get_Name_String (Chars (First_Formal (Def_Id)))
10416                                = "self_id"
10417                     and then Etype (First_Formal (Def_Id)) = RTE (RE_Address)
10418                   then
10419                      null;
10420
10421                   elsif Get_Name_String (Chars (This_Formal)) /= "this" then
10422                      Error_Msg_Name_1 := Pname;
10423                      Error_Msg_N
10424                        ("first formal of % function must be named `this`",
10425                         Parent (This_Formal));
10426
10427                   elsif not Is_Access_Type (Etype (This_Formal)) then
10428                      Error_Msg_Name_1 := Pname;
10429                      Error_Msg_N
10430                        ("first formal of % function must be an access type",
10431                         Parameter_Type (Parent (This_Formal)));
10432
10433                   --  For delegates the type of the first formal must be a
10434                   --  named access-to-subprogram type (see previous example)
10435
10436                   elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type
10437                     and then Ekind (Etype (This_Formal))
10438                                /= E_Access_Subprogram_Type
10439                   then
10440                      Error_Msg_Name_1 := Pname;
10441                      Error_Msg_N
10442                        ("first formal of % function must be a named access" &
10443                         " to subprogram type",
10444                         Parameter_Type (Parent (This_Formal)));
10445
10446                   --  Warning: We should reject anonymous access types because
10447                   --  the constructor must not be handled as a primitive of the
10448                   --  tagged type. We temporarily allow it because this profile
10449                   --  is currently generated by cil2ada???
10450
10451                   elsif Ekind (Etype (Def_Id)) /= E_Access_Subprogram_Type
10452                     and then not Ekind_In (Etype (This_Formal),
10453                                              E_Access_Type,
10454                                              E_General_Access_Type,
10455                                              E_Anonymous_Access_Type)
10456                   then
10457                      Error_Msg_Name_1 := Pname;
10458                      Error_Msg_N
10459                        ("first formal of % function must be a named access" &
10460                         " type",
10461                         Parameter_Type (Parent (This_Formal)));
10462
10463                   elsif Atree.Convention
10464                          (Designated_Type (Etype (This_Formal))) /= Convention
10465                   then
10466                      Error_Msg_Name_1 := Pname;
10467
10468                      if Convention = Convention_Java then
10469                         Error_Msg_N
10470                           ("pragma% requires convention 'Cil in designated" &
10471                            " type",
10472                            Parameter_Type (Parent (This_Formal)));
10473                      else
10474                         Error_Msg_N
10475                           ("pragma% requires convention 'Java in designated" &
10476                            " type",
10477                            Parameter_Type (Parent (This_Formal)));
10478                      end if;
10479
10480                   elsif No (Expression (Parent (This_Formal)))
10481                     or else Nkind (Expression (Parent (This_Formal))) /= N_Null
10482                   then
10483                      Error_Msg_Name_1 := Pname;
10484                      Error_Msg_N
10485                        ("pragma% requires first formal with default `null`",
10486                         Parameter_Type (Parent (This_Formal)));
10487                   end if;
10488                end if;
10489
10490                --  Check result type: the constructor must be a function
10491                --  returning:
10492                --   * a value type (only allowed in the CIL compiler)
10493                --   * an access-to-subprogram type with convention Java/CIL
10494                --   * an access-type designating a type that has convention
10495                --     Java/CIL.
10496
10497                if Is_Value_Type (Etype (Def_Id)) then
10498                   null;
10499
10500                --  Access-to-subprogram type with convention Java/CIL
10501
10502                elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type then
10503                   if Atree.Convention (Etype (Def_Id)) /= Convention then
10504                      if Convention = Convention_Java then
10505                         Error_Pragma_Arg
10506                           ("pragma% requires function returning a " &
10507                            "'Java access type", Arg1);
10508                      else
10509                         pragma Assert (Convention = Convention_CIL);
10510                         Error_Pragma_Arg
10511                           ("pragma% requires function returning a " &
10512                            "'C'I'L access type", Arg1);
10513                      end if;
10514                   end if;
10515
10516                elsif Ekind (Etype (Def_Id)) in Access_Kind then
10517                   if not Ekind_In (Etype (Def_Id), E_Access_Type,
10518                                                    E_General_Access_Type)
10519                     or else
10520                       Atree.Convention
10521                         (Designated_Type (Etype (Def_Id))) /= Convention
10522                   then
10523                      Error_Msg_Name_1 := Pname;
10524
10525                      if Convention = Convention_Java then
10526                         Error_Pragma_Arg
10527                           ("pragma% requires function returning a named" &
10528                            "'Java access type", Arg1);
10529                      else
10530                         Error_Pragma_Arg
10531                           ("pragma% requires function returning a named" &
10532                            "'C'I'L access type", Arg1);
10533                      end if;
10534                   end if;
10535                end if;
10536
10537                Set_Is_Constructor (Def_Id);
10538                Set_Convention     (Def_Id, Convention);
10539                Set_Is_Imported    (Def_Id);
10540
10541                exit when From_Aspect_Specification (N);
10542                Hom_Id := Homonym (Hom_Id);
10543
10544                exit when No (Hom_Id) or else Scope (Hom_Id) /= Current_Scope;
10545             end loop;
10546          end Java_Constructor;
10547
10548          ----------------------
10549          -- Java_Interface --
10550          ----------------------
10551
10552          --  pragma Java_Interface ([Entity =>] LOCAL_NAME);
10553
10554          when Pragma_Java_Interface => Java_Interface : declare
10555             Arg : Node_Id;
10556             Typ : Entity_Id;
10557
10558          begin
10559             GNAT_Pragma;
10560             Check_Arg_Count (1);
10561             Check_Optional_Identifier (Arg1, Name_Entity);
10562             Check_Arg_Is_Local_Name (Arg1);
10563
10564             Arg := Get_Pragma_Arg (Arg1);
10565             Analyze (Arg);
10566
10567             if Etype (Arg) = Any_Type then
10568                return;
10569             end if;
10570
10571             if not Is_Entity_Name (Arg)
10572               or else not Is_Type (Entity (Arg))
10573             then
10574                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
10575             end if;
10576
10577             Typ := Underlying_Type (Entity (Arg));
10578
10579             --  For now simply check some of the semantic constraints on the
10580             --  type. This currently leaves out some restrictions on interface
10581             --  types, namely that the parent type must be java.lang.Object.Typ
10582             --  and that all primitives of the type should be declared
10583             --  abstract. ???
10584
10585             if not Is_Tagged_Type (Typ) or else not Is_Abstract_Type (Typ) then
10586                Error_Pragma_Arg ("pragma% requires an abstract "
10587                  & "tagged type", Arg1);
10588
10589             elsif not Has_Discriminants (Typ)
10590               or else Ekind (Etype (First_Discriminant (Typ)))
10591                         /= E_Anonymous_Access_Type
10592               or else
10593                 not Is_Class_Wide_Type
10594                       (Designated_Type (Etype (First_Discriminant (Typ))))
10595             then
10596                Error_Pragma_Arg
10597                  ("type must have a class-wide access discriminant", Arg1);
10598             end if;
10599          end Java_Interface;
10600
10601          ----------------
10602          -- Keep_Names --
10603          ----------------
10604
10605          --  pragma Keep_Names ([On => ] local_NAME);
10606
10607          when Pragma_Keep_Names => Keep_Names : declare
10608             Arg : Node_Id;
10609
10610          begin
10611             GNAT_Pragma;
10612             Check_Arg_Count (1);
10613             Check_Optional_Identifier (Arg1, Name_On);
10614             Check_Arg_Is_Local_Name (Arg1);
10615
10616             Arg := Get_Pragma_Arg (Arg1);
10617             Analyze (Arg);
10618
10619             if Etype (Arg) = Any_Type then
10620                return;
10621             end if;
10622
10623             if not Is_Entity_Name (Arg)
10624               or else Ekind (Entity (Arg)) /= E_Enumeration_Type
10625             then
10626                Error_Pragma_Arg
10627                  ("pragma% requires a local enumeration type", Arg1);
10628             end if;
10629
10630             Set_Discard_Names (Entity (Arg), False);
10631          end Keep_Names;
10632
10633          -------------
10634          -- License --
10635          -------------
10636
10637          --  pragma License (RESTRICTED | UNRESTRICTED | GPL | MODIFIED_GPL);
10638
10639          when Pragma_License =>
10640             GNAT_Pragma;
10641             Check_Arg_Count (1);
10642             Check_No_Identifiers;
10643             Check_Valid_Configuration_Pragma;
10644             Check_Arg_Is_Identifier (Arg1);
10645
10646             declare
10647                Sind : constant Source_File_Index :=
10648                         Source_Index (Current_Sem_Unit);
10649
10650             begin
10651                case Chars (Get_Pragma_Arg (Arg1)) is
10652                   when Name_GPL =>
10653                      Set_License (Sind, GPL);
10654
10655                   when Name_Modified_GPL =>
10656                      Set_License (Sind, Modified_GPL);
10657
10658                   when Name_Restricted =>
10659                      Set_License (Sind, Restricted);
10660
10661                   when Name_Unrestricted =>
10662                      Set_License (Sind, Unrestricted);
10663
10664                   when others =>
10665                      Error_Pragma_Arg ("invalid license name", Arg1);
10666                end case;
10667             end;
10668
10669          ---------------
10670          -- Link_With --
10671          ---------------
10672
10673          --  pragma Link_With (string_EXPRESSION {, string_EXPRESSION});
10674
10675          when Pragma_Link_With => Link_With : declare
10676             Arg : Node_Id;
10677
10678          begin
10679             GNAT_Pragma;
10680
10681             if Operating_Mode = Generate_Code
10682               and then In_Extended_Main_Source_Unit (N)
10683             then
10684                Check_At_Least_N_Arguments (1);
10685                Check_No_Identifiers;
10686                Check_Is_In_Decl_Part_Or_Package_Spec;
10687                Check_Arg_Is_Static_Expression (Arg1, Standard_String);
10688                Start_String;
10689
10690                Arg := Arg1;
10691                while Present (Arg) loop
10692                   Check_Arg_Is_Static_Expression (Arg, Standard_String);
10693
10694                   --  Store argument, converting sequences of spaces to a
10695                   --  single null character (this is one of the differences
10696                   --  in processing between Link_With and Linker_Options).
10697
10698                   Arg_Store : declare
10699                      C : constant Char_Code := Get_Char_Code (' ');
10700                      S : constant String_Id :=
10701                            Strval (Expr_Value_S (Get_Pragma_Arg (Arg)));
10702                      L : constant Nat := String_Length (S);
10703                      F : Nat := 1;
10704
10705                      procedure Skip_Spaces;
10706                      --  Advance F past any spaces
10707
10708                      -----------------
10709                      -- Skip_Spaces --
10710                      -----------------
10711
10712                      procedure Skip_Spaces is
10713                      begin
10714                         while F <= L and then Get_String_Char (S, F) = C loop
10715                            F := F + 1;
10716                         end loop;
10717                      end Skip_Spaces;
10718
10719                   --  Start of processing for Arg_Store
10720
10721                   begin
10722                      Skip_Spaces; -- skip leading spaces
10723
10724                      --  Loop through characters, changing any embedded
10725                      --  sequence of spaces to a single null character (this
10726                      --  is how Link_With/Linker_Options differ)
10727
10728                      while F <= L loop
10729                         if Get_String_Char (S, F) = C then
10730                            Skip_Spaces;
10731                            exit when F > L;
10732                            Store_String_Char (ASCII.NUL);
10733
10734                         else
10735                            Store_String_Char (Get_String_Char (S, F));
10736                            F := F + 1;
10737                         end if;
10738                      end loop;
10739                   end Arg_Store;
10740
10741                   Arg := Next (Arg);
10742
10743                   if Present (Arg) then
10744                      Store_String_Char (ASCII.NUL);
10745                   end if;
10746                end loop;
10747
10748                Store_Linker_Option_String (End_String);
10749             end if;
10750          end Link_With;
10751
10752          ------------------
10753          -- Linker_Alias --
10754          ------------------
10755
10756          --  pragma Linker_Alias (
10757          --      [Entity =>]  LOCAL_NAME
10758          --      [Target =>]  static_string_EXPRESSION);
10759
10760          when Pragma_Linker_Alias =>
10761             GNAT_Pragma;
10762             Check_Arg_Order ((Name_Entity, Name_Target));
10763             Check_Arg_Count (2);
10764             Check_Optional_Identifier (Arg1, Name_Entity);
10765             Check_Optional_Identifier (Arg2, Name_Target);
10766             Check_Arg_Is_Library_Level_Local_Name (Arg1);
10767             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10768
10769             --  The only processing required is to link this item on to the
10770             --  list of rep items for the given entity. This is accomplished
10771             --  by the call to Rep_Item_Too_Late (when no error is detected
10772             --  and False is returned).
10773
10774             if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
10775                return;
10776             else
10777                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10778             end if;
10779
10780          ------------------------
10781          -- Linker_Constructor --
10782          ------------------------
10783
10784          --  pragma Linker_Constructor (procedure_LOCAL_NAME);
10785
10786          --  Code is shared with Linker_Destructor
10787
10788          -----------------------
10789          -- Linker_Destructor --
10790          -----------------------
10791
10792          --  pragma Linker_Destructor (procedure_LOCAL_NAME);
10793
10794          when Pragma_Linker_Constructor |
10795               Pragma_Linker_Destructor =>
10796          Linker_Constructor : declare
10797             Arg1_X : Node_Id;
10798             Proc   : Entity_Id;
10799
10800          begin
10801             GNAT_Pragma;
10802             Check_Arg_Count (1);
10803             Check_No_Identifiers;
10804             Check_Arg_Is_Local_Name (Arg1);
10805             Arg1_X := Get_Pragma_Arg (Arg1);
10806             Analyze (Arg1_X);
10807             Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
10808
10809             if not Is_Library_Level_Entity (Proc) then
10810                Error_Pragma_Arg
10811                 ("argument for pragma% must be library level entity", Arg1);
10812             end if;
10813
10814             --  The only processing required is to link this item on to the
10815             --  list of rep items for the given entity. This is accomplished
10816             --  by the call to Rep_Item_Too_Late (when no error is detected
10817             --  and False is returned).
10818
10819             if Rep_Item_Too_Late (Proc, N) then
10820                return;
10821             else
10822                Set_Has_Gigi_Rep_Item (Proc);
10823             end if;
10824          end Linker_Constructor;
10825
10826          --------------------
10827          -- Linker_Options --
10828          --------------------
10829
10830          --  pragma Linker_Options (string_EXPRESSION {, string_EXPRESSION});
10831
10832          when Pragma_Linker_Options => Linker_Options : declare
10833             Arg : Node_Id;
10834
10835          begin
10836             Check_Ada_83_Warning;
10837             Check_No_Identifiers;
10838             Check_Arg_Count (1);
10839             Check_Is_In_Decl_Part_Or_Package_Spec;
10840             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
10841             Start_String (Strval (Expr_Value_S (Get_Pragma_Arg (Arg1))));
10842
10843             Arg := Arg2;
10844             while Present (Arg) loop
10845                Check_Arg_Is_Static_Expression (Arg, Standard_String);
10846                Store_String_Char (ASCII.NUL);
10847                Store_String_Chars
10848                  (Strval (Expr_Value_S (Get_Pragma_Arg (Arg))));
10849                Arg := Next (Arg);
10850             end loop;
10851
10852             if Operating_Mode = Generate_Code
10853               and then In_Extended_Main_Source_Unit (N)
10854             then
10855                Store_Linker_Option_String (End_String);
10856             end if;
10857          end Linker_Options;
10858
10859          --------------------
10860          -- Linker_Section --
10861          --------------------
10862
10863          --  pragma Linker_Section (
10864          --      [Entity  =>]  LOCAL_NAME
10865          --      [Section =>]  static_string_EXPRESSION);
10866
10867          when Pragma_Linker_Section =>
10868             GNAT_Pragma;
10869             Check_Arg_Order ((Name_Entity, Name_Section));
10870             Check_Arg_Count (2);
10871             Check_Optional_Identifier (Arg1, Name_Entity);
10872             Check_Optional_Identifier (Arg2, Name_Section);
10873             Check_Arg_Is_Library_Level_Local_Name (Arg1);
10874             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10875
10876             --  This pragma applies only to objects
10877
10878             if not Is_Object (Entity (Get_Pragma_Arg (Arg1))) then
10879                Error_Pragma_Arg ("pragma% applies only to objects", Arg1);
10880             end if;
10881
10882             --  The only processing required is to link this item on to the
10883             --  list of rep items for the given entity. This is accomplished
10884             --  by the call to Rep_Item_Too_Late (when no error is detected
10885             --  and False is returned).
10886
10887             if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
10888                return;
10889             else
10890                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10891             end if;
10892
10893          ----------
10894          -- List --
10895          ----------
10896
10897          --  pragma List (On | Off)
10898
10899          --  There is nothing to do here, since we did all the processing for
10900          --  this pragma in Par.Prag (so that it works properly even in syntax
10901          --  only mode).
10902
10903          when Pragma_List =>
10904             null;
10905
10906          --------------------
10907          -- Locking_Policy --
10908          --------------------
10909
10910          --  pragma Locking_Policy (policy_IDENTIFIER);
10911
10912          when Pragma_Locking_Policy => declare
10913             subtype LP_Range is Name_Id
10914               range First_Locking_Policy_Name .. Last_Locking_Policy_Name;
10915             LP_Val : LP_Range;
10916             LP     : Character;
10917          begin
10918             Check_Ada_83_Warning;
10919             Check_Arg_Count (1);
10920             Check_No_Identifiers;
10921             Check_Arg_Is_Locking_Policy (Arg1);
10922             Check_Valid_Configuration_Pragma;
10923             LP_Val := Chars (Get_Pragma_Arg (Arg1));
10924
10925             case LP_Val is
10926                when Name_Ceiling_Locking            => LP := 'C';
10927                when Name_Inheritance_Locking        => LP := 'I';
10928                when Name_Concurrent_Readers_Locking => LP := 'R';
10929             end case;
10930
10931             if Locking_Policy /= ' '
10932               and then Locking_Policy /= LP
10933             then
10934                Error_Msg_Sloc := Locking_Policy_Sloc;
10935                Error_Pragma ("locking policy incompatible with policy#");
10936
10937             --  Set new policy, but always preserve System_Location since we
10938             --  like the error message with the run time name.
10939
10940             else
10941                Locking_Policy := LP;
10942
10943                if Locking_Policy_Sloc /= System_Location then
10944                   Locking_Policy_Sloc := Loc;
10945                end if;
10946             end if;
10947          end;
10948
10949          ----------------
10950          -- Long_Float --
10951          ----------------
10952
10953          --  pragma Long_Float (D_Float | G_Float);
10954
10955          when Pragma_Long_Float =>
10956             GNAT_Pragma;
10957             Check_Valid_Configuration_Pragma;
10958             Check_Arg_Count (1);
10959             Check_No_Identifier (Arg1);
10960             Check_Arg_Is_One_Of (Arg1, Name_D_Float, Name_G_Float);
10961
10962             if not OpenVMS_On_Target then
10963                Error_Pragma ("?pragma% ignored (applies only to Open'V'M'S)");
10964             end if;
10965
10966             --  D_Float case
10967
10968             if Chars (Get_Pragma_Arg (Arg1)) = Name_D_Float then
10969                if Opt.Float_Format_Long = 'G' then
10970                   Error_Pragma ("G_Float previously specified");
10971                end if;
10972
10973                Opt.Float_Format_Long := 'D';
10974
10975             --  G_Float case (this is the default, does not need overriding)
10976
10977             else
10978                if Opt.Float_Format_Long = 'D' then
10979                   Error_Pragma ("D_Float previously specified");
10980                end if;
10981
10982                Opt.Float_Format_Long := 'G';
10983             end if;
10984
10985             Set_Standard_Fpt_Formats;
10986
10987          -----------------------
10988          -- Machine_Attribute --
10989          -----------------------
10990
10991          --  pragma Machine_Attribute (
10992          --       [Entity         =>] LOCAL_NAME,
10993          --       [Attribute_Name =>] static_string_EXPRESSION
10994          --    [, [Info           =>] static_EXPRESSION] );
10995
10996          when Pragma_Machine_Attribute => Machine_Attribute : declare
10997             Def_Id : Entity_Id;
10998
10999          begin
11000             GNAT_Pragma;
11001             Check_Arg_Order ((Name_Entity, Name_Attribute_Name, Name_Info));
11002
11003             if Arg_Count = 3 then
11004                Check_Optional_Identifier (Arg3, Name_Info);
11005                Check_Arg_Is_Static_Expression (Arg3);
11006             else
11007                Check_Arg_Count (2);
11008             end if;
11009
11010             Check_Optional_Identifier (Arg1, Name_Entity);
11011             Check_Optional_Identifier (Arg2, Name_Attribute_Name);
11012             Check_Arg_Is_Local_Name (Arg1);
11013             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
11014             Def_Id := Entity (Get_Pragma_Arg (Arg1));
11015
11016             if Is_Access_Type (Def_Id) then
11017                Def_Id := Designated_Type (Def_Id);
11018             end if;
11019
11020             if Rep_Item_Too_Early (Def_Id, N) then
11021                return;
11022             end if;
11023
11024             Def_Id := Underlying_Type (Def_Id);
11025
11026             --  The only processing required is to link this item on to the
11027             --  list of rep items for the given entity. This is accomplished
11028             --  by the call to Rep_Item_Too_Late (when no error is detected
11029             --  and False is returned).
11030
11031             if Rep_Item_Too_Late (Def_Id, N) then
11032                return;
11033             else
11034                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
11035             end if;
11036          end Machine_Attribute;
11037
11038          ----------
11039          -- Main --
11040          ----------
11041
11042          --  pragma Main
11043          --   (MAIN_OPTION [, MAIN_OPTION]);
11044
11045          --  MAIN_OPTION ::=
11046          --    [STACK_SIZE              =>] static_integer_EXPRESSION
11047          --  | [TASK_STACK_SIZE_DEFAULT =>] static_integer_EXPRESSION
11048          --  | [TIME_SLICING_ENABLED    =>] static_boolean_EXPRESSION
11049
11050          when Pragma_Main => Main : declare
11051             Args  : Args_List (1 .. 3);
11052             Names : constant Name_List (1 .. 3) := (
11053                       Name_Stack_Size,
11054                       Name_Task_Stack_Size_Default,
11055                       Name_Time_Slicing_Enabled);
11056
11057             Nod : Node_Id;
11058
11059          begin
11060             GNAT_Pragma;
11061             Gather_Associations (Names, Args);
11062
11063             for J in 1 .. 2 loop
11064                if Present (Args (J)) then
11065                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
11066                end if;
11067             end loop;
11068
11069             if Present (Args (3)) then
11070                Check_Arg_Is_Static_Expression (Args (3), Standard_Boolean);
11071             end if;
11072
11073             Nod := Next (N);
11074             while Present (Nod) loop
11075                if Nkind (Nod) = N_Pragma
11076                  and then Pragma_Name (Nod) = Name_Main
11077                then
11078                   Error_Msg_Name_1 := Pname;
11079                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
11080                end if;
11081
11082                Next (Nod);
11083             end loop;
11084          end Main;
11085
11086          ------------------
11087          -- Main_Storage --
11088          ------------------
11089
11090          --  pragma Main_Storage
11091          --   (MAIN_STORAGE_OPTION [, MAIN_STORAGE_OPTION]);
11092
11093          --  MAIN_STORAGE_OPTION ::=
11094          --    [WORKING_STORAGE =>] static_SIMPLE_EXPRESSION
11095          --  | [TOP_GUARD =>] static_SIMPLE_EXPRESSION
11096
11097          when Pragma_Main_Storage => Main_Storage : declare
11098             Args  : Args_List (1 .. 2);
11099             Names : constant Name_List (1 .. 2) := (
11100                       Name_Working_Storage,
11101                       Name_Top_Guard);
11102
11103             Nod : Node_Id;
11104
11105          begin
11106             GNAT_Pragma;
11107             Gather_Associations (Names, Args);
11108
11109             for J in 1 .. 2 loop
11110                if Present (Args (J)) then
11111                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
11112                end if;
11113             end loop;
11114
11115             Check_In_Main_Program;
11116
11117             Nod := Next (N);
11118             while Present (Nod) loop
11119                if Nkind (Nod) = N_Pragma
11120                  and then Pragma_Name (Nod) = Name_Main_Storage
11121                then
11122                   Error_Msg_Name_1 := Pname;
11123                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
11124                end if;
11125
11126                Next (Nod);
11127             end loop;
11128          end Main_Storage;
11129
11130          -----------------
11131          -- Memory_Size --
11132          -----------------
11133
11134          --  pragma Memory_Size (NUMERIC_LITERAL)
11135
11136          when Pragma_Memory_Size =>
11137             GNAT_Pragma;
11138
11139             --  Memory size is simply ignored
11140
11141             Check_No_Identifiers;
11142             Check_Arg_Count (1);
11143             Check_Arg_Is_Integer_Literal (Arg1);
11144
11145          -------------
11146          -- No_Body --
11147          -------------
11148
11149          --  pragma No_Body;
11150
11151          --  The only correct use of this pragma is on its own in a file, in
11152          --  which case it is specially processed (see Gnat1drv.Check_Bad_Body
11153          --  and Frontend, which use Sinput.L.Source_File_Is_Pragma_No_Body to
11154          --  check for a file containing nothing but a No_Body pragma). If we
11155          --  attempt to process it during normal semantics processing, it means
11156          --  it was misplaced.
11157
11158          when Pragma_No_Body =>
11159             GNAT_Pragma;
11160             Pragma_Misplaced;
11161
11162          ---------------
11163          -- No_Return --
11164          ---------------
11165
11166          --  pragma No_Return (procedure_LOCAL_NAME {, procedure_Local_Name});
11167
11168          when Pragma_No_Return => No_Return : declare
11169             Id    : Node_Id;
11170             E     : Entity_Id;
11171             Found : Boolean;
11172             Arg   : Node_Id;
11173
11174          begin
11175             Ada_2005_Pragma;
11176             Check_At_Least_N_Arguments (1);
11177
11178             --  Loop through arguments of pragma
11179
11180             Arg := Arg1;
11181             while Present (Arg) loop
11182                Check_Arg_Is_Local_Name (Arg);
11183                Id := Get_Pragma_Arg (Arg);
11184                Analyze (Id);
11185
11186                if not Is_Entity_Name (Id) then
11187                   Error_Pragma_Arg ("entity name required", Arg);
11188                end if;
11189
11190                if Etype (Id) = Any_Type then
11191                   raise Pragma_Exit;
11192                end if;
11193
11194                --  Loop to find matching procedures
11195
11196                E := Entity (Id);
11197                Found := False;
11198                while Present (E)
11199                  and then Scope (E) = Current_Scope
11200                loop
11201                   if Ekind_In (E, E_Procedure, E_Generic_Procedure) then
11202                      Set_No_Return (E);
11203
11204                      --  Set flag on any alias as well
11205
11206                      if Is_Overloadable (E) and then Present (Alias (E)) then
11207                         Set_No_Return (Alias (E));
11208                      end if;
11209
11210                      Found := True;
11211                   end if;
11212
11213                   exit when From_Aspect_Specification (N);
11214                   E := Homonym (E);
11215                end loop;
11216
11217                if not Found then
11218                   Error_Pragma_Arg ("no procedure & found for pragma%", Arg);
11219                end if;
11220
11221                Next (Arg);
11222             end loop;
11223          end No_Return;
11224
11225          -----------------
11226          -- No_Run_Time --
11227          -----------------
11228
11229          --  pragma No_Run_Time;
11230
11231          --  Note: this pragma is retained for backwards compatibility. See
11232          --  body of Rtsfind for full details on its handling.
11233
11234          when Pragma_No_Run_Time =>
11235             GNAT_Pragma;
11236             Check_Valid_Configuration_Pragma;
11237             Check_Arg_Count (0);
11238
11239             No_Run_Time_Mode           := True;
11240             Configurable_Run_Time_Mode := True;
11241
11242             --  Set Duration to 32 bits if word size is 32
11243
11244             if Ttypes.System_Word_Size = 32 then
11245                Duration_32_Bits_On_Target := True;
11246             end if;
11247
11248             --  Set appropriate restrictions
11249
11250             Set_Restriction (No_Finalization, N);
11251             Set_Restriction (No_Exception_Handlers, N);
11252             Set_Restriction (Max_Tasks, N, 0);
11253             Set_Restriction (No_Tasking, N);
11254
11255          ------------------------
11256          -- No_Strict_Aliasing --
11257          ------------------------
11258
11259          --  pragma No_Strict_Aliasing [([Entity =>] type_LOCAL_NAME)];
11260
11261          when Pragma_No_Strict_Aliasing => No_Strict_Aliasing : declare
11262             E_Id : Entity_Id;
11263
11264          begin
11265             GNAT_Pragma;
11266             Check_At_Most_N_Arguments (1);
11267
11268             if Arg_Count = 0 then
11269                Check_Valid_Configuration_Pragma;
11270                Opt.No_Strict_Aliasing := True;
11271
11272             else
11273                Check_Optional_Identifier (Arg2, Name_Entity);
11274                Check_Arg_Is_Local_Name (Arg1);
11275                E_Id := Entity (Get_Pragma_Arg (Arg1));
11276
11277                if E_Id = Any_Type then
11278                   return;
11279                elsif No (E_Id) or else not Is_Access_Type (E_Id) then
11280                   Error_Pragma_Arg ("pragma% requires access type", Arg1);
11281                end if;
11282
11283                Set_No_Strict_Aliasing (Implementation_Base_Type (E_Id));
11284             end if;
11285          end No_Strict_Aliasing;
11286
11287          -----------------------
11288          -- Normalize_Scalars --
11289          -----------------------
11290
11291          --  pragma Normalize_Scalars;
11292
11293          when Pragma_Normalize_Scalars =>
11294             Check_Ada_83_Warning;
11295             Check_Arg_Count (0);
11296             Check_Valid_Configuration_Pragma;
11297
11298             --  Normalize_Scalars creates false positives in CodePeer, and
11299             --  incorrect negative results in Alfa mode, so ignore this pragma
11300             --  in these modes.
11301
11302             if not (CodePeer_Mode or Alfa_Mode) then
11303                Normalize_Scalars := True;
11304                Init_Or_Norm_Scalars := True;
11305             end if;
11306
11307          -----------------
11308          -- Obsolescent --
11309          -----------------
11310
11311          --  pragma Obsolescent;
11312
11313          --  pragma Obsolescent (
11314          --    [Message =>] static_string_EXPRESSION
11315          --  [,[Version =>] Ada_05]]);
11316
11317          --  pragma Obsolescent (
11318          --    [Entity  =>] NAME
11319          --  [,[Message =>] static_string_EXPRESSION
11320          --  [,[Version =>] Ada_05]] );
11321
11322          when Pragma_Obsolescent => Obsolescent : declare
11323             Ename : Node_Id;
11324             Decl  : Node_Id;
11325
11326             procedure Set_Obsolescent (E : Entity_Id);
11327             --  Given an entity Ent, mark it as obsolescent if appropriate
11328
11329             ---------------------
11330             -- Set_Obsolescent --
11331             ---------------------
11332
11333             procedure Set_Obsolescent (E : Entity_Id) is
11334                Active : Boolean;
11335                Ent    : Entity_Id;
11336                S      : String_Id;
11337
11338             begin
11339                Active := True;
11340                Ent    := E;
11341
11342                --  Entity name was given
11343
11344                if Present (Ename) then
11345
11346                   --  If entity name matches, we are fine. Save entity in
11347                   --  pragma argument, for ASIS use.
11348
11349                   if Chars (Ename) = Chars (Ent) then
11350                      Set_Entity (Ename, Ent);
11351                      Generate_Reference (Ent, Ename);
11352
11353                   --  If entity name does not match, only possibility is an
11354                   --  enumeration literal from an enumeration type declaration.
11355
11356                   elsif Ekind (Ent) /= E_Enumeration_Type then
11357                      Error_Pragma
11358                        ("pragma % entity name does not match declaration");
11359
11360                   else
11361                      Ent := First_Literal (E);
11362                      loop
11363                         if No (Ent) then
11364                            Error_Pragma
11365                              ("pragma % entity name does not match any " &
11366                               "enumeration literal");
11367
11368                         elsif Chars (Ent) = Chars (Ename) then
11369                            Set_Entity (Ename, Ent);
11370                            Generate_Reference (Ent, Ename);
11371                            exit;
11372
11373                         else
11374                            Ent := Next_Literal (Ent);
11375                         end if;
11376                      end loop;
11377                   end if;
11378                end if;
11379
11380                --  Ent points to entity to be marked
11381
11382                if Arg_Count >= 1 then
11383
11384                   --  Deal with static string argument
11385
11386                   Check_Arg_Is_Static_Expression (Arg1, Standard_String);
11387                   S := Strval (Get_Pragma_Arg (Arg1));
11388
11389                   for J in 1 .. String_Length (S) loop
11390                      if not In_Character_Range (Get_String_Char (S, J)) then
11391                         Error_Pragma_Arg
11392                           ("pragma% argument does not allow wide characters",
11393                            Arg1);
11394                      end if;
11395                   end loop;
11396
11397                   Obsolescent_Warnings.Append
11398                     ((Ent => Ent, Msg => Strval (Get_Pragma_Arg (Arg1))));
11399
11400                   --  Check for Ada_05 parameter
11401
11402                   if Arg_Count /= 1 then
11403                      Check_Arg_Count (2);
11404
11405                      declare
11406                         Argx : constant Node_Id := Get_Pragma_Arg (Arg2);
11407
11408                      begin
11409                         Check_Arg_Is_Identifier (Argx);
11410
11411                         if Chars (Argx) /= Name_Ada_05 then
11412                            Error_Msg_Name_2 := Name_Ada_05;
11413                            Error_Pragma_Arg
11414                              ("only allowed argument for pragma% is %", Argx);
11415                         end if;
11416
11417                         if Ada_Version_Explicit < Ada_2005
11418                           or else not Warn_On_Ada_2005_Compatibility
11419                         then
11420                            Active := False;
11421                         end if;
11422                      end;
11423                   end if;
11424                end if;
11425
11426                --  Set flag if pragma active
11427
11428                if Active then
11429                   Set_Is_Obsolescent (Ent);
11430                end if;
11431
11432                return;
11433             end Set_Obsolescent;
11434
11435          --  Start of processing for pragma Obsolescent
11436
11437          begin
11438             GNAT_Pragma;
11439
11440             Check_At_Most_N_Arguments (3);
11441
11442             --  See if first argument specifies an entity name
11443
11444             if Arg_Count >= 1
11445               and then
11446                 (Chars (Arg1) = Name_Entity
11447                    or else
11448                      Nkind_In (Get_Pragma_Arg (Arg1), N_Character_Literal,
11449                                                       N_Identifier,
11450                                                       N_Operator_Symbol))
11451             then
11452                Ename := Get_Pragma_Arg (Arg1);
11453
11454                --  Eliminate first argument, so we can share processing
11455
11456                Arg1 := Arg2;
11457                Arg2 := Arg3;
11458                Arg_Count := Arg_Count - 1;
11459
11460             --  No Entity name argument given
11461
11462             else
11463                Ename := Empty;
11464             end if;
11465
11466             if Arg_Count >= 1 then
11467                Check_Optional_Identifier (Arg1, Name_Message);
11468
11469                if Arg_Count = 2 then
11470                   Check_Optional_Identifier (Arg2, Name_Version);
11471                end if;
11472             end if;
11473
11474             --  Get immediately preceding declaration
11475
11476             Decl := Prev (N);
11477             while Present (Decl) and then Nkind (Decl) = N_Pragma loop
11478                Prev (Decl);
11479             end loop;
11480
11481             --  Cases where we do not follow anything other than another pragma
11482
11483             if No (Decl) then
11484
11485                --  First case: library level compilation unit declaration with
11486                --  the pragma immediately following the declaration.
11487
11488                if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
11489                   Set_Obsolescent
11490                     (Defining_Entity (Unit (Parent (Parent (N)))));
11491                   return;
11492
11493                --  Case 2: library unit placement for package
11494
11495                else
11496                   declare
11497                      Ent : constant Entity_Id := Find_Lib_Unit_Name;
11498                   begin
11499                      if Is_Package_Or_Generic_Package (Ent) then
11500                         Set_Obsolescent (Ent);
11501                         return;
11502                      end if;
11503                   end;
11504                end if;
11505
11506             --  Cases where we must follow a declaration
11507
11508             else
11509                if         Nkind (Decl) not in N_Declaration
11510                  and then Nkind (Decl) not in N_Later_Decl_Item
11511                  and then Nkind (Decl) not in N_Generic_Declaration
11512                  and then Nkind (Decl) not in N_Renaming_Declaration
11513                then
11514                   Error_Pragma
11515                     ("pragma% misplaced, "
11516                      & "must immediately follow a declaration");
11517
11518                else
11519                   Set_Obsolescent (Defining_Entity (Decl));
11520                   return;
11521                end if;
11522             end if;
11523          end Obsolescent;
11524
11525          --------------
11526          -- Optimize --
11527          --------------
11528
11529          --  pragma Optimize (Time | Space | Off);
11530
11531          --  The actual check for optimize is done in Gigi. Note that this
11532          --  pragma does not actually change the optimization setting, it
11533          --  simply checks that it is consistent with the pragma.
11534
11535          when Pragma_Optimize =>
11536             Check_No_Identifiers;
11537             Check_Arg_Count (1);
11538             Check_Arg_Is_One_Of (Arg1, Name_Time, Name_Space, Name_Off);
11539
11540          ------------------------
11541          -- Optimize_Alignment --
11542          ------------------------
11543
11544          --  pragma Optimize_Alignment (Time | Space | Off);
11545
11546          when Pragma_Optimize_Alignment => Optimize_Alignment : begin
11547             GNAT_Pragma;
11548             Check_No_Identifiers;
11549             Check_Arg_Count (1);
11550             Check_Valid_Configuration_Pragma;
11551
11552             declare
11553                Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
11554             begin
11555                case Nam is
11556                   when Name_Time =>
11557                      Opt.Optimize_Alignment := 'T';
11558                   when Name_Space =>
11559                      Opt.Optimize_Alignment := 'S';
11560                   when Name_Off =>
11561                      Opt.Optimize_Alignment := 'O';
11562                   when others =>
11563                      Error_Pragma_Arg ("invalid argument for pragma%", Arg1);
11564                end case;
11565             end;
11566
11567             --  Set indication that mode is set locally. If we are in fact in a
11568             --  configuration pragma file, this setting is harmless since the
11569             --  switch will get reset anyway at the start of each unit.
11570
11571             Optimize_Alignment_Local := True;
11572          end Optimize_Alignment;
11573
11574          -------------
11575          -- Ordered --
11576          -------------
11577
11578          --  pragma Ordered (first_enumeration_subtype_LOCAL_NAME);
11579
11580          when Pragma_Ordered => Ordered : declare
11581             Assoc   : constant Node_Id := Arg1;
11582             Type_Id : Node_Id;
11583             Typ     : Entity_Id;
11584
11585          begin
11586             GNAT_Pragma;
11587             Check_No_Identifiers;
11588             Check_Arg_Count (1);
11589             Check_Arg_Is_Local_Name (Arg1);
11590
11591             Type_Id := Get_Pragma_Arg (Assoc);
11592             Find_Type (Type_Id);
11593             Typ := Entity (Type_Id);
11594
11595             if Typ = Any_Type then
11596                return;
11597             else
11598                Typ := Underlying_Type (Typ);
11599             end if;
11600
11601             if not Is_Enumeration_Type (Typ) then
11602                Error_Pragma ("pragma% must specify enumeration type");
11603             end if;
11604
11605             Check_First_Subtype (Arg1);
11606             Set_Has_Pragma_Ordered (Base_Type (Typ));
11607          end Ordered;
11608
11609          ----------
11610          -- Pack --
11611          ----------
11612
11613          --  pragma Pack (first_subtype_LOCAL_NAME);
11614
11615          when Pragma_Pack => Pack : declare
11616             Assoc   : constant Node_Id := Arg1;
11617             Type_Id : Node_Id;
11618             Typ     : Entity_Id;
11619             Ctyp    : Entity_Id;
11620             Ignore  : Boolean := False;
11621
11622          begin
11623             Check_No_Identifiers;
11624             Check_Arg_Count (1);
11625             Check_Arg_Is_Local_Name (Arg1);
11626
11627             Type_Id := Get_Pragma_Arg (Assoc);
11628             Find_Type (Type_Id);
11629             Typ := Entity (Type_Id);
11630
11631             if Typ = Any_Type
11632               or else Rep_Item_Too_Early (Typ, N)
11633             then
11634                return;
11635             else
11636                Typ := Underlying_Type (Typ);
11637             end if;
11638
11639             if not Is_Array_Type (Typ) and then not Is_Record_Type (Typ) then
11640                Error_Pragma ("pragma% must specify array or record type");
11641             end if;
11642
11643             Check_First_Subtype (Arg1);
11644             Check_Duplicate_Pragma (Typ);
11645
11646             --  Array type
11647
11648             if Is_Array_Type (Typ) then
11649                Ctyp := Component_Type (Typ);
11650
11651                --  Ignore pack that does nothing
11652
11653                if Known_Static_Esize (Ctyp)
11654                  and then Known_Static_RM_Size (Ctyp)
11655                  and then Esize (Ctyp) = RM_Size (Ctyp)
11656                  and then Addressable (Esize (Ctyp))
11657                then
11658                   Ignore := True;
11659                end if;
11660
11661                --  Process OK pragma Pack. Note that if there is a separate
11662                --  component clause present, the Pack will be cancelled. This
11663                --  processing is in Freeze.
11664
11665                if not Rep_Item_Too_Late (Typ, N) then
11666
11667                   --  In the context of static code analysis, we do not need
11668                   --  complex front-end expansions related to pragma Pack,
11669                   --  so disable handling of pragma Pack in these cases.
11670
11671                   if CodePeer_Mode or Alfa_Mode then
11672                      null;
11673
11674                   --  Don't attempt any packing for VM targets. We possibly
11675                   --  could deal with some cases of array bit-packing, but we
11676                   --  don't bother, since this is not a typical kind of
11677                   --  representation in the VM context anyway (and would not
11678                   --  for example work nicely with the debugger).
11679
11680                   elsif VM_Target /= No_VM then
11681                      if not GNAT_Mode then
11682                         Error_Pragma
11683                           ("?pragma% ignored in this configuration");
11684                      end if;
11685
11686                   --  Normal case where we do the pack action
11687
11688                   else
11689                      if not Ignore then
11690                         Set_Is_Packed            (Base_Type (Typ));
11691                         Set_Has_Non_Standard_Rep (Base_Type (Typ));
11692                      end if;
11693
11694                      Set_Has_Pragma_Pack (Base_Type (Typ));
11695                   end if;
11696                end if;
11697
11698             --  For record types, the pack is always effective
11699
11700             else pragma Assert (Is_Record_Type (Typ));
11701                if not Rep_Item_Too_Late (Typ, N) then
11702
11703                   --  Ignore pack request with warning in VM mode (skip warning
11704                   --  if we are compiling GNAT run time library).
11705
11706                   if VM_Target /= No_VM then
11707                      if not GNAT_Mode then
11708                         Error_Pragma
11709                           ("?pragma% ignored in this configuration");
11710                      end if;
11711
11712                   --  Normal case of pack request active
11713
11714                   else
11715                      Set_Is_Packed            (Base_Type (Typ));
11716                      Set_Has_Pragma_Pack      (Base_Type (Typ));
11717                      Set_Has_Non_Standard_Rep (Base_Type (Typ));
11718                   end if;
11719                end if;
11720             end if;
11721          end Pack;
11722
11723          ----------
11724          -- Page --
11725          ----------
11726
11727          --  pragma Page;
11728
11729          --  There is nothing to do here, since we did all the processing for
11730          --  this pragma in Par.Prag (so that it works properly even in syntax
11731          --  only mode).
11732
11733          when Pragma_Page =>
11734             null;
11735
11736          -------------
11737          -- Passive --
11738          -------------
11739
11740          --  pragma Passive [(PASSIVE_FORM)];
11741
11742          --  PASSIVE_FORM ::= Semaphore | No
11743
11744          when Pragma_Passive =>
11745             GNAT_Pragma;
11746
11747             if Nkind (Parent (N)) /= N_Task_Definition then
11748                Error_Pragma ("pragma% must be within task definition");
11749             end if;
11750
11751             if Arg_Count /= 0 then
11752                Check_Arg_Count (1);
11753                Check_Arg_Is_One_Of (Arg1, Name_Semaphore, Name_No);
11754             end if;
11755
11756          ----------------------------------
11757          -- Preelaborable_Initialization --
11758          ----------------------------------
11759
11760          --  pragma Preelaborable_Initialization (DIRECT_NAME);
11761
11762          when Pragma_Preelaborable_Initialization => Preelab_Init : declare
11763             Ent : Entity_Id;
11764
11765          begin
11766             Ada_2005_Pragma;
11767             Check_Arg_Count (1);
11768             Check_No_Identifiers;
11769             Check_Arg_Is_Identifier (Arg1);
11770             Check_Arg_Is_Local_Name (Arg1);
11771             Check_First_Subtype (Arg1);
11772             Ent := Entity (Get_Pragma_Arg (Arg1));
11773
11774             if not (Is_Private_Type (Ent)
11775                       or else
11776                     Is_Protected_Type (Ent)
11777                       or else
11778                     (Is_Generic_Type (Ent) and then Is_Derived_Type (Ent)))
11779             then
11780                Error_Pragma_Arg
11781                  ("pragma % can only be applied to private, formal derived or "
11782                   & "protected type",
11783                   Arg1);
11784             end if;
11785
11786             --  Give an error if the pragma is applied to a protected type that
11787             --  does not qualify (due to having entries, or due to components
11788             --  that do not qualify).
11789
11790             if Is_Protected_Type (Ent)
11791               and then not Has_Preelaborable_Initialization (Ent)
11792             then
11793                Error_Msg_N
11794                  ("protected type & does not have preelaborable " &
11795                   "initialization", Ent);
11796
11797             --  Otherwise mark the type as definitely having preelaborable
11798             --  initialization.
11799
11800             else
11801                Set_Known_To_Have_Preelab_Init (Ent);
11802             end if;
11803
11804             if Has_Pragma_Preelab_Init (Ent)
11805               and then Warn_On_Redundant_Constructs
11806             then
11807                Error_Pragma ("?duplicate pragma%!");
11808             else
11809                Set_Has_Pragma_Preelab_Init (Ent);
11810             end if;
11811          end Preelab_Init;
11812
11813          --------------------
11814          -- Persistent_BSS --
11815          --------------------
11816
11817          --  pragma Persistent_BSS [(object_NAME)];
11818
11819          when Pragma_Persistent_BSS => Persistent_BSS :  declare
11820             Decl : Node_Id;
11821             Ent  : Entity_Id;
11822             Prag : Node_Id;
11823
11824          begin
11825             GNAT_Pragma;
11826             Check_At_Most_N_Arguments (1);
11827
11828             --  Case of application to specific object (one argument)
11829
11830             if Arg_Count = 1 then
11831                Check_Arg_Is_Library_Level_Local_Name (Arg1);
11832
11833                if not Is_Entity_Name (Get_Pragma_Arg (Arg1))
11834                  or else not
11835                   Ekind_In (Entity (Get_Pragma_Arg (Arg1)), E_Variable,
11836                                                             E_Constant)
11837                then
11838                   Error_Pragma_Arg ("pragma% only applies to objects", Arg1);
11839                end if;
11840
11841                Ent := Entity (Get_Pragma_Arg (Arg1));
11842                Decl := Parent (Ent);
11843
11844                if Rep_Item_Too_Late (Ent, N) then
11845                   return;
11846                end if;
11847
11848                if Present (Expression (Decl)) then
11849                   Error_Pragma_Arg
11850                     ("object for pragma% cannot have initialization", Arg1);
11851                end if;
11852
11853                if not Is_Potentially_Persistent_Type (Etype (Ent)) then
11854                   Error_Pragma_Arg
11855                     ("object type for pragma% is not potentially persistent",
11856                      Arg1);
11857                end if;
11858
11859                Check_Duplicate_Pragma (Ent);
11860
11861                Prag :=
11862                  Make_Linker_Section_Pragma
11863                    (Ent, Sloc (N), ".persistent.bss");
11864                Insert_After (N, Prag);
11865                Analyze (Prag);
11866
11867             --  Case of use as configuration pragma with no arguments
11868
11869             else
11870                Check_Valid_Configuration_Pragma;
11871                Persistent_BSS_Mode := True;
11872             end if;
11873          end Persistent_BSS;
11874
11875          -------------
11876          -- Polling --
11877          -------------
11878
11879          --  pragma Polling (ON | OFF);
11880
11881          when Pragma_Polling =>
11882             GNAT_Pragma;
11883             Check_Arg_Count (1);
11884             Check_No_Identifiers;
11885             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
11886             Polling_Required := (Chars (Get_Pragma_Arg (Arg1)) = Name_On);
11887
11888          -------------------
11889          -- Postcondition --
11890          -------------------
11891
11892          --  pragma Postcondition ([Check   =>] Boolean_EXPRESSION
11893          --                      [,[Message =>] String_EXPRESSION]);
11894
11895          when Pragma_Postcondition => Postcondition : declare
11896             In_Body : Boolean;
11897             pragma Warnings (Off, In_Body);
11898
11899          begin
11900             GNAT_Pragma;
11901             Check_At_Least_N_Arguments (1);
11902             Check_At_Most_N_Arguments (2);
11903             Check_Optional_Identifier (Arg1, Name_Check);
11904
11905             --  All we need to do here is call the common check procedure,
11906             --  the remainder of the processing is found in Sem_Ch6/Sem_Ch7.
11907
11908             Check_Precondition_Postcondition (In_Body);
11909          end Postcondition;
11910
11911          ------------------
11912          -- Precondition --
11913          ------------------
11914
11915          --  pragma Precondition ([Check   =>] Boolean_EXPRESSION
11916          --                     [,[Message =>] String_EXPRESSION]);
11917
11918          when Pragma_Precondition => Precondition : declare
11919             In_Body : Boolean;
11920
11921          begin
11922             GNAT_Pragma;
11923             Check_At_Least_N_Arguments (1);
11924             Check_At_Most_N_Arguments (2);
11925             Check_Optional_Identifier (Arg1, Name_Check);
11926             Check_Precondition_Postcondition (In_Body);
11927
11928             --  If in spec, nothing more to do. If in body, then we convert the
11929             --  pragma to pragma Check (Precondition, cond [, msg]). Note we do
11930             --  this whether or not precondition checks are enabled. That works
11931             --  fine since pragma Check will do this check, and will also
11932             --  analyze the condition itself in the proper context.
11933
11934             if In_Body then
11935                Rewrite (N,
11936                  Make_Pragma (Loc,
11937                    Chars => Name_Check,
11938                    Pragma_Argument_Associations => New_List (
11939                      Make_Pragma_Argument_Association (Loc,
11940                        Expression => Make_Identifier (Loc, Name_Precondition)),
11941
11942                      Make_Pragma_Argument_Association (Sloc (Arg1),
11943                        Expression => Relocate_Node (Get_Pragma_Arg (Arg1))))));
11944
11945                if Arg_Count = 2 then
11946                   Append_To (Pragma_Argument_Associations (N),
11947                     Make_Pragma_Argument_Association (Sloc (Arg2),
11948                       Expression => Relocate_Node (Get_Pragma_Arg (Arg2))));
11949                end if;
11950
11951                Analyze (N);
11952             end if;
11953          end Precondition;
11954
11955          ---------------
11956          -- Predicate --
11957          ---------------
11958
11959          --  pragma Predicate
11960          --    ([Entity =>] type_LOCAL_NAME,
11961          --     [Check  =>] EXPRESSION);
11962
11963          when Pragma_Predicate => Predicate : declare
11964             Type_Id : Node_Id;
11965             Typ     : Entity_Id;
11966
11967             Discard : Boolean;
11968             pragma Unreferenced (Discard);
11969
11970          begin
11971             GNAT_Pragma;
11972             Check_Arg_Count (2);
11973             Check_Optional_Identifier (Arg1, Name_Entity);
11974             Check_Optional_Identifier (Arg2, Name_Check);
11975
11976             Check_Arg_Is_Local_Name (Arg1);
11977
11978             Type_Id := Get_Pragma_Arg (Arg1);
11979             Find_Type (Type_Id);
11980             Typ := Entity (Type_Id);
11981
11982             if Typ = Any_Type then
11983                return;
11984             end if;
11985
11986             --  The remaining processing is simply to link the pragma on to
11987             --  the rep item chain, for processing when the type is frozen.
11988             --  This is accomplished by a call to Rep_Item_Too_Late. We also
11989             --  mark the type as having predicates.
11990
11991             Set_Has_Predicates (Typ);
11992             Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
11993          end Predicate;
11994
11995          ------------------
11996          -- Preelaborate --
11997          ------------------
11998
11999          --  pragma Preelaborate [(library_unit_NAME)];
12000
12001          --  Set the flag Is_Preelaborated of program unit name entity
12002
12003          when Pragma_Preelaborate => Preelaborate : declare
12004             Pa  : constant Node_Id   := Parent (N);
12005             Pk  : constant Node_Kind := Nkind (Pa);
12006             Ent : Entity_Id;
12007
12008          begin
12009             Check_Ada_83_Warning;
12010             Check_Valid_Library_Unit_Pragma;
12011
12012             if Nkind (N) = N_Null_Statement then
12013                return;
12014             end if;
12015
12016             Ent := Find_Lib_Unit_Name;
12017             Check_Duplicate_Pragma (Ent);
12018
12019             --  This filters out pragmas inside generic parent then
12020             --  show up inside instantiation
12021
12022             if Present (Ent)
12023               and then not (Pk = N_Package_Specification
12024                              and then Present (Generic_Parent (Pa)))
12025             then
12026                if not Debug_Flag_U then
12027                   Set_Is_Preelaborated (Ent);
12028                   Set_Suppress_Elaboration_Warnings (Ent);
12029                end if;
12030             end if;
12031          end Preelaborate;
12032
12033          ---------------------
12034          -- Preelaborate_05 --
12035          ---------------------
12036
12037          --  pragma Preelaborate_05 [(library_unit_NAME)];
12038
12039          --  This pragma is useable only in GNAT_Mode, where it is used like
12040          --  pragma Preelaborate but it is only effective in Ada 2005 mode
12041          --  (otherwise it is ignored). This is used to implement AI-362 which
12042          --  recategorizes some run-time packages in Ada 2005 mode.
12043
12044          when Pragma_Preelaborate_05 => Preelaborate_05 : declare
12045             Ent : Entity_Id;
12046
12047          begin
12048             GNAT_Pragma;
12049             Check_Valid_Library_Unit_Pragma;
12050
12051             if not GNAT_Mode then
12052                Error_Pragma ("pragma% only available in GNAT mode");
12053             end if;
12054
12055             if Nkind (N) = N_Null_Statement then
12056                return;
12057             end if;
12058
12059             --  This is one of the few cases where we need to test the value of
12060             --  Ada_Version_Explicit rather than Ada_Version (which is always
12061             --  set to Ada_2012 in a predefined unit), we need to know the
12062             --  explicit version set to know if this pragma is active.
12063
12064             if Ada_Version_Explicit >= Ada_2005 then
12065                Ent := Find_Lib_Unit_Name;
12066                Set_Is_Preelaborated (Ent);
12067                Set_Suppress_Elaboration_Warnings (Ent);
12068             end if;
12069          end Preelaborate_05;
12070
12071          --------------
12072          -- Priority --
12073          --------------
12074
12075          --  pragma Priority (EXPRESSION);
12076
12077          when Pragma_Priority => Priority : declare
12078             P   : constant Node_Id := Parent (N);
12079             Arg : Node_Id;
12080
12081          begin
12082             Check_No_Identifiers;
12083             Check_Arg_Count (1);
12084
12085             --  Subprogram case
12086
12087             if Nkind (P) = N_Subprogram_Body then
12088                Check_In_Main_Program;
12089
12090                Arg := Get_Pragma_Arg (Arg1);
12091                Analyze_And_Resolve (Arg, Standard_Integer);
12092
12093                --  Must be static
12094
12095                if not Is_Static_Expression (Arg) then
12096                   Flag_Non_Static_Expr
12097                     ("main subprogram priority is not static!", Arg);
12098                   raise Pragma_Exit;
12099
12100                --  If constraint error, then we already signalled an error
12101
12102                elsif Raises_Constraint_Error (Arg) then
12103                   null;
12104
12105                --  Otherwise check in range
12106
12107                else
12108                   declare
12109                      Val : constant Uint := Expr_Value (Arg);
12110
12111                   begin
12112                      if Val < 0
12113                        or else Val > Expr_Value (Expression
12114                                        (Parent (RTE (RE_Max_Priority))))
12115                      then
12116                         Error_Pragma_Arg
12117                           ("main subprogram priority is out of range", Arg1);
12118                      end if;
12119                   end;
12120                end if;
12121
12122                Set_Main_Priority
12123                     (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
12124
12125                --  Load an arbitrary entity from System.Tasking to make sure
12126                --  this package is implicitly with'ed, since we need to have
12127                --  the tasking run-time active for the pragma Priority to have
12128                --  any effect.
12129
12130                declare
12131                   Discard : Entity_Id;
12132                   pragma Warnings (Off, Discard);
12133                begin
12134                   Discard := RTE (RE_Task_List);
12135                end;
12136
12137             --  Task or Protected, must be of type Integer
12138
12139             elsif Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
12140                Arg := Get_Pragma_Arg (Arg1);
12141
12142                --  The expression must be analyzed in the special manner
12143                --  described in "Handling of Default and Per-Object
12144                --  Expressions" in sem.ads.
12145
12146                Preanalyze_Spec_Expression (Arg, Standard_Integer);
12147
12148                if not Is_Static_Expression (Arg) then
12149                   Check_Restriction (Static_Priorities, Arg);
12150                end if;
12151
12152             --  Anything else is incorrect
12153
12154             else
12155                Pragma_Misplaced;
12156             end if;
12157
12158             if Has_Pragma_Priority (P) then
12159                Error_Pragma ("duplicate pragma% not allowed");
12160             else
12161                Set_Has_Pragma_Priority (P, True);
12162
12163                if Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
12164                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
12165                   --  exp_ch9 should use this ???
12166                end if;
12167             end if;
12168          end Priority;
12169
12170          -----------------------------------
12171          -- Priority_Specific_Dispatching --
12172          -----------------------------------
12173
12174          --  pragma Priority_Specific_Dispatching (
12175          --    policy_IDENTIFIER,
12176          --    first_priority_EXPRESSION,
12177          --    last_priority_EXPRESSION);
12178
12179          when Pragma_Priority_Specific_Dispatching =>
12180          Priority_Specific_Dispatching : declare
12181             Prio_Id : constant Entity_Id := RTE (RE_Any_Priority);
12182             --  This is the entity System.Any_Priority;
12183
12184             DP          : Character;
12185             Lower_Bound : Node_Id;
12186             Upper_Bound : Node_Id;
12187             Lower_Val   : Uint;
12188             Upper_Val   : Uint;
12189
12190          begin
12191             Ada_2005_Pragma;
12192             Check_Arg_Count (3);
12193             Check_No_Identifiers;
12194             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
12195             Check_Valid_Configuration_Pragma;
12196             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
12197             DP := Fold_Upper (Name_Buffer (1));
12198
12199             Lower_Bound := Get_Pragma_Arg (Arg2);
12200             Check_Arg_Is_Static_Expression (Lower_Bound, Standard_Integer);
12201             Lower_Val := Expr_Value (Lower_Bound);
12202
12203             Upper_Bound := Get_Pragma_Arg (Arg3);
12204             Check_Arg_Is_Static_Expression (Upper_Bound, Standard_Integer);
12205             Upper_Val := Expr_Value (Upper_Bound);
12206
12207             --  It is not allowed to use Task_Dispatching_Policy and
12208             --  Priority_Specific_Dispatching in the same partition.
12209
12210             if Task_Dispatching_Policy /= ' ' then
12211                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
12212                Error_Pragma
12213                  ("pragma% incompatible with Task_Dispatching_Policy#");
12214
12215             --  Check lower bound in range
12216
12217             elsif Lower_Val < Expr_Value (Type_Low_Bound (Prio_Id))
12218                     or else
12219                   Lower_Val > Expr_Value (Type_High_Bound (Prio_Id))
12220             then
12221                Error_Pragma_Arg
12222                  ("first_priority is out of range", Arg2);
12223
12224             --  Check upper bound in range
12225
12226             elsif Upper_Val < Expr_Value (Type_Low_Bound (Prio_Id))
12227                     or else
12228                   Upper_Val > Expr_Value (Type_High_Bound (Prio_Id))
12229             then
12230                Error_Pragma_Arg
12231                  ("last_priority is out of range", Arg3);
12232
12233             --  Check that the priority range is valid
12234
12235             elsif Lower_Val > Upper_Val then
12236                Error_Pragma
12237                  ("last_priority_expression must be greater than" &
12238                   " or equal to first_priority_expression");
12239
12240             --  Store the new policy, but always preserve System_Location since
12241             --  we like the error message with the run-time name.
12242
12243             else
12244                --  Check overlapping in the priority ranges specified in other
12245                --  Priority_Specific_Dispatching pragmas within the same
12246                --  partition. We can only check those we know about!
12247
12248                for J in
12249                   Specific_Dispatching.First .. Specific_Dispatching.Last
12250                loop
12251                   if Specific_Dispatching.Table (J).First_Priority in
12252                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
12253                   or else Specific_Dispatching.Table (J).Last_Priority in
12254                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
12255                   then
12256                      Error_Msg_Sloc :=
12257                        Specific_Dispatching.Table (J).Pragma_Loc;
12258                         Error_Pragma
12259                           ("priority range overlaps with "
12260                            & "Priority_Specific_Dispatching#");
12261                   end if;
12262                end loop;
12263
12264                --  The use of Priority_Specific_Dispatching is incompatible
12265                --  with Task_Dispatching_Policy.
12266
12267                if Task_Dispatching_Policy /= ' ' then
12268                   Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
12269                      Error_Pragma
12270                        ("Priority_Specific_Dispatching incompatible "
12271                         & "with Task_Dispatching_Policy#");
12272                end if;
12273
12274                --  The use of Priority_Specific_Dispatching forces ceiling
12275                --  locking policy.
12276
12277                if Locking_Policy /= ' ' and then Locking_Policy /= 'C' then
12278                   Error_Msg_Sloc := Locking_Policy_Sloc;
12279                      Error_Pragma
12280                        ("Priority_Specific_Dispatching incompatible "
12281                         & "with Locking_Policy#");
12282
12283                --  Set the Ceiling_Locking policy, but preserve System_Location
12284                --  since we like the error message with the run time name.
12285
12286                else
12287                   Locking_Policy := 'C';
12288
12289                   if Locking_Policy_Sloc /= System_Location then
12290                      Locking_Policy_Sloc := Loc;
12291                   end if;
12292                end if;
12293
12294                --  Add entry in the table
12295
12296                Specific_Dispatching.Append
12297                     ((Dispatching_Policy => DP,
12298                       First_Priority     => UI_To_Int (Lower_Val),
12299                       Last_Priority      => UI_To_Int (Upper_Val),
12300                       Pragma_Loc         => Loc));
12301             end if;
12302          end Priority_Specific_Dispatching;
12303
12304          -------------
12305          -- Profile --
12306          -------------
12307
12308          --  pragma Profile (profile_IDENTIFIER);
12309
12310          --  profile_IDENTIFIER => Restricted | Ravenscar
12311
12312          when Pragma_Profile =>
12313             Ada_2005_Pragma;
12314             Check_Arg_Count (1);
12315             Check_Valid_Configuration_Pragma;
12316             Check_No_Identifiers;
12317
12318             declare
12319                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
12320
12321             begin
12322                if Chars (Argx) = Name_Ravenscar then
12323                   Set_Ravenscar_Profile (N);
12324
12325                elsif Chars (Argx) = Name_Restricted then
12326                   Set_Profile_Restrictions
12327                     (Restricted,
12328                      N, Warn => Treat_Restrictions_As_Warnings);
12329
12330                elsif Chars (Argx) = Name_No_Implementation_Extensions then
12331                   Set_Profile_Restrictions
12332                     (No_Implementation_Extensions,
12333                      N, Warn => Treat_Restrictions_As_Warnings);
12334
12335                else
12336                   Error_Pragma_Arg ("& is not a valid profile", Argx);
12337                end if;
12338             end;
12339
12340          ----------------------
12341          -- Profile_Warnings --
12342          ----------------------
12343
12344          --  pragma Profile_Warnings (profile_IDENTIFIER);
12345
12346          --  profile_IDENTIFIER => Restricted | Ravenscar
12347
12348          when Pragma_Profile_Warnings =>
12349             GNAT_Pragma;
12350             Check_Arg_Count (1);
12351             Check_Valid_Configuration_Pragma;
12352             Check_No_Identifiers;
12353
12354             declare
12355                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
12356
12357             begin
12358                if Chars (Argx) = Name_Ravenscar then
12359                   Set_Profile_Restrictions (Ravenscar, N, Warn => True);
12360
12361                elsif Chars (Argx) = Name_Restricted then
12362                   Set_Profile_Restrictions (Restricted, N, Warn => True);
12363
12364                elsif Chars (Argx) = Name_No_Implementation_Extensions then
12365                   Set_Profile_Restrictions
12366                     (No_Implementation_Extensions, N, Warn => True);
12367
12368                else
12369                   Error_Pragma_Arg ("& is not a valid profile", Argx);
12370                end if;
12371             end;
12372
12373          --------------------------
12374          -- Propagate_Exceptions --
12375          --------------------------
12376
12377          --  pragma Propagate_Exceptions;
12378
12379          --  Note: this pragma is obsolete and has no effect
12380
12381          when Pragma_Propagate_Exceptions =>
12382             GNAT_Pragma;
12383             Check_Arg_Count (0);
12384
12385             if In_Extended_Main_Source_Unit (N) then
12386                Propagate_Exceptions := True;
12387             end if;
12388
12389          ------------------
12390          -- Psect_Object --
12391          ------------------
12392
12393          --  pragma Psect_Object (
12394          --        [Internal =>] LOCAL_NAME,
12395          --     [, [External =>] EXTERNAL_SYMBOL]
12396          --     [, [Size     =>] EXTERNAL_SYMBOL]);
12397
12398          when Pragma_Psect_Object | Pragma_Common_Object =>
12399          Psect_Object : declare
12400             Args  : Args_List (1 .. 3);
12401             Names : constant Name_List (1 .. 3) := (
12402                       Name_Internal,
12403                       Name_External,
12404                       Name_Size);
12405
12406             Internal : Node_Id renames Args (1);
12407             External : Node_Id renames Args (2);
12408             Size     : Node_Id renames Args (3);
12409
12410             Def_Id : Entity_Id;
12411
12412             procedure Check_Too_Long (Arg : Node_Id);
12413             --  Posts message if the argument is an identifier with more
12414             --  than 31 characters, or a string literal with more than
12415             --  31 characters, and we are operating under VMS
12416
12417             --------------------
12418             -- Check_Too_Long --
12419             --------------------
12420
12421             procedure Check_Too_Long (Arg : Node_Id) is
12422                X : constant Node_Id := Original_Node (Arg);
12423
12424             begin
12425                if not Nkind_In (X, N_String_Literal, N_Identifier) then
12426                   Error_Pragma_Arg
12427                     ("inappropriate argument for pragma %", Arg);
12428                end if;
12429
12430                if OpenVMS_On_Target then
12431                   if (Nkind (X) = N_String_Literal
12432                        and then String_Length (Strval (X)) > 31)
12433                     or else
12434                      (Nkind (X) = N_Identifier
12435                        and then Length_Of_Name (Chars (X)) > 31)
12436                   then
12437                      Error_Pragma_Arg
12438                        ("argument for pragma % is longer than 31 characters",
12439                         Arg);
12440                   end if;
12441                end if;
12442             end Check_Too_Long;
12443
12444          --  Start of processing for Common_Object/Psect_Object
12445
12446          begin
12447             GNAT_Pragma;
12448             Gather_Associations (Names, Args);
12449             Process_Extended_Import_Export_Internal_Arg (Internal);
12450
12451             Def_Id := Entity (Internal);
12452
12453             if not Ekind_In (Def_Id, E_Constant, E_Variable) then
12454                Error_Pragma_Arg
12455                  ("pragma% must designate an object", Internal);
12456             end if;
12457
12458             Check_Too_Long (Internal);
12459
12460             if Is_Imported (Def_Id) or else Is_Exported (Def_Id) then
12461                Error_Pragma_Arg
12462                  ("cannot use pragma% for imported/exported object",
12463                   Internal);
12464             end if;
12465
12466             if Is_Concurrent_Type (Etype (Internal)) then
12467                Error_Pragma_Arg
12468                  ("cannot specify pragma % for task/protected object",
12469                   Internal);
12470             end if;
12471
12472             if Has_Rep_Pragma (Def_Id, Name_Common_Object)
12473                  or else
12474                Has_Rep_Pragma (Def_Id, Name_Psect_Object)
12475             then
12476                Error_Msg_N ("?duplicate Common/Psect_Object pragma", N);
12477             end if;
12478
12479             if Ekind (Def_Id) = E_Constant then
12480                Error_Pragma_Arg
12481                  ("cannot specify pragma % for a constant", Internal);
12482             end if;
12483
12484             if Is_Record_Type (Etype (Internal)) then
12485                declare
12486                   Ent  : Entity_Id;
12487                   Decl : Entity_Id;
12488
12489                begin
12490                   Ent := First_Entity (Etype (Internal));
12491                   while Present (Ent) loop
12492                      Decl := Declaration_Node (Ent);
12493
12494                      if Ekind (Ent) = E_Component
12495                        and then Nkind (Decl) = N_Component_Declaration
12496                        and then Present (Expression (Decl))
12497                        and then Warn_On_Export_Import
12498                      then
12499                         Error_Msg_N
12500                           ("?object for pragma % has defaults", Internal);
12501                         exit;
12502
12503                      else
12504                         Next_Entity (Ent);
12505                      end if;
12506                   end loop;
12507                end;
12508             end if;
12509
12510             if Present (Size) then
12511                Check_Too_Long (Size);
12512             end if;
12513
12514             if Present (External) then
12515                Check_Arg_Is_External_Name (External);
12516                Check_Too_Long (External);
12517             end if;
12518
12519             --  If all error tests pass, link pragma on to the rep item chain
12520
12521             Record_Rep_Item (Def_Id, N);
12522          end Psect_Object;
12523
12524          ----------
12525          -- Pure --
12526          ----------
12527
12528          --  pragma Pure [(library_unit_NAME)];
12529
12530          when Pragma_Pure => Pure : declare
12531             Ent : Entity_Id;
12532
12533          begin
12534             Check_Ada_83_Warning;
12535             Check_Valid_Library_Unit_Pragma;
12536
12537             if Nkind (N) = N_Null_Statement then
12538                return;
12539             end if;
12540
12541             Ent := Find_Lib_Unit_Name;
12542             Set_Is_Pure (Ent);
12543             Set_Has_Pragma_Pure (Ent);
12544             Set_Suppress_Elaboration_Warnings (Ent);
12545          end Pure;
12546
12547          -------------
12548          -- Pure_05 --
12549          -------------
12550
12551          --  pragma Pure_05 [(library_unit_NAME)];
12552
12553          --  This pragma is useable only in GNAT_Mode, where it is used like
12554          --  pragma Pure but it is only effective in Ada 2005 mode (otherwise
12555          --  it is ignored). It may be used after a pragma Preelaborate, in
12556          --  which case it overrides the effect of the pragma Preelaborate.
12557          --  This is used to implement AI-362 which recategorizes some run-time
12558          --  packages in Ada 2005 mode.
12559
12560          when Pragma_Pure_05 => Pure_05 : declare
12561             Ent : Entity_Id;
12562
12563          begin
12564             GNAT_Pragma;
12565             Check_Valid_Library_Unit_Pragma;
12566
12567             if not GNAT_Mode then
12568                Error_Pragma ("pragma% only available in GNAT mode");
12569             end if;
12570
12571             if Nkind (N) = N_Null_Statement then
12572                return;
12573             end if;
12574
12575             --  This is one of the few cases where we need to test the value of
12576             --  Ada_Version_Explicit rather than Ada_Version (which is always
12577             --  set to Ada_2012 in a predefined unit), we need to know the
12578             --  explicit version set to know if this pragma is active.
12579
12580             if Ada_Version_Explicit >= Ada_2005 then
12581                Ent := Find_Lib_Unit_Name;
12582                Set_Is_Preelaborated (Ent, False);
12583                Set_Is_Pure (Ent);
12584                Set_Suppress_Elaboration_Warnings (Ent);
12585             end if;
12586          end Pure_05;
12587
12588          -------------------
12589          -- Pure_Function --
12590          -------------------
12591
12592          --  pragma Pure_Function ([Entity =>] function_LOCAL_NAME);
12593
12594          when Pragma_Pure_Function => Pure_Function : declare
12595             E_Id      : Node_Id;
12596             E         : Entity_Id;
12597             Def_Id    : Entity_Id;
12598             Effective : Boolean := False;
12599
12600          begin
12601             GNAT_Pragma;
12602             Check_Arg_Count (1);
12603             Check_Optional_Identifier (Arg1, Name_Entity);
12604             Check_Arg_Is_Local_Name (Arg1);
12605             E_Id := Get_Pragma_Arg (Arg1);
12606
12607             if Error_Posted (E_Id) then
12608                return;
12609             end if;
12610
12611             --  Loop through homonyms (overloadings) of referenced entity
12612
12613             E := Entity (E_Id);
12614
12615             if Present (E) then
12616                loop
12617                   Def_Id := Get_Base_Subprogram (E);
12618
12619                   if not Ekind_In (Def_Id, E_Function,
12620                                            E_Generic_Function,
12621                                            E_Operator)
12622                   then
12623                      Error_Pragma_Arg
12624                        ("pragma% requires a function name", Arg1);
12625                   end if;
12626
12627                   Set_Is_Pure (Def_Id);
12628
12629                   if not Has_Pragma_Pure_Function (Def_Id) then
12630                      Set_Has_Pragma_Pure_Function (Def_Id);
12631                      Effective := True;
12632                   end if;
12633
12634                   exit when From_Aspect_Specification (N);
12635                   E := Homonym (E);
12636                   exit when No (E) or else Scope (E) /= Current_Scope;
12637                end loop;
12638
12639                if not Effective
12640                  and then Warn_On_Redundant_Constructs
12641                then
12642                   Error_Msg_NE
12643                     ("pragma Pure_Function on& is redundant?",
12644                      N, Entity (E_Id));
12645                end if;
12646             end if;
12647          end Pure_Function;
12648
12649          --------------------
12650          -- Queuing_Policy --
12651          --------------------
12652
12653          --  pragma Queuing_Policy (policy_IDENTIFIER);
12654
12655          when Pragma_Queuing_Policy => declare
12656             QP : Character;
12657
12658          begin
12659             Check_Ada_83_Warning;
12660             Check_Arg_Count (1);
12661             Check_No_Identifiers;
12662             Check_Arg_Is_Queuing_Policy (Arg1);
12663             Check_Valid_Configuration_Pragma;
12664             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
12665             QP := Fold_Upper (Name_Buffer (1));
12666
12667             if Queuing_Policy /= ' '
12668               and then Queuing_Policy /= QP
12669             then
12670                Error_Msg_Sloc := Queuing_Policy_Sloc;
12671                Error_Pragma ("queuing policy incompatible with policy#");
12672
12673             --  Set new policy, but always preserve System_Location since we
12674             --  like the error message with the run time name.
12675
12676             else
12677                Queuing_Policy := QP;
12678
12679                if Queuing_Policy_Sloc /= System_Location then
12680                   Queuing_Policy_Sloc := Loc;
12681                end if;
12682             end if;
12683          end;
12684
12685          -----------------------
12686          -- Relative_Deadline --
12687          -----------------------
12688
12689          --  pragma Relative_Deadline (time_span_EXPRESSION);
12690
12691          when Pragma_Relative_Deadline => Relative_Deadline : declare
12692             P   : constant Node_Id := Parent (N);
12693             Arg : Node_Id;
12694
12695          begin
12696             Ada_2005_Pragma;
12697             Check_No_Identifiers;
12698             Check_Arg_Count (1);
12699
12700             Arg := Get_Pragma_Arg (Arg1);
12701
12702             --  The expression must be analyzed in the special manner described
12703             --  in "Handling of Default and Per-Object Expressions" in sem.ads.
12704
12705             Preanalyze_Spec_Expression (Arg, RTE (RE_Time_Span));
12706
12707             --  Subprogram case
12708
12709             if Nkind (P) = N_Subprogram_Body then
12710                Check_In_Main_Program;
12711
12712             --  Tasks
12713
12714             elsif Nkind (P) = N_Task_Definition then
12715                null;
12716
12717             --  Anything else is incorrect
12718
12719             else
12720                Pragma_Misplaced;
12721             end if;
12722
12723             if Has_Relative_Deadline_Pragma (P) then
12724                Error_Pragma ("duplicate pragma% not allowed");
12725             else
12726                Set_Has_Relative_Deadline_Pragma (P, True);
12727
12728                if Nkind (P) = N_Task_Definition then
12729                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
12730                end if;
12731             end if;
12732          end Relative_Deadline;
12733
12734          ---------------------------
12735          -- Remote_Call_Interface --
12736          ---------------------------
12737
12738          --  pragma Remote_Call_Interface [(library_unit_NAME)];
12739
12740          when Pragma_Remote_Call_Interface => Remote_Call_Interface : declare
12741             Cunit_Node : Node_Id;
12742             Cunit_Ent  : Entity_Id;
12743             K          : Node_Kind;
12744
12745          begin
12746             Check_Ada_83_Warning;
12747             Check_Valid_Library_Unit_Pragma;
12748
12749             if Nkind (N) = N_Null_Statement then
12750                return;
12751             end if;
12752
12753             Cunit_Node := Cunit (Current_Sem_Unit);
12754             K          := Nkind (Unit (Cunit_Node));
12755             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12756
12757             if K = N_Package_Declaration
12758               or else K = N_Generic_Package_Declaration
12759               or else K = N_Subprogram_Declaration
12760               or else K = N_Generic_Subprogram_Declaration
12761               or else (K = N_Subprogram_Body
12762                          and then Acts_As_Spec (Unit (Cunit_Node)))
12763             then
12764                null;
12765             else
12766                Error_Pragma (
12767                  "pragma% must apply to package or subprogram declaration");
12768             end if;
12769
12770             Set_Is_Remote_Call_Interface (Cunit_Ent);
12771          end Remote_Call_Interface;
12772
12773          ------------------
12774          -- Remote_Types --
12775          ------------------
12776
12777          --  pragma Remote_Types [(library_unit_NAME)];
12778
12779          when Pragma_Remote_Types => Remote_Types : declare
12780             Cunit_Node : Node_Id;
12781             Cunit_Ent  : Entity_Id;
12782
12783          begin
12784             Check_Ada_83_Warning;
12785             Check_Valid_Library_Unit_Pragma;
12786
12787             if Nkind (N) = N_Null_Statement then
12788                return;
12789             end if;
12790
12791             Cunit_Node := Cunit (Current_Sem_Unit);
12792             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12793
12794             if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
12795                                                 N_Generic_Package_Declaration)
12796             then
12797                Error_Pragma
12798                  ("pragma% can only apply to a package declaration");
12799             end if;
12800
12801             Set_Is_Remote_Types (Cunit_Ent);
12802          end Remote_Types;
12803
12804          ---------------
12805          -- Ravenscar --
12806          ---------------
12807
12808          --  pragma Ravenscar;
12809
12810          when Pragma_Ravenscar =>
12811             GNAT_Pragma;
12812             Check_Arg_Count (0);
12813             Check_Valid_Configuration_Pragma;
12814             Set_Ravenscar_Profile (N);
12815
12816             if Warn_On_Obsolescent_Feature then
12817                Error_Msg_N ("pragma Ravenscar is an obsolescent feature?", N);
12818                Error_Msg_N ("|use pragma Profile (Ravenscar) instead", N);
12819             end if;
12820
12821          -------------------------
12822          -- Restricted_Run_Time --
12823          -------------------------
12824
12825          --  pragma Restricted_Run_Time;
12826
12827          when Pragma_Restricted_Run_Time =>
12828             GNAT_Pragma;
12829             Check_Arg_Count (0);
12830             Check_Valid_Configuration_Pragma;
12831             Set_Profile_Restrictions
12832               (Restricted, N, Warn => Treat_Restrictions_As_Warnings);
12833
12834             if Warn_On_Obsolescent_Feature then
12835                Error_Msg_N
12836                  ("pragma Restricted_Run_Time is an obsolescent feature?", N);
12837                Error_Msg_N ("|use pragma Profile (Restricted) instead", N);
12838             end if;
12839
12840          ------------------
12841          -- Restrictions --
12842          ------------------
12843
12844          --  pragma Restrictions (RESTRICTION {, RESTRICTION});
12845
12846          --  RESTRICTION ::=
12847          --    restriction_IDENTIFIER
12848          --  | restriction_parameter_IDENTIFIER => EXPRESSION
12849
12850          when Pragma_Restrictions =>
12851             Process_Restrictions_Or_Restriction_Warnings
12852               (Warn => Treat_Restrictions_As_Warnings);
12853
12854          --------------------------
12855          -- Restriction_Warnings --
12856          --------------------------
12857
12858          --  pragma Restriction_Warnings (RESTRICTION {, RESTRICTION});
12859
12860          --  RESTRICTION ::=
12861          --    restriction_IDENTIFIER
12862          --  | restriction_parameter_IDENTIFIER => EXPRESSION
12863
12864          when Pragma_Restriction_Warnings =>
12865             GNAT_Pragma;
12866             Process_Restrictions_Or_Restriction_Warnings (Warn => True);
12867
12868          ----------------
12869          -- Reviewable --
12870          ----------------
12871
12872          --  pragma Reviewable;
12873
12874          when Pragma_Reviewable =>
12875             Check_Ada_83_Warning;
12876             Check_Arg_Count (0);
12877
12878             --  Call dummy debugging function rv. This is done to assist front
12879             --  end debugging. By placing a Reviewable pragma in the source
12880             --  program, a breakpoint on rv catches this place in the source,
12881             --  allowing convenient stepping to the point of interest.
12882
12883             rv;
12884
12885          --------------------------
12886          -- Short_Circuit_And_Or --
12887          --------------------------
12888
12889          when Pragma_Short_Circuit_And_Or =>
12890             GNAT_Pragma;
12891             Check_Arg_Count (0);
12892             Check_Valid_Configuration_Pragma;
12893             Short_Circuit_And_Or := True;
12894
12895          -------------------
12896          -- Share_Generic --
12897          -------------------
12898
12899          --  pragma Share_Generic (NAME {, NAME});
12900
12901          when Pragma_Share_Generic =>
12902             GNAT_Pragma;
12903             Process_Generic_List;
12904
12905          ------------
12906          -- Shared --
12907          ------------
12908
12909          --  pragma Shared (LOCAL_NAME);
12910
12911          when Pragma_Shared =>
12912             GNAT_Pragma;
12913             Process_Atomic_Shared_Volatile;
12914
12915          --------------------
12916          -- Shared_Passive --
12917          --------------------
12918
12919          --  pragma Shared_Passive [(library_unit_NAME)];
12920
12921          --  Set the flag Is_Shared_Passive of program unit name entity
12922
12923          when Pragma_Shared_Passive => Shared_Passive : declare
12924             Cunit_Node : Node_Id;
12925             Cunit_Ent  : Entity_Id;
12926
12927          begin
12928             Check_Ada_83_Warning;
12929             Check_Valid_Library_Unit_Pragma;
12930
12931             if Nkind (N) = N_Null_Statement then
12932                return;
12933             end if;
12934
12935             Cunit_Node := Cunit (Current_Sem_Unit);
12936             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12937
12938             if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
12939                                                 N_Generic_Package_Declaration)
12940             then
12941                Error_Pragma
12942                  ("pragma% can only apply to a package declaration");
12943             end if;
12944
12945             Set_Is_Shared_Passive (Cunit_Ent);
12946          end Shared_Passive;
12947
12948          -----------------------
12949          -- Short_Descriptors --
12950          -----------------------
12951
12952          --  pragma Short_Descriptors;
12953
12954          when Pragma_Short_Descriptors =>
12955             GNAT_Pragma;
12956             Check_Arg_Count (0);
12957             Check_Valid_Configuration_Pragma;
12958             Short_Descriptors := True;
12959
12960          ----------------------
12961          -- Source_File_Name --
12962          ----------------------
12963
12964          --  There are five forms for this pragma:
12965
12966          --  pragma Source_File_Name (
12967          --    [UNIT_NAME      =>] unit_NAME,
12968          --     BODY_FILE_NAME =>  STRING_LITERAL
12969          --    [, [INDEX =>] INTEGER_LITERAL]);
12970
12971          --  pragma Source_File_Name (
12972          --    [UNIT_NAME      =>] unit_NAME,
12973          --     SPEC_FILE_NAME =>  STRING_LITERAL
12974          --    [, [INDEX =>] INTEGER_LITERAL]);
12975
12976          --  pragma Source_File_Name (
12977          --     BODY_FILE_NAME  => STRING_LITERAL
12978          --  [, DOT_REPLACEMENT => STRING_LITERAL]
12979          --  [, CASING          => CASING_SPEC]);
12980
12981          --  pragma Source_File_Name (
12982          --     SPEC_FILE_NAME  => STRING_LITERAL
12983          --  [, DOT_REPLACEMENT => STRING_LITERAL]
12984          --  [, CASING          => CASING_SPEC]);
12985
12986          --  pragma Source_File_Name (
12987          --     SUBUNIT_FILE_NAME  => STRING_LITERAL
12988          --  [, DOT_REPLACEMENT    => STRING_LITERAL]
12989          --  [, CASING             => CASING_SPEC]);
12990
12991          --  CASING_SPEC ::= Uppercase | Lowercase | Mixedcase
12992
12993          --  Pragma Source_File_Name_Project (SFNP) is equivalent to pragma
12994          --  Source_File_Name (SFN), however their usage is exclusive: SFN can
12995          --  only be used when no project file is used, while SFNP can only be
12996          --  used when a project file is used.
12997
12998          --  No processing here. Processing was completed during parsing, since
12999          --  we need to have file names set as early as possible. Units are
13000          --  loaded well before semantic processing starts.
13001
13002          --  The only processing we defer to this point is the check for
13003          --  correct placement.
13004
13005          when Pragma_Source_File_Name =>
13006             GNAT_Pragma;
13007             Check_Valid_Configuration_Pragma;
13008
13009          ------------------------------
13010          -- Source_File_Name_Project --
13011          ------------------------------
13012
13013          --  See Source_File_Name for syntax
13014
13015          --  No processing here. Processing was completed during parsing, since
13016          --  we need to have file names set as early as possible. Units are
13017          --  loaded well before semantic processing starts.
13018
13019          --  The only processing we defer to this point is the check for
13020          --  correct placement.
13021
13022          when Pragma_Source_File_Name_Project =>
13023             GNAT_Pragma;
13024             Check_Valid_Configuration_Pragma;
13025
13026             --  Check that a pragma Source_File_Name_Project is used only in a
13027             --  configuration pragmas file.
13028
13029             --  Pragmas Source_File_Name_Project should only be generated by
13030             --  the Project Manager in configuration pragmas files.
13031
13032             --  This is really an ugly test. It seems to depend on some
13033             --  accidental and undocumented property. At the very least it
13034             --  needs to be documented, but it would be better to have a
13035             --  clean way of testing if we are in a configuration file???
13036
13037             if Present (Parent (N)) then
13038                Error_Pragma
13039                  ("pragma% can only appear in a configuration pragmas file");
13040             end if;
13041
13042          ----------------------
13043          -- Source_Reference --
13044          ----------------------
13045
13046          --  pragma Source_Reference (INTEGER_LITERAL [, STRING_LITERAL]);
13047
13048          --  Nothing to do, all processing completed in Par.Prag, since we need
13049          --  the information for possible parser messages that are output.
13050
13051          when Pragma_Source_Reference =>
13052             GNAT_Pragma;
13053
13054          --------------------------------
13055          -- Static_Elaboration_Desired --
13056          --------------------------------
13057
13058          --  pragma Static_Elaboration_Desired (DIRECT_NAME);
13059
13060          when Pragma_Static_Elaboration_Desired =>
13061             GNAT_Pragma;
13062             Check_At_Most_N_Arguments (1);
13063
13064             if Is_Compilation_Unit (Current_Scope)
13065               and then Ekind (Current_Scope) = E_Package
13066             then
13067                Set_Static_Elaboration_Desired (Current_Scope, True);
13068             else
13069                Error_Pragma ("pragma% must apply to a library-level package");
13070             end if;
13071
13072          ------------------
13073          -- Storage_Size --
13074          ------------------
13075
13076          --  pragma Storage_Size (EXPRESSION);
13077
13078          when Pragma_Storage_Size => Storage_Size : declare
13079             P   : constant Node_Id := Parent (N);
13080             Arg : Node_Id;
13081
13082          begin
13083             Check_No_Identifiers;
13084             Check_Arg_Count (1);
13085
13086             --  The expression must be analyzed in the special manner described
13087             --  in "Handling of Default Expressions" in sem.ads.
13088
13089             Arg := Get_Pragma_Arg (Arg1);
13090             Preanalyze_Spec_Expression (Arg, Any_Integer);
13091
13092             if not Is_Static_Expression (Arg) then
13093                Check_Restriction (Static_Storage_Size, Arg);
13094             end if;
13095
13096             if Nkind (P) /= N_Task_Definition then
13097                Pragma_Misplaced;
13098                return;
13099
13100             else
13101                if Has_Storage_Size_Pragma (P) then
13102                   Error_Pragma ("duplicate pragma% not allowed");
13103                else
13104                   Set_Has_Storage_Size_Pragma (P, True);
13105                end if;
13106
13107                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
13108                --  ???  exp_ch9 should use this!
13109             end if;
13110          end Storage_Size;
13111
13112          ------------------
13113          -- Storage_Unit --
13114          ------------------
13115
13116          --  pragma Storage_Unit (NUMERIC_LITERAL);
13117
13118          --  Only permitted argument is System'Storage_Unit value
13119
13120          when Pragma_Storage_Unit =>
13121             Check_No_Identifiers;
13122             Check_Arg_Count (1);
13123             Check_Arg_Is_Integer_Literal (Arg1);
13124
13125             if Intval (Get_Pragma_Arg (Arg1)) /=
13126               UI_From_Int (Ttypes.System_Storage_Unit)
13127             then
13128                Error_Msg_Uint_1 := UI_From_Int (Ttypes.System_Storage_Unit);
13129                Error_Pragma_Arg
13130                  ("the only allowed argument for pragma% is ^", Arg1);
13131             end if;
13132
13133          --------------------
13134          -- Stream_Convert --
13135          --------------------
13136
13137          --  pragma Stream_Convert (
13138          --    [Entity =>] type_LOCAL_NAME,
13139          --    [Read   =>] function_NAME,
13140          --    [Write  =>] function NAME);
13141
13142          when Pragma_Stream_Convert => Stream_Convert : declare
13143
13144             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id);
13145             --  Check that the given argument is the name of a local function
13146             --  of one argument that is not overloaded earlier in the current
13147             --  local scope. A check is also made that the argument is a
13148             --  function with one parameter.
13149
13150             --------------------------------------
13151             -- Check_OK_Stream_Convert_Function --
13152             --------------------------------------
13153
13154             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id) is
13155                Ent : Entity_Id;
13156
13157             begin
13158                Check_Arg_Is_Local_Name (Arg);
13159                Ent := Entity (Get_Pragma_Arg (Arg));
13160
13161                if Has_Homonym (Ent) then
13162                   Error_Pragma_Arg
13163                     ("argument for pragma% may not be overloaded", Arg);
13164                end if;
13165
13166                if Ekind (Ent) /= E_Function
13167                  or else No (First_Formal (Ent))
13168                  or else Present (Next_Formal (First_Formal (Ent)))
13169                then
13170                   Error_Pragma_Arg
13171                     ("argument for pragma% must be" &
13172                      " function of one argument", Arg);
13173                end if;
13174             end Check_OK_Stream_Convert_Function;
13175
13176          --  Start of processing for Stream_Convert
13177
13178          begin
13179             GNAT_Pragma;
13180             Check_Arg_Order ((Name_Entity, Name_Read, Name_Write));
13181             Check_Arg_Count (3);
13182             Check_Optional_Identifier (Arg1, Name_Entity);
13183             Check_Optional_Identifier (Arg2, Name_Read);
13184             Check_Optional_Identifier (Arg3, Name_Write);
13185             Check_Arg_Is_Local_Name (Arg1);
13186             Check_OK_Stream_Convert_Function (Arg2);
13187             Check_OK_Stream_Convert_Function (Arg3);
13188
13189             declare
13190                Typ   : constant Entity_Id :=
13191                          Underlying_Type (Entity (Get_Pragma_Arg (Arg1)));
13192                Read  : constant Entity_Id := Entity (Get_Pragma_Arg (Arg2));
13193                Write : constant Entity_Id := Entity (Get_Pragma_Arg (Arg3));
13194
13195             begin
13196                Check_First_Subtype (Arg1);
13197
13198                --  Check for too early or too late. Note that we don't enforce
13199                --  the rule about primitive operations in this case, since, as
13200                --  is the case for explicit stream attributes themselves, these
13201                --  restrictions are not appropriate. Note that the chaining of
13202                --  the pragma by Rep_Item_Too_Late is actually the critical
13203                --  processing done for this pragma.
13204
13205                if Rep_Item_Too_Early (Typ, N)
13206                     or else
13207                   Rep_Item_Too_Late (Typ, N, FOnly => True)
13208                then
13209                   return;
13210                end if;
13211
13212                --  Return if previous error
13213
13214                if Etype (Typ) = Any_Type
13215                     or else
13216                   Etype (Read) = Any_Type
13217                     or else
13218                   Etype (Write) = Any_Type
13219                then
13220                   return;
13221                end if;
13222
13223                --  Error checks
13224
13225                if Underlying_Type (Etype (Read)) /= Typ then
13226                   Error_Pragma_Arg
13227                     ("incorrect return type for function&", Arg2);
13228                end if;
13229
13230                if Underlying_Type (Etype (First_Formal (Write))) /= Typ then
13231                   Error_Pragma_Arg
13232                     ("incorrect parameter type for function&", Arg3);
13233                end if;
13234
13235                if Underlying_Type (Etype (First_Formal (Read))) /=
13236                   Underlying_Type (Etype (Write))
13237                then
13238                   Error_Pragma_Arg
13239                     ("result type of & does not match Read parameter type",
13240                      Arg3);
13241                end if;
13242             end;
13243          end Stream_Convert;
13244
13245          -------------------------
13246          -- Style_Checks (GNAT) --
13247          -------------------------
13248
13249          --  pragma Style_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
13250
13251          --  This is processed by the parser since some of the style checks
13252          --  take place during source scanning and parsing. This means that
13253          --  we don't need to issue error messages here.
13254
13255          when Pragma_Style_Checks => Style_Checks : declare
13256             A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
13257             S  : String_Id;
13258             C  : Char_Code;
13259
13260          begin
13261             GNAT_Pragma;
13262             Check_No_Identifiers;
13263
13264             --  Two argument form
13265
13266             if Arg_Count = 2 then
13267                Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
13268
13269                declare
13270                   E_Id : Node_Id;
13271                   E    : Entity_Id;
13272
13273                begin
13274                   E_Id := Get_Pragma_Arg (Arg2);
13275                   Analyze (E_Id);
13276
13277                   if not Is_Entity_Name (E_Id) then
13278                      Error_Pragma_Arg
13279                        ("second argument of pragma% must be entity name",
13280                         Arg2);
13281                   end if;
13282
13283                   E := Entity (E_Id);
13284
13285                   if E = Any_Id then
13286                      return;
13287                   else
13288                      loop
13289                         Set_Suppress_Style_Checks (E,
13290                           (Chars (Get_Pragma_Arg (Arg1)) = Name_Off));
13291                         exit when No (Homonym (E));
13292                         E := Homonym (E);
13293                      end loop;
13294                   end if;
13295                end;
13296
13297             --  One argument form
13298
13299             else
13300                Check_Arg_Count (1);
13301
13302                if Nkind (A) = N_String_Literal then
13303                   S   := Strval (A);
13304
13305                   declare
13306                      Slen    : constant Natural := Natural (String_Length (S));
13307                      Options : String (1 .. Slen);
13308                      J       : Natural;
13309
13310                   begin
13311                      J := 1;
13312                      loop
13313                         C := Get_String_Char (S, Int (J));
13314                         exit when not In_Character_Range (C);
13315                         Options (J) := Get_Character (C);
13316
13317                         --  If at end of string, set options. As per discussion
13318                         --  above, no need to check for errors, since we issued
13319                         --  them in the parser.
13320
13321                         if J = Slen then
13322                            Set_Style_Check_Options (Options);
13323                            exit;
13324                         end if;
13325
13326                         J := J + 1;
13327                      end loop;
13328                   end;
13329
13330                elsif Nkind (A) = N_Identifier then
13331                   if Chars (A) = Name_All_Checks then
13332                      if GNAT_Mode then
13333                         Set_GNAT_Style_Check_Options;
13334                      else
13335                         Set_Default_Style_Check_Options;
13336                      end if;
13337
13338                   elsif Chars (A) = Name_On then
13339                      Style_Check := True;
13340
13341                   elsif Chars (A) = Name_Off then
13342                      Style_Check := False;
13343                   end if;
13344                end if;
13345             end if;
13346          end Style_Checks;
13347
13348          --------------
13349          -- Subtitle --
13350          --------------
13351
13352          --  pragma Subtitle ([Subtitle =>] STRING_LITERAL);
13353
13354          when Pragma_Subtitle =>
13355             GNAT_Pragma;
13356             Check_Arg_Count (1);
13357             Check_Optional_Identifier (Arg1, Name_Subtitle);
13358             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
13359             Store_Note (N);
13360
13361          --------------
13362          -- Suppress --
13363          --------------
13364
13365          --  pragma Suppress (IDENTIFIER [, [On =>] NAME]);
13366
13367          when Pragma_Suppress =>
13368             Process_Suppress_Unsuppress (True);
13369
13370          ------------------
13371          -- Suppress_All --
13372          ------------------
13373
13374          --  pragma Suppress_All;
13375
13376          --  The only check made here is that the pragma has no arguments.
13377          --  There are no placement rules, and the processing required (setting
13378          --  the Has_Pragma_Suppress_All flag in the compilation unit node was
13379          --  taken care of by the parser). Process_Compilation_Unit_Pragmas
13380          --  then creates and inserts a pragma Suppress (All_Checks).
13381
13382          when Pragma_Suppress_All =>
13383             GNAT_Pragma;
13384             Check_Arg_Count (0);
13385
13386          -------------------------
13387          -- Suppress_Debug_Info --
13388          -------------------------
13389
13390          --  pragma Suppress_Debug_Info ([Entity =>] LOCAL_NAME);
13391
13392          when Pragma_Suppress_Debug_Info =>
13393             GNAT_Pragma;
13394             Check_Arg_Count (1);
13395             Check_Optional_Identifier (Arg1, Name_Entity);
13396             Check_Arg_Is_Local_Name (Arg1);
13397             Set_Debug_Info_Off (Entity (Get_Pragma_Arg (Arg1)));
13398
13399          ----------------------------------
13400          -- Suppress_Exception_Locations --
13401          ----------------------------------
13402
13403          --  pragma Suppress_Exception_Locations;
13404
13405          when Pragma_Suppress_Exception_Locations =>
13406             GNAT_Pragma;
13407             Check_Arg_Count (0);
13408             Check_Valid_Configuration_Pragma;
13409             Exception_Locations_Suppressed := True;
13410
13411          -----------------------------
13412          -- Suppress_Initialization --
13413          -----------------------------
13414
13415          --  pragma Suppress_Initialization ([Entity =>] type_Name);
13416
13417          when Pragma_Suppress_Initialization => Suppress_Init : declare
13418             E_Id : Node_Id;
13419             E    : Entity_Id;
13420
13421          begin
13422             GNAT_Pragma;
13423             Check_Arg_Count (1);
13424             Check_Optional_Identifier (Arg1, Name_Entity);
13425             Check_Arg_Is_Local_Name (Arg1);
13426
13427             E_Id := Get_Pragma_Arg (Arg1);
13428
13429             if Etype (E_Id) = Any_Type then
13430                return;
13431             end if;
13432
13433             E := Entity (E_Id);
13434
13435             if not Is_Type (E) then
13436                Error_Pragma_Arg ("pragma% requires type or subtype", Arg1);
13437             end if;
13438
13439             if Rep_Item_Too_Early (E, N)
13440                  or else
13441                Rep_Item_Too_Late (E, N, FOnly => True)
13442             then
13443                return;
13444             end if;
13445
13446             --  For incomplete/private type, set flag on full view
13447
13448             if Is_Incomplete_Or_Private_Type (E) then
13449                if No (Full_View (Base_Type (E))) then
13450                   Error_Pragma_Arg
13451                     ("argument of pragma% cannot be an incomplete type", Arg1);
13452                else
13453                   Set_Suppress_Initialization (Full_View (Base_Type (E)));
13454                end if;
13455
13456             --  For first subtype, set flag on base type
13457
13458             elsif Is_First_Subtype (E) then
13459                Set_Suppress_Initialization (Base_Type (E));
13460
13461             --  For other than first subtype, set flag on subtype itself
13462
13463             else
13464                Set_Suppress_Initialization (E);
13465             end if;
13466          end Suppress_Init;
13467
13468          -----------------
13469          -- System_Name --
13470          -----------------
13471
13472          --  pragma System_Name (DIRECT_NAME);
13473
13474          --  Syntax check: one argument, which must be the identifier GNAT or
13475          --  the identifier GCC, no other identifiers are acceptable.
13476
13477          when Pragma_System_Name =>
13478             GNAT_Pragma;
13479             Check_No_Identifiers;
13480             Check_Arg_Count (1);
13481             Check_Arg_Is_One_Of (Arg1, Name_Gcc, Name_Gnat);
13482
13483          -----------------------------
13484          -- Task_Dispatching_Policy --
13485          -----------------------------
13486
13487          --  pragma Task_Dispatching_Policy (policy_IDENTIFIER);
13488
13489          when Pragma_Task_Dispatching_Policy => declare
13490             DP : Character;
13491
13492          begin
13493             Check_Ada_83_Warning;
13494             Check_Arg_Count (1);
13495             Check_No_Identifiers;
13496             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
13497             Check_Valid_Configuration_Pragma;
13498             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
13499             DP := Fold_Upper (Name_Buffer (1));
13500
13501             if Task_Dispatching_Policy /= ' '
13502               and then Task_Dispatching_Policy /= DP
13503             then
13504                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
13505                Error_Pragma
13506                  ("task dispatching policy incompatible with policy#");
13507
13508             --  Set new policy, but always preserve System_Location since we
13509             --  like the error message with the run time name.
13510
13511             else
13512                Task_Dispatching_Policy := DP;
13513
13514                if Task_Dispatching_Policy_Sloc /= System_Location then
13515                   Task_Dispatching_Policy_Sloc := Loc;
13516                end if;
13517             end if;
13518          end;
13519
13520          ---------------
13521          -- Task_Info --
13522          ---------------
13523
13524          --  pragma Task_Info (EXPRESSION);
13525
13526          when Pragma_Task_Info => Task_Info : declare
13527             P : constant Node_Id := Parent (N);
13528
13529          begin
13530             GNAT_Pragma;
13531
13532             if Nkind (P) /= N_Task_Definition then
13533                Error_Pragma ("pragma% must appear in task definition");
13534             end if;
13535
13536             Check_No_Identifiers;
13537             Check_Arg_Count (1);
13538
13539             Analyze_And_Resolve
13540               (Get_Pragma_Arg (Arg1), RTE (RE_Task_Info_Type));
13541
13542             if Etype (Get_Pragma_Arg (Arg1)) = Any_Type then
13543                return;
13544             end if;
13545
13546             if Has_Task_Info_Pragma (P) then
13547                Error_Pragma ("duplicate pragma% not allowed");
13548             else
13549                Set_Has_Task_Info_Pragma (P, True);
13550             end if;
13551          end Task_Info;
13552
13553          ---------------
13554          -- Task_Name --
13555          ---------------
13556
13557          --  pragma Task_Name (string_EXPRESSION);
13558
13559          when Pragma_Task_Name => Task_Name : declare
13560             P   : constant Node_Id := Parent (N);
13561             Arg : Node_Id;
13562
13563          begin
13564             Check_No_Identifiers;
13565             Check_Arg_Count (1);
13566
13567             Arg := Get_Pragma_Arg (Arg1);
13568
13569             --  The expression is used in the call to Create_Task, and must be
13570             --  expanded there, not in the context of the current spec. It must
13571             --  however be analyzed to capture global references, in case it
13572             --  appears in a generic context.
13573
13574             Preanalyze_And_Resolve (Arg, Standard_String);
13575
13576             if Nkind (P) /= N_Task_Definition then
13577                Pragma_Misplaced;
13578             end if;
13579
13580             if Has_Task_Name_Pragma (P) then
13581                Error_Pragma ("duplicate pragma% not allowed");
13582             else
13583                Set_Has_Task_Name_Pragma (P, True);
13584                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
13585             end if;
13586          end Task_Name;
13587
13588          ------------------
13589          -- Task_Storage --
13590          ------------------
13591
13592          --  pragma Task_Storage (
13593          --     [Task_Type =>] LOCAL_NAME,
13594          --     [Top_Guard =>] static_integer_EXPRESSION);
13595
13596          when Pragma_Task_Storage => Task_Storage : declare
13597             Args  : Args_List (1 .. 2);
13598             Names : constant Name_List (1 .. 2) := (
13599                       Name_Task_Type,
13600                       Name_Top_Guard);
13601
13602             Task_Type : Node_Id renames Args (1);
13603             Top_Guard : Node_Id renames Args (2);
13604
13605             Ent : Entity_Id;
13606
13607          begin
13608             GNAT_Pragma;
13609             Gather_Associations (Names, Args);
13610
13611             if No (Task_Type) then
13612                Error_Pragma
13613                  ("missing task_type argument for pragma%");
13614             end if;
13615
13616             Check_Arg_Is_Local_Name (Task_Type);
13617
13618             Ent := Entity (Task_Type);
13619
13620             if not Is_Task_Type (Ent) then
13621                Error_Pragma_Arg
13622                  ("argument for pragma% must be task type", Task_Type);
13623             end if;
13624
13625             if No (Top_Guard) then
13626                Error_Pragma_Arg
13627                  ("pragma% takes two arguments", Task_Type);
13628             else
13629                Check_Arg_Is_Static_Expression (Top_Guard, Any_Integer);
13630             end if;
13631
13632             Check_First_Subtype (Task_Type);
13633
13634             if Rep_Item_Too_Late (Ent, N) then
13635                raise Pragma_Exit;
13636             end if;
13637          end Task_Storage;
13638
13639          ---------------
13640          -- Test_Case --
13641          ---------------
13642
13643          --  pragma Test_Case ([Name     =>] Static_String_EXPRESSION
13644          --                   ,[Mode     =>] MODE_TYPE
13645          --                  [, Requires =>  Boolean_EXPRESSION]
13646          --                  [, Ensures  =>  Boolean_EXPRESSION]);
13647
13648          --  MODE_TYPE ::= Nominal | Robustness
13649
13650          when Pragma_Test_Case => Test_Case : declare
13651          begin
13652             GNAT_Pragma;
13653             Check_At_Least_N_Arguments (2);
13654             Check_At_Most_N_Arguments (4);
13655             Check_Arg_Order
13656                  ((Name_Name, Name_Mode, Name_Requires, Name_Ensures));
13657
13658             Check_Optional_Identifier (Arg1, Name_Name);
13659             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
13660             Check_Optional_Identifier (Arg2, Name_Mode);
13661             Check_Arg_Is_One_Of (Arg2, Name_Nominal, Name_Robustness);
13662
13663             if Arg_Count = 4 then
13664                Check_Identifier (Arg3, Name_Requires);
13665                Check_Identifier (Arg4, Name_Ensures);
13666
13667             elsif Arg_Count = 3 then
13668                Check_Identifier_Is_One_Of (Arg3, Name_Requires, Name_Ensures);
13669             end if;
13670
13671             Check_Test_Case;
13672          end Test_Case;
13673
13674          --------------------------
13675          -- Thread_Local_Storage --
13676          --------------------------
13677
13678          --  pragma Thread_Local_Storage ([Entity =>] LOCAL_NAME);
13679
13680          when Pragma_Thread_Local_Storage => Thread_Local_Storage : declare
13681             Id : Node_Id;
13682             E  : Entity_Id;
13683
13684          begin
13685             GNAT_Pragma;
13686             Check_Arg_Count (1);
13687             Check_Optional_Identifier (Arg1, Name_Entity);
13688             Check_Arg_Is_Library_Level_Local_Name (Arg1);
13689
13690             Id := Get_Pragma_Arg (Arg1);
13691             Analyze (Id);
13692
13693             if not Is_Entity_Name (Id)
13694               or else Ekind (Entity (Id)) /= E_Variable
13695             then
13696                Error_Pragma_Arg ("local variable name required", Arg1);
13697             end if;
13698
13699             E := Entity (Id);
13700
13701             if Rep_Item_Too_Early (E, N)
13702               or else Rep_Item_Too_Late (E, N)
13703             then
13704                raise Pragma_Exit;
13705             end if;
13706
13707             Set_Has_Pragma_Thread_Local_Storage (E);
13708             Set_Has_Gigi_Rep_Item (E);
13709          end Thread_Local_Storage;
13710
13711          ----------------
13712          -- Time_Slice --
13713          ----------------
13714
13715          --  pragma Time_Slice (static_duration_EXPRESSION);
13716
13717          when Pragma_Time_Slice => Time_Slice : declare
13718             Val : Ureal;
13719             Nod : Node_Id;
13720
13721          begin
13722             GNAT_Pragma;
13723             Check_Arg_Count (1);
13724             Check_No_Identifiers;
13725             Check_In_Main_Program;
13726             Check_Arg_Is_Static_Expression (Arg1, Standard_Duration);
13727
13728             if not Error_Posted (Arg1) then
13729                Nod := Next (N);
13730                while Present (Nod) loop
13731                   if Nkind (Nod) = N_Pragma
13732                     and then Pragma_Name (Nod) = Name_Time_Slice
13733                   then
13734                      Error_Msg_Name_1 := Pname;
13735                      Error_Msg_N ("duplicate pragma% not permitted", Nod);
13736                   end if;
13737
13738                   Next (Nod);
13739                end loop;
13740             end if;
13741
13742             --  Process only if in main unit
13743
13744             if Get_Source_Unit (Loc) = Main_Unit then
13745                Opt.Time_Slice_Set := True;
13746                Val := Expr_Value_R (Get_Pragma_Arg (Arg1));
13747
13748                if Val <= Ureal_0 then
13749                   Opt.Time_Slice_Value := 0;
13750
13751                elsif Val > UR_From_Uint (UI_From_Int (1000)) then
13752                   Opt.Time_Slice_Value := 1_000_000_000;
13753
13754                else
13755                   Opt.Time_Slice_Value :=
13756                     UI_To_Int (UR_To_Uint (Val * UI_From_Int (1_000_000)));
13757                end if;
13758             end if;
13759          end Time_Slice;
13760
13761          -----------
13762          -- Title --
13763          -----------
13764
13765          --  pragma Title (TITLING_OPTION [, TITLING OPTION]);
13766
13767          --   TITLING_OPTION ::=
13768          --     [Title =>] STRING_LITERAL
13769          --   | [Subtitle =>] STRING_LITERAL
13770
13771          when Pragma_Title => Title : declare
13772             Args  : Args_List (1 .. 2);
13773             Names : constant Name_List (1 .. 2) := (
13774                       Name_Title,
13775                       Name_Subtitle);
13776
13777          begin
13778             GNAT_Pragma;
13779             Gather_Associations (Names, Args);
13780             Store_Note (N);
13781
13782             for J in 1 .. 2 loop
13783                if Present (Args (J)) then
13784                   Check_Arg_Is_Static_Expression (Args (J), Standard_String);
13785                end if;
13786             end loop;
13787          end Title;
13788
13789          ---------------------
13790          -- Unchecked_Union --
13791          ---------------------
13792
13793          --  pragma Unchecked_Union (first_subtype_LOCAL_NAME)
13794
13795          when Pragma_Unchecked_Union => Unchecked_Union : declare
13796             Assoc   : constant Node_Id := Arg1;
13797             Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
13798             Typ     : Entity_Id;
13799             Discr   : Entity_Id;
13800             Tdef    : Node_Id;
13801             Clist   : Node_Id;
13802             Vpart   : Node_Id;
13803             Comp    : Node_Id;
13804             Variant : Node_Id;
13805
13806          begin
13807             Ada_2005_Pragma;
13808             Check_No_Identifiers;
13809             Check_Arg_Count (1);
13810             Check_Arg_Is_Local_Name (Arg1);
13811
13812             Find_Type (Type_Id);
13813             Typ := Entity (Type_Id);
13814
13815             if Typ = Any_Type
13816               or else Rep_Item_Too_Early (Typ, N)
13817             then
13818                return;
13819             else
13820                Typ := Underlying_Type (Typ);
13821             end if;
13822
13823             if Rep_Item_Too_Late (Typ, N) then
13824                return;
13825             end if;
13826
13827             Check_First_Subtype (Arg1);
13828
13829             --  Note remaining cases are references to a type in the current
13830             --  declarative part. If we find an error, we post the error on
13831             --  the relevant type declaration at an appropriate point.
13832
13833             if not Is_Record_Type (Typ) then
13834                Error_Msg_N ("Unchecked_Union must be record type", Typ);
13835                return;
13836
13837             elsif Is_Tagged_Type (Typ) then
13838                Error_Msg_N ("Unchecked_Union must not be tagged", Typ);
13839                return;
13840
13841             elsif not Has_Discriminants (Typ) then
13842                Error_Msg_N
13843                 ("Unchecked_Union must have one discriminant", Typ);
13844                return;
13845
13846             --  Note: in previous versions of GNAT we used to check for limited
13847             --  types and give an error, but in fact the standard does allow
13848             --  Unchecked_Union on limited types, so this check was removed.
13849
13850             --  Proceed with basic error checks completed
13851
13852             else
13853                Discr := First_Discriminant (Typ);
13854                while Present (Discr) loop
13855                   if No (Discriminant_Default_Value (Discr)) then
13856                      Error_Msg_N
13857                        ("Unchecked_Union discriminant must have default value",
13858                         Discr);
13859                   end if;
13860
13861                   Next_Discriminant (Discr);
13862                end loop;
13863
13864                Tdef  := Type_Definition (Declaration_Node (Typ));
13865                Clist := Component_List (Tdef);
13866
13867                Comp := First (Component_Items (Clist));
13868                while Present (Comp) loop
13869                   Check_Component (Comp, Typ);
13870                   Next (Comp);
13871                end loop;
13872
13873                if No (Clist) or else No (Variant_Part (Clist)) then
13874                   Error_Msg_N
13875                     ("Unchecked_Union must have variant part",
13876                      Tdef);
13877                   return;
13878                end if;
13879
13880                Vpart := Variant_Part (Clist);
13881
13882                Variant := First (Variants (Vpart));
13883                while Present (Variant) loop
13884                   Check_Variant (Variant, Typ);
13885                   Next (Variant);
13886                end loop;
13887             end if;
13888
13889             Set_Is_Unchecked_Union  (Typ);
13890             Set_Convention (Typ, Convention_C);
13891             Set_Has_Unchecked_Union (Base_Type (Typ));
13892             Set_Is_Unchecked_Union  (Base_Type (Typ));
13893          end Unchecked_Union;
13894
13895          ------------------------
13896          -- Unimplemented_Unit --
13897          ------------------------
13898
13899          --  pragma Unimplemented_Unit;
13900
13901          --  Note: this only gives an error if we are generating code, or if
13902          --  we are in a generic library unit (where the pragma appears in the
13903          --  body, not in the spec).
13904
13905          when Pragma_Unimplemented_Unit => Unimplemented_Unit : declare
13906             Cunitent : constant Entity_Id :=
13907                          Cunit_Entity (Get_Source_Unit (Loc));
13908             Ent_Kind : constant Entity_Kind :=
13909                          Ekind (Cunitent);
13910
13911          begin
13912             GNAT_Pragma;
13913             Check_Arg_Count (0);
13914
13915             if Operating_Mode = Generate_Code
13916               or else Ent_Kind = E_Generic_Function
13917               or else Ent_Kind = E_Generic_Procedure
13918               or else Ent_Kind = E_Generic_Package
13919             then
13920                Get_Name_String (Chars (Cunitent));
13921                Set_Casing (Mixed_Case);
13922                Write_Str (Name_Buffer (1 .. Name_Len));
13923                Write_Str (" is not supported in this configuration");
13924                Write_Eol;
13925                raise Unrecoverable_Error;
13926             end if;
13927          end Unimplemented_Unit;
13928
13929          ------------------------
13930          -- Universal_Aliasing --
13931          ------------------------
13932
13933          --  pragma Universal_Aliasing [([Entity =>] type_LOCAL_NAME)];
13934
13935          when Pragma_Universal_Aliasing => Universal_Alias : declare
13936             E_Id : Entity_Id;
13937
13938          begin
13939             GNAT_Pragma;
13940             Check_Arg_Count (1);
13941             Check_Optional_Identifier (Arg2, Name_Entity);
13942             Check_Arg_Is_Local_Name (Arg1);
13943             E_Id := Entity (Get_Pragma_Arg (Arg1));
13944
13945             if E_Id = Any_Type then
13946                return;
13947             elsif No (E_Id) or else not Is_Type (E_Id) then
13948                Error_Pragma_Arg ("pragma% requires type", Arg1);
13949             end if;
13950
13951             Set_Universal_Aliasing (Implementation_Base_Type (E_Id));
13952          end Universal_Alias;
13953
13954          --------------------
13955          -- Universal_Data --
13956          --------------------
13957
13958          --  pragma Universal_Data [(library_unit_NAME)];
13959
13960          when Pragma_Universal_Data =>
13961             GNAT_Pragma;
13962
13963             --  If this is a configuration pragma, then set the universal
13964             --  addressing option, otherwise confirm that the pragma satisfies
13965             --  the requirements of library unit pragma placement and leave it
13966             --  to the GNAAMP back end to detect the pragma (avoids transitive
13967             --  setting of the option due to withed units).
13968
13969             if Is_Configuration_Pragma then
13970                Universal_Addressing_On_AAMP := True;
13971             else
13972                Check_Valid_Library_Unit_Pragma;
13973             end if;
13974
13975             if not AAMP_On_Target then
13976                Error_Pragma ("?pragma% ignored (applies only to AAMP)");
13977             end if;
13978
13979          ----------------
13980          -- Unmodified --
13981          ----------------
13982
13983          --  pragma Unmodified (local_Name {, local_Name});
13984
13985          when Pragma_Unmodified => Unmodified : declare
13986             Arg_Node : Node_Id;
13987             Arg_Expr : Node_Id;
13988             Arg_Ent  : Entity_Id;
13989
13990          begin
13991             GNAT_Pragma;
13992             Check_At_Least_N_Arguments (1);
13993
13994             --  Loop through arguments
13995
13996             Arg_Node := Arg1;
13997             while Present (Arg_Node) loop
13998                Check_No_Identifier (Arg_Node);
13999
14000                --  Note: the analyze call done by Check_Arg_Is_Local_Name will
14001                --  in fact generate reference, so that the entity will have a
14002                --  reference, which will inhibit any warnings about it not
14003                --  being referenced, and also properly show up in the ali file
14004                --  as a reference. But this reference is recorded before the
14005                --  Has_Pragma_Unreferenced flag is set, so that no warning is
14006                --  generated for this reference.
14007
14008                Check_Arg_Is_Local_Name (Arg_Node);
14009                Arg_Expr := Get_Pragma_Arg (Arg_Node);
14010
14011                if Is_Entity_Name (Arg_Expr) then
14012                   Arg_Ent := Entity (Arg_Expr);
14013
14014                   if not Is_Assignable (Arg_Ent) then
14015                      Error_Pragma_Arg
14016                        ("pragma% can only be applied to a variable",
14017                         Arg_Expr);
14018                   else
14019                      Set_Has_Pragma_Unmodified (Arg_Ent);
14020                   end if;
14021                end if;
14022
14023                Next (Arg_Node);
14024             end loop;
14025          end Unmodified;
14026
14027          ------------------
14028          -- Unreferenced --
14029          ------------------
14030
14031          --  pragma Unreferenced (local_Name {, local_Name});
14032
14033          --    or when used in a context clause:
14034
14035          --  pragma Unreferenced (library_unit_NAME {, library_unit_NAME}
14036
14037          when Pragma_Unreferenced => Unreferenced : declare
14038             Arg_Node : Node_Id;
14039             Arg_Expr : Node_Id;
14040             Arg_Ent  : Entity_Id;
14041             Citem    : Node_Id;
14042
14043          begin
14044             GNAT_Pragma;
14045             Check_At_Least_N_Arguments (1);
14046
14047             --  Check case of appearing within context clause
14048
14049             if Is_In_Context_Clause then
14050
14051                --  The arguments must all be units mentioned in a with clause
14052                --  in the same context clause. Note we already checked (in
14053                --  Par.Prag) that the arguments are either identifiers or
14054                --  selected components.
14055
14056                Arg_Node := Arg1;
14057                while Present (Arg_Node) loop
14058                   Citem := First (List_Containing (N));
14059                   while Citem /= N loop
14060                      if Nkind (Citem) = N_With_Clause
14061                        and then
14062                          Same_Name (Name (Citem), Get_Pragma_Arg (Arg_Node))
14063                      then
14064                         Set_Has_Pragma_Unreferenced
14065                           (Cunit_Entity
14066                              (Get_Source_Unit
14067                                 (Library_Unit (Citem))));
14068                         Set_Unit_Name
14069                           (Get_Pragma_Arg (Arg_Node), Name (Citem));
14070                         exit;
14071                      end if;
14072
14073                      Next (Citem);
14074                   end loop;
14075
14076                   if Citem = N then
14077                      Error_Pragma_Arg
14078                        ("argument of pragma% is not with'ed unit", Arg_Node);
14079                   end if;
14080
14081                   Next (Arg_Node);
14082                end loop;
14083
14084             --  Case of not in list of context items
14085
14086             else
14087                Arg_Node := Arg1;
14088                while Present (Arg_Node) loop
14089                   Check_No_Identifier (Arg_Node);
14090
14091                   --  Note: the analyze call done by Check_Arg_Is_Local_Name
14092                   --  will in fact generate reference, so that the entity will
14093                   --  have a reference, which will inhibit any warnings about
14094                   --  it not being referenced, and also properly show up in the
14095                   --  ali file as a reference. But this reference is recorded
14096                   --  before the Has_Pragma_Unreferenced flag is set, so that
14097                   --  no warning is generated for this reference.
14098
14099                   Check_Arg_Is_Local_Name (Arg_Node);
14100                   Arg_Expr := Get_Pragma_Arg (Arg_Node);
14101
14102                   if Is_Entity_Name (Arg_Expr) then
14103                      Arg_Ent := Entity (Arg_Expr);
14104
14105                      --  If the entity is overloaded, the pragma applies to the
14106                      --  most recent overloading, as documented. In this case,
14107                      --  name resolution does not generate a reference, so it
14108                      --  must be done here explicitly.
14109
14110                      if Is_Overloaded (Arg_Expr) then
14111                         Generate_Reference (Arg_Ent, N);
14112                      end if;
14113
14114                      Set_Has_Pragma_Unreferenced (Arg_Ent);
14115                   end if;
14116
14117                   Next (Arg_Node);
14118                end loop;
14119             end if;
14120          end Unreferenced;
14121
14122          --------------------------
14123          -- Unreferenced_Objects --
14124          --------------------------
14125
14126          --  pragma Unreferenced_Objects (local_Name {, local_Name});
14127
14128          when Pragma_Unreferenced_Objects => Unreferenced_Objects : declare
14129             Arg_Node : Node_Id;
14130             Arg_Expr : Node_Id;
14131
14132          begin
14133             GNAT_Pragma;
14134             Check_At_Least_N_Arguments (1);
14135
14136             Arg_Node := Arg1;
14137             while Present (Arg_Node) loop
14138                Check_No_Identifier (Arg_Node);
14139                Check_Arg_Is_Local_Name (Arg_Node);
14140                Arg_Expr := Get_Pragma_Arg (Arg_Node);
14141
14142                if not Is_Entity_Name (Arg_Expr)
14143                  or else not Is_Type (Entity (Arg_Expr))
14144                then
14145                   Error_Pragma_Arg
14146                     ("argument for pragma% must be type or subtype", Arg_Node);
14147                end if;
14148
14149                Set_Has_Pragma_Unreferenced_Objects (Entity (Arg_Expr));
14150                Next (Arg_Node);
14151             end loop;
14152          end Unreferenced_Objects;
14153
14154          ------------------------------
14155          -- Unreserve_All_Interrupts --
14156          ------------------------------
14157
14158          --  pragma Unreserve_All_Interrupts;
14159
14160          when Pragma_Unreserve_All_Interrupts =>
14161             GNAT_Pragma;
14162             Check_Arg_Count (0);
14163
14164             if In_Extended_Main_Code_Unit (Main_Unit_Entity) then
14165                Unreserve_All_Interrupts := True;
14166             end if;
14167
14168          ----------------
14169          -- Unsuppress --
14170          ----------------
14171
14172          --  pragma Unsuppress (IDENTIFIER [, [On =>] NAME]);
14173
14174          when Pragma_Unsuppress =>
14175             Ada_2005_Pragma;
14176             Process_Suppress_Unsuppress (False);
14177
14178          -------------------
14179          -- Use_VADS_Size --
14180          -------------------
14181
14182          --  pragma Use_VADS_Size;
14183
14184          when Pragma_Use_VADS_Size =>
14185             GNAT_Pragma;
14186             Check_Arg_Count (0);
14187             Check_Valid_Configuration_Pragma;
14188             Use_VADS_Size := True;
14189
14190          ---------------------
14191          -- Validity_Checks --
14192          ---------------------
14193
14194          --  pragma Validity_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
14195
14196          when Pragma_Validity_Checks => Validity_Checks : declare
14197             A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
14198             S  : String_Id;
14199             C  : Char_Code;
14200
14201          begin
14202             GNAT_Pragma;
14203             Check_Arg_Count (1);
14204             Check_No_Identifiers;
14205
14206             if Nkind (A) = N_String_Literal then
14207                S   := Strval (A);
14208
14209                declare
14210                   Slen    : constant Natural := Natural (String_Length (S));
14211                   Options : String (1 .. Slen);
14212                   J       : Natural;
14213
14214                begin
14215                   J := 1;
14216                   loop
14217                      C := Get_String_Char (S, Int (J));
14218                      exit when not In_Character_Range (C);
14219                      Options (J) := Get_Character (C);
14220
14221                      if J = Slen then
14222                         Set_Validity_Check_Options (Options);
14223                         exit;
14224                      else
14225                         J := J + 1;
14226                      end if;
14227                   end loop;
14228                end;
14229
14230             elsif Nkind (A) = N_Identifier then
14231                if Chars (A) = Name_All_Checks then
14232                   Set_Validity_Check_Options ("a");
14233                elsif Chars (A) = Name_On then
14234                   Validity_Checks_On := True;
14235                elsif Chars (A) = Name_Off then
14236                   Validity_Checks_On := False;
14237                end if;
14238             end if;
14239          end Validity_Checks;
14240
14241          --------------
14242          -- Volatile --
14243          --------------
14244
14245          --  pragma Volatile (LOCAL_NAME);
14246
14247          when Pragma_Volatile =>
14248             Process_Atomic_Shared_Volatile;
14249
14250          -------------------------
14251          -- Volatile_Components --
14252          -------------------------
14253
14254          --  pragma Volatile_Components (array_LOCAL_NAME);
14255
14256          --  Volatile is handled by the same circuit as Atomic_Components
14257
14258          --------------
14259          -- Warnings --
14260          --------------
14261
14262          --  pragma Warnings (On | Off);
14263          --  pragma Warnings (On | Off, LOCAL_NAME);
14264          --  pragma Warnings (static_string_EXPRESSION);
14265          --  pragma Warnings (On | Off, STRING_LITERAL);
14266
14267          when Pragma_Warnings => Warnings : begin
14268             GNAT_Pragma;
14269             Check_At_Least_N_Arguments (1);
14270             Check_No_Identifiers;
14271
14272             --  If debug flag -gnatd.i is set, pragma is ignored
14273
14274             if Debug_Flag_Dot_I then
14275                return;
14276             end if;
14277
14278             --  Process various forms of the pragma
14279
14280             declare
14281                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
14282
14283             begin
14284                --  One argument case
14285
14286                if Arg_Count = 1 then
14287
14288                   --  On/Off one argument case was processed by parser
14289
14290                   if Nkind (Argx) = N_Identifier
14291                     and then
14292                       (Chars (Argx) = Name_On
14293                          or else
14294                        Chars (Argx) = Name_Off)
14295                   then
14296                      null;
14297
14298                   --  One argument case must be ON/OFF or static string expr
14299
14300                   elsif not Is_Static_String_Expression (Arg1) then
14301                      Error_Pragma_Arg
14302                        ("argument of pragma% must be On/Off or " &
14303                         "static string expression", Arg1);
14304
14305                   --  One argument string expression case
14306
14307                   else
14308                      declare
14309                         Lit : constant Node_Id   := Expr_Value_S (Argx);
14310                         Str : constant String_Id := Strval (Lit);
14311                         Len : constant Nat       := String_Length (Str);
14312                         C   : Char_Code;
14313                         J   : Nat;
14314                         OK  : Boolean;
14315                         Chr : Character;
14316
14317                      begin
14318                         J := 1;
14319                         while J <= Len loop
14320                            C := Get_String_Char (Str, J);
14321                            OK := In_Character_Range (C);
14322
14323                            if OK then
14324                               Chr := Get_Character (C);
14325
14326                               --  Dot case
14327
14328                               if J < Len and then Chr = '.' then
14329                                  J := J + 1;
14330                                  C := Get_String_Char (Str, J);
14331                                  Chr := Get_Character (C);
14332
14333                                  if not Set_Dot_Warning_Switch (Chr) then
14334                                     Error_Pragma_Arg
14335                                       ("invalid warning switch character " &
14336                                        '.' & Chr, Arg1);
14337                                  end if;
14338
14339                               --  Non-Dot case
14340
14341                               else
14342                                  OK := Set_Warning_Switch (Chr);
14343                               end if;
14344                            end if;
14345
14346                            if not OK then
14347                               Error_Pragma_Arg
14348                                 ("invalid warning switch character " & Chr,
14349                                  Arg1);
14350                            end if;
14351
14352                            J := J + 1;
14353                         end loop;
14354                      end;
14355                   end if;
14356
14357                   --  Two or more arguments (must be two)
14358
14359                else
14360                   Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
14361                   Check_At_Most_N_Arguments (2);
14362
14363                   declare
14364                      E_Id : Node_Id;
14365                      E    : Entity_Id;
14366                      Err  : Boolean;
14367
14368                   begin
14369                      E_Id := Get_Pragma_Arg (Arg2);
14370                      Analyze (E_Id);
14371
14372                      --  In the expansion of an inlined body, a reference to
14373                      --  the formal may be wrapped in a conversion if the
14374                      --  actual is a conversion. Retrieve the real entity name.
14375
14376                      if (In_Instance_Body
14377                          or else In_Inlined_Body)
14378                        and then Nkind (E_Id) = N_Unchecked_Type_Conversion
14379                      then
14380                         E_Id := Expression (E_Id);
14381                      end if;
14382
14383                      --  Entity name case
14384
14385                      if Is_Entity_Name (E_Id) then
14386                         E := Entity (E_Id);
14387
14388                         if E = Any_Id then
14389                            return;
14390                         else
14391                            loop
14392                               Set_Warnings_Off
14393                                 (E, (Chars (Get_Pragma_Arg (Arg1)) =
14394                                                               Name_Off));
14395
14396                               if Chars (Get_Pragma_Arg (Arg1)) = Name_Off
14397                                 and then Warn_On_Warnings_Off
14398                               then
14399                                  Warnings_Off_Pragmas.Append ((N, E));
14400                               end if;
14401
14402                               if Is_Enumeration_Type (E) then
14403                                  declare
14404                                     Lit : Entity_Id;
14405                                  begin
14406                                     Lit := First_Literal (E);
14407                                     while Present (Lit) loop
14408                                        Set_Warnings_Off (Lit);
14409                                        Next_Literal (Lit);
14410                                     end loop;
14411                                  end;
14412                               end if;
14413
14414                               exit when No (Homonym (E));
14415                               E := Homonym (E);
14416                            end loop;
14417                         end if;
14418
14419                      --  Error if not entity or static string literal case
14420
14421                      elsif not Is_Static_String_Expression (Arg2) then
14422                         Error_Pragma_Arg
14423                           ("second argument of pragma% must be entity " &
14424                            "name or static string expression", Arg2);
14425
14426                      --  String literal case
14427
14428                      else
14429                         String_To_Name_Buffer
14430                           (Strval (Expr_Value_S (Get_Pragma_Arg (Arg2))));
14431
14432                         --  Note on configuration pragma case: If this is a
14433                         --  configuration pragma, then for an OFF pragma, we
14434                         --  just set Config True in the call, which is all
14435                         --  that needs to be done. For the case of ON, this
14436                         --  is normally an error, unless it is canceling the
14437                         --  effect of a previous OFF pragma in the same file.
14438                         --  In any other case, an error will be signalled (ON
14439                         --  with no matching OFF).
14440
14441                         if Chars (Argx) = Name_Off then
14442                            Set_Specific_Warning_Off
14443                              (Loc, Name_Buffer (1 .. Name_Len),
14444                               Config => Is_Configuration_Pragma);
14445
14446                         elsif Chars (Argx) = Name_On then
14447                            Set_Specific_Warning_On
14448                              (Loc, Name_Buffer (1 .. Name_Len), Err);
14449
14450                            if Err then
14451                               Error_Msg
14452                                 ("?pragma Warnings On with no " &
14453                                  "matching Warnings Off",
14454                                  Loc);
14455                            end if;
14456                         end if;
14457                      end if;
14458                   end;
14459                end if;
14460             end;
14461          end Warnings;
14462
14463          -------------------
14464          -- Weak_External --
14465          -------------------
14466
14467          --  pragma Weak_External ([Entity =>] LOCAL_NAME);
14468
14469          when Pragma_Weak_External => Weak_External : declare
14470             Ent : Entity_Id;
14471
14472          begin
14473             GNAT_Pragma;
14474             Check_Arg_Count (1);
14475             Check_Optional_Identifier (Arg1, Name_Entity);
14476             Check_Arg_Is_Library_Level_Local_Name (Arg1);
14477             Ent := Entity (Get_Pragma_Arg (Arg1));
14478
14479             if Rep_Item_Too_Early (Ent, N) then
14480                return;
14481             else
14482                Ent := Underlying_Type (Ent);
14483             end if;
14484
14485             --  The only processing required is to link this item on to the
14486             --  list of rep items for the given entity. This is accomplished
14487             --  by the call to Rep_Item_Too_Late (when no error is detected
14488             --  and False is returned).
14489
14490             if Rep_Item_Too_Late (Ent, N) then
14491                return;
14492             else
14493                Set_Has_Gigi_Rep_Item (Ent);
14494             end if;
14495          end Weak_External;
14496
14497          -----------------------------
14498          -- Wide_Character_Encoding --
14499          -----------------------------
14500
14501          --  pragma Wide_Character_Encoding (IDENTIFIER);
14502
14503          when Pragma_Wide_Character_Encoding =>
14504             GNAT_Pragma;
14505
14506             --  Nothing to do, handled in parser. Note that we do not enforce
14507             --  configuration pragma placement, this pragma can appear at any
14508             --  place in the source, allowing mixed encodings within a single
14509             --  source program.
14510
14511             null;
14512
14513          --------------------
14514          -- Unknown_Pragma --
14515          --------------------
14516
14517          --  Should be impossible, since the case of an unknown pragma is
14518          --  separately processed before the case statement is entered.
14519
14520          when Unknown_Pragma =>
14521             raise Program_Error;
14522       end case;
14523
14524       --  AI05-0144: detect dangerous order dependence. Disabled for now,
14525       --  until AI is formally approved.
14526
14527       --  Check_Order_Dependence;
14528
14529    exception
14530       when Pragma_Exit => null;
14531    end Analyze_Pragma;
14532
14533    -----------------------------
14534    -- Analyze_TC_In_Decl_Part --
14535    -----------------------------
14536
14537    procedure Analyze_TC_In_Decl_Part (N : Node_Id; S : Entity_Id) is
14538    begin
14539       --  Install formals and push subprogram spec onto scope stack so that we
14540       --  can see the formals from the pragma.
14541
14542       Install_Formals (S);
14543       Push_Scope (S);
14544
14545       --  Preanalyze the boolean expressions, we treat these as spec
14546       --  expressions (i.e. similar to a default expression).
14547
14548       Preanalyze_TC_Args (Get_Requires_From_Test_Case_Pragma (N),
14549                           Get_Ensures_From_Test_Case_Pragma (N));
14550
14551       --  Remove the subprogram from the scope stack now that the pre-analysis
14552       --  of the expressions in the test-case is done.
14553
14554       End_Scope;
14555    end Analyze_TC_In_Decl_Part;
14556
14557    --------------------
14558    -- Check_Disabled --
14559    --------------------
14560
14561    function Check_Disabled (Nam : Name_Id) return Boolean is
14562       PP : Node_Id;
14563
14564    begin
14565       --  Loop through entries in check policy list
14566
14567       PP := Opt.Check_Policy_List;
14568       loop
14569          --  If there are no specific entries that matched, then nothing is
14570          --  disabled, so return False.
14571
14572          if No (PP) then
14573             return False;
14574
14575          --  Here we have an entry see if it matches
14576
14577          else
14578             declare
14579                PPA : constant List_Id := Pragma_Argument_Associations (PP);
14580             begin
14581                if Nam = Chars (Get_Pragma_Arg (First (PPA))) then
14582                   return Chars (Get_Pragma_Arg (Last (PPA))) = Name_Disable;
14583                else
14584                   PP := Next_Pragma (PP);
14585                end if;
14586             end;
14587          end if;
14588       end loop;
14589    end Check_Disabled;
14590
14591    -------------------
14592    -- Check_Enabled --
14593    -------------------
14594
14595    function Check_Enabled (Nam : Name_Id) return Boolean is
14596       PP : Node_Id;
14597
14598    begin
14599       --  Loop through entries in check policy list
14600
14601       PP := Opt.Check_Policy_List;
14602       loop
14603          --  If there are no specific entries that matched, then we let the
14604          --  setting of assertions govern. Note that this provides the needed
14605          --  compatibility with the RM for the cases of assertion, invariant,
14606          --  precondition, predicate, and postcondition.
14607
14608          if No (PP) then
14609             return Assertions_Enabled;
14610
14611          --  Here we have an entry see if it matches
14612
14613          else
14614             declare
14615                PPA : constant List_Id := Pragma_Argument_Associations (PP);
14616
14617             begin
14618                if Nam = Chars (Get_Pragma_Arg (First (PPA))) then
14619                   case (Chars (Get_Pragma_Arg (Last (PPA)))) is
14620                      when Name_On | Name_Check =>
14621                         return True;
14622                      when Name_Off | Name_Ignore =>
14623                         return False;
14624                      when others =>
14625                         raise Program_Error;
14626                   end case;
14627
14628                else
14629                   PP := Next_Pragma (PP);
14630                end if;
14631             end;
14632          end if;
14633       end loop;
14634    end Check_Enabled;
14635
14636    ---------------------------------
14637    -- Delay_Config_Pragma_Analyze --
14638    ---------------------------------
14639
14640    function Delay_Config_Pragma_Analyze (N : Node_Id) return Boolean is
14641    begin
14642       return Pragma_Name (N) = Name_Interrupt_State
14643                or else
14644              Pragma_Name (N) = Name_Priority_Specific_Dispatching;
14645    end Delay_Config_Pragma_Analyze;
14646
14647    -------------------------
14648    -- Get_Base_Subprogram --
14649    -------------------------
14650
14651    function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id is
14652       Result : Entity_Id;
14653
14654    begin
14655       --  Follow subprogram renaming chain
14656
14657       Result := Def_Id;
14658       while Is_Subprogram (Result)
14659         and then
14660           Nkind (Parent (Declaration_Node (Result))) =
14661                                          N_Subprogram_Renaming_Declaration
14662         and then Present (Alias (Result))
14663       loop
14664          Result := Alias (Result);
14665       end loop;
14666
14667       return Result;
14668    end Get_Base_Subprogram;
14669
14670    ----------------
14671    -- Initialize --
14672    ----------------
14673
14674    procedure Initialize is
14675    begin
14676       Externals.Init;
14677    end Initialize;
14678
14679    -----------------------------
14680    -- Is_Config_Static_String --
14681    -----------------------------
14682
14683    function Is_Config_Static_String (Arg : Node_Id) return Boolean is
14684
14685       function Add_Config_Static_String (Arg : Node_Id) return Boolean;
14686       --  This is an internal recursive function that is just like the outer
14687       --  function except that it adds the string to the name buffer rather
14688       --  than placing the string in the name buffer.
14689
14690       ------------------------------
14691       -- Add_Config_Static_String --
14692       ------------------------------
14693
14694       function Add_Config_Static_String (Arg : Node_Id) return Boolean is
14695          N : Node_Id;
14696          C : Char_Code;
14697
14698       begin
14699          N := Arg;
14700
14701          if Nkind (N) = N_Op_Concat then
14702             if Add_Config_Static_String (Left_Opnd (N)) then
14703                N := Right_Opnd (N);
14704             else
14705                return False;
14706             end if;
14707          end if;
14708
14709          if Nkind (N) /= N_String_Literal then
14710             Error_Msg_N ("string literal expected for pragma argument", N);
14711             return False;
14712
14713          else
14714             for J in 1 .. String_Length (Strval (N)) loop
14715                C := Get_String_Char (Strval (N), J);
14716
14717                if not In_Character_Range (C) then
14718                   Error_Msg
14719                     ("string literal contains invalid wide character",
14720                      Sloc (N) + 1 + Source_Ptr (J));
14721                   return False;
14722                end if;
14723
14724                Add_Char_To_Name_Buffer (Get_Character (C));
14725             end loop;
14726          end if;
14727
14728          return True;
14729       end Add_Config_Static_String;
14730
14731    --  Start of processing for Is_Config_Static_String
14732
14733    begin
14734
14735       Name_Len := 0;
14736       return Add_Config_Static_String (Arg);
14737    end Is_Config_Static_String;
14738
14739    -----------------------------------------
14740    -- Is_Non_Significant_Pragma_Reference --
14741    -----------------------------------------
14742
14743    --  This function makes use of the following static table which indicates
14744    --  whether a given pragma is significant.
14745
14746    --  -1  indicates that references in any argument position are significant
14747    --  0   indicates that appearance in any argument is not significant
14748    --  +n  indicates that appearance as argument n is significant, but all
14749    --      other arguments are not significant
14750    --  99  special processing required (e.g. for pragma Check)
14751
14752    Sig_Flags : constant array (Pragma_Id) of Int :=
14753      (Pragma_AST_Entry                      => -1,
14754       Pragma_Abort_Defer                    => -1,
14755       Pragma_Ada_83                         => -1,
14756       Pragma_Ada_95                         => -1,
14757       Pragma_Ada_05                         => -1,
14758       Pragma_Ada_2005                       => -1,
14759       Pragma_Ada_12                         => -1,
14760       Pragma_Ada_2012                       => -1,
14761       Pragma_All_Calls_Remote               => -1,
14762       Pragma_Annotate                       => -1,
14763       Pragma_Assert                         => -1,
14764       Pragma_Assertion_Policy               =>  0,
14765       Pragma_Assume_No_Invalid_Values       =>  0,
14766       Pragma_Asynchronous                   => -1,
14767       Pragma_Atomic                         =>  0,
14768       Pragma_Atomic_Components              =>  0,
14769       Pragma_Attach_Handler                 => -1,
14770       Pragma_Check                          => 99,
14771       Pragma_Check_Name                     =>  0,
14772       Pragma_Check_Policy                   =>  0,
14773       Pragma_CIL_Constructor                => -1,
14774       Pragma_CPP_Class                      =>  0,
14775       Pragma_CPP_Constructor                =>  0,
14776       Pragma_CPP_Virtual                    =>  0,
14777       Pragma_CPP_Vtable                     =>  0,
14778       Pragma_CPU                            => -1,
14779       Pragma_C_Pass_By_Copy                 =>  0,
14780       Pragma_Comment                        =>  0,
14781       Pragma_Common_Object                  => -1,
14782       Pragma_Compile_Time_Error             => -1,
14783       Pragma_Compile_Time_Warning           => -1,
14784       Pragma_Compiler_Unit                  =>  0,
14785       Pragma_Complete_Representation        =>  0,
14786       Pragma_Complex_Representation         =>  0,
14787       Pragma_Component_Alignment            => -1,
14788       Pragma_Controlled                     =>  0,
14789       Pragma_Convention                     =>  0,
14790       Pragma_Convention_Identifier          =>  0,
14791       Pragma_Debug                          => -1,
14792       Pragma_Debug_Policy                   =>  0,
14793       Pragma_Detect_Blocking                => -1,
14794       Pragma_Default_Storage_Pool           => -1,
14795       Pragma_Dimension                      => -1,
14796       Pragma_Disable_Atomic_Synchronization => -1,
14797       Pragma_Discard_Names                  =>  0,
14798       Pragma_Dispatching_Domain             => -1,
14799       Pragma_Elaborate                      => -1,
14800       Pragma_Elaborate_All                  => -1,
14801       Pragma_Elaborate_Body                 => -1,
14802       Pragma_Elaboration_Checks             => -1,
14803       Pragma_Eliminate                      => -1,
14804       Pragma_Enable_Atomic_Synchronization  => -1,
14805       Pragma_Export                         => -1,
14806       Pragma_Export_Exception               => -1,
14807       Pragma_Export_Function                => -1,
14808       Pragma_Export_Object                  => -1,
14809       Pragma_Export_Procedure               => -1,
14810       Pragma_Export_Value                   => -1,
14811       Pragma_Export_Valued_Procedure        => -1,
14812       Pragma_Extend_System                  => -1,
14813       Pragma_Extensions_Allowed             => -1,
14814       Pragma_External                       => -1,
14815       Pragma_Favor_Top_Level                => -1,
14816       Pragma_External_Name_Casing           => -1,
14817       Pragma_Fast_Math                      => -1,
14818       Pragma_Finalize_Storage_Only          =>  0,
14819       Pragma_Float_Representation           =>  0,
14820       Pragma_Ident                          => -1,
14821       Pragma_Implementation_Defined         => -1,
14822       Pragma_Implemented                    => -1,
14823       Pragma_Implicit_Packing               =>  0,
14824       Pragma_Import                         => +2,
14825       Pragma_Import_Exception               =>  0,
14826       Pragma_Import_Function                =>  0,
14827       Pragma_Import_Object                  =>  0,
14828       Pragma_Import_Procedure               =>  0,
14829       Pragma_Import_Valued_Procedure        =>  0,
14830       Pragma_Independent                    =>  0,
14831       Pragma_Independent_Components         =>  0,
14832       Pragma_Initialize_Scalars             => -1,
14833       Pragma_Inline                         =>  0,
14834       Pragma_Inline_Always                  =>  0,
14835       Pragma_Inline_Generic                 =>  0,
14836       Pragma_Inspection_Point               => -1,
14837       Pragma_Interface                      => +2,
14838       Pragma_Interface_Name                 => +2,
14839       Pragma_Interrupt_Handler              => -1,
14840       Pragma_Interrupt_Priority             => -1,
14841       Pragma_Interrupt_State                => -1,
14842       Pragma_Invariant                      => -1,
14843       Pragma_Java_Constructor               => -1,
14844       Pragma_Java_Interface                 => -1,
14845       Pragma_Keep_Names                     =>  0,
14846       Pragma_License                        => -1,
14847       Pragma_Link_With                      => -1,
14848       Pragma_Linker_Alias                   => -1,
14849       Pragma_Linker_Constructor             => -1,
14850       Pragma_Linker_Destructor              => -1,
14851       Pragma_Linker_Options                 => -1,
14852       Pragma_Linker_Section                 => -1,
14853       Pragma_List                           => -1,
14854       Pragma_Locking_Policy                 => -1,
14855       Pragma_Long_Float                     => -1,
14856       Pragma_Machine_Attribute              => -1,
14857       Pragma_Main                           => -1,
14858       Pragma_Main_Storage                   => -1,
14859       Pragma_Memory_Size                    => -1,
14860       Pragma_No_Return                      =>  0,
14861       Pragma_No_Body                        =>  0,
14862       Pragma_No_Run_Time                    => -1,
14863       Pragma_No_Strict_Aliasing             => -1,
14864       Pragma_Normalize_Scalars              => -1,
14865       Pragma_Obsolescent                    =>  0,
14866       Pragma_Optimize                       => -1,
14867       Pragma_Optimize_Alignment             => -1,
14868       Pragma_Ordered                        =>  0,
14869       Pragma_Pack                           =>  0,
14870       Pragma_Page                           => -1,
14871       Pragma_Passive                        => -1,
14872       Pragma_Preelaborable_Initialization   => -1,
14873       Pragma_Polling                        => -1,
14874       Pragma_Persistent_BSS                 =>  0,
14875       Pragma_Postcondition                  => -1,
14876       Pragma_Precondition                   => -1,
14877       Pragma_Predicate                      => -1,
14878       Pragma_Preelaborate                   => -1,
14879       Pragma_Preelaborate_05                => -1,
14880       Pragma_Priority                       => -1,
14881       Pragma_Priority_Specific_Dispatching  => -1,
14882       Pragma_Profile                        =>  0,
14883       Pragma_Profile_Warnings               =>  0,
14884       Pragma_Propagate_Exceptions           => -1,
14885       Pragma_Psect_Object                   => -1,
14886       Pragma_Pure                           => -1,
14887       Pragma_Pure_05                        => -1,
14888       Pragma_Pure_Function                  => -1,
14889       Pragma_Queuing_Policy                 => -1,
14890       Pragma_Ravenscar                      => -1,
14891       Pragma_Relative_Deadline              => -1,
14892       Pragma_Remote_Call_Interface          => -1,
14893       Pragma_Remote_Types                   => -1,
14894       Pragma_Restricted_Run_Time            => -1,
14895       Pragma_Restriction_Warnings           => -1,
14896       Pragma_Restrictions                   => -1,
14897       Pragma_Reviewable                     => -1,
14898       Pragma_Short_Circuit_And_Or           => -1,
14899       Pragma_Share_Generic                  => -1,
14900       Pragma_Shared                         => -1,
14901       Pragma_Shared_Passive                 => -1,
14902       Pragma_Short_Descriptors              =>  0,
14903       Pragma_Source_File_Name               => -1,
14904       Pragma_Source_File_Name_Project       => -1,
14905       Pragma_Source_Reference               => -1,
14906       Pragma_Storage_Size                   => -1,
14907       Pragma_Storage_Unit                   => -1,
14908       Pragma_Static_Elaboration_Desired     => -1,
14909       Pragma_Stream_Convert                 => -1,
14910       Pragma_Style_Checks                   => -1,
14911       Pragma_Subtitle                       => -1,
14912       Pragma_Suppress                       =>  0,
14913       Pragma_Suppress_Exception_Locations   =>  0,
14914       Pragma_Suppress_All                   => -1,
14915       Pragma_Suppress_Debug_Info            =>  0,
14916       Pragma_Suppress_Initialization        =>  0,
14917       Pragma_System_Name                    => -1,
14918       Pragma_Task_Dispatching_Policy        => -1,
14919       Pragma_Task_Info                      => -1,
14920       Pragma_Task_Name                      => -1,
14921       Pragma_Task_Storage                   =>  0,
14922       Pragma_Test_Case                      => -1,
14923       Pragma_Thread_Local_Storage           =>  0,
14924       Pragma_Time_Slice                     => -1,
14925       Pragma_Title                          => -1,
14926       Pragma_Unchecked_Union                =>  0,
14927       Pragma_Unimplemented_Unit             => -1,
14928       Pragma_Universal_Aliasing             => -1,
14929       Pragma_Universal_Data                 => -1,
14930       Pragma_Unmodified                     => -1,
14931       Pragma_Unreferenced                   => -1,
14932       Pragma_Unreferenced_Objects           => -1,
14933       Pragma_Unreserve_All_Interrupts       => -1,
14934       Pragma_Unsuppress                     =>  0,
14935       Pragma_Use_VADS_Size                  => -1,
14936       Pragma_Validity_Checks                => -1,
14937       Pragma_Volatile                       =>  0,
14938       Pragma_Volatile_Components            =>  0,
14939       Pragma_Warnings                       => -1,
14940       Pragma_Weak_External                  => -1,
14941       Pragma_Wide_Character_Encoding        =>  0,
14942       Unknown_Pragma                        =>  0);
14943
14944    function Is_Non_Significant_Pragma_Reference (N : Node_Id) return Boolean is
14945       Id : Pragma_Id;
14946       P  : Node_Id;
14947       C  : Int;
14948       A  : Node_Id;
14949
14950    begin
14951       P := Parent (N);
14952
14953       if Nkind (P) /= N_Pragma_Argument_Association then
14954          return False;
14955
14956       else
14957          Id := Get_Pragma_Id (Parent (P));
14958          C := Sig_Flags (Id);
14959
14960          case C is
14961             when -1 =>
14962                return False;
14963
14964             when 0 =>
14965                return True;
14966
14967             when 99 =>
14968                case Id is
14969
14970                   --  For pragma Check, the first argument is not significant,
14971                   --  the second and the third (if present) arguments are
14972                   --  significant.
14973
14974                   when Pragma_Check =>
14975                      return
14976                        P = First (Pragma_Argument_Associations (Parent (P)));
14977
14978                   when others =>
14979                      raise Program_Error;
14980                end case;
14981
14982             when others =>
14983                A := First (Pragma_Argument_Associations (Parent (P)));
14984                for J in 1 .. C - 1 loop
14985                   if No (A) then
14986                      return False;
14987                   end if;
14988
14989                   Next (A);
14990                end loop;
14991
14992                return A = P; -- is this wrong way round ???
14993          end case;
14994       end if;
14995    end Is_Non_Significant_Pragma_Reference;
14996
14997    ------------------------------
14998    -- Is_Pragma_String_Literal --
14999    ------------------------------
15000
15001    --  This function returns true if the corresponding pragma argument is a
15002    --  static string expression. These are the only cases in which string
15003    --  literals can appear as pragma arguments. We also allow a string literal
15004    --  as the first argument to pragma Assert (although it will of course
15005    --  always generate a type error).
15006
15007    function Is_Pragma_String_Literal (Par : Node_Id) return Boolean is
15008       Pragn : constant Node_Id := Parent (Par);
15009       Assoc : constant List_Id := Pragma_Argument_Associations (Pragn);
15010       Pname : constant Name_Id := Pragma_Name (Pragn);
15011       Argn  : Natural;
15012       N     : Node_Id;
15013
15014    begin
15015       Argn := 1;
15016       N := First (Assoc);
15017       loop
15018          exit when N = Par;
15019          Argn := Argn + 1;
15020          Next (N);
15021       end loop;
15022
15023       if Pname = Name_Assert then
15024          return True;
15025
15026       elsif Pname = Name_Export then
15027          return Argn > 2;
15028
15029       elsif Pname = Name_Ident then
15030          return Argn = 1;
15031
15032       elsif Pname = Name_Import then
15033          return Argn > 2;
15034
15035       elsif Pname = Name_Interface_Name then
15036          return Argn > 1;
15037
15038       elsif Pname = Name_Linker_Alias then
15039          return Argn = 2;
15040
15041       elsif Pname = Name_Linker_Section then
15042          return Argn = 2;
15043
15044       elsif Pname = Name_Machine_Attribute then
15045          return Argn = 2;
15046
15047       elsif Pname = Name_Source_File_Name then
15048          return True;
15049
15050       elsif Pname = Name_Source_Reference then
15051          return Argn = 2;
15052
15053       elsif Pname = Name_Title then
15054          return True;
15055
15056       elsif Pname = Name_Subtitle then
15057          return True;
15058
15059       else
15060          return False;
15061       end if;
15062    end Is_Pragma_String_Literal;
15063
15064    ------------------------
15065    -- Preanalyze_TC_Args --
15066    ------------------------
15067
15068    procedure Preanalyze_TC_Args (Arg_Req, Arg_Ens : Node_Id) is
15069    begin
15070       --  Preanalyze the boolean expressions, we treat these as spec
15071       --  expressions (i.e. similar to a default expression).
15072
15073       if Present (Arg_Req) then
15074          Preanalyze_Spec_Expression
15075            (Get_Pragma_Arg (Arg_Req), Standard_Boolean);
15076       end if;
15077
15078       if Present (Arg_Ens) then
15079          Preanalyze_Spec_Expression
15080            (Get_Pragma_Arg (Arg_Ens), Standard_Boolean);
15081       end if;
15082    end Preanalyze_TC_Args;
15083
15084    --------------------------------------
15085    -- Process_Compilation_Unit_Pragmas --
15086    --------------------------------------
15087
15088    procedure Process_Compilation_Unit_Pragmas (N : Node_Id) is
15089    begin
15090       --  A special check for pragma Suppress_All, a very strange DEC pragma,
15091       --  strange because it comes at the end of the unit. Rational has the
15092       --  same name for a pragma, but treats it as a program unit pragma, In
15093       --  GNAT we just decide to allow it anywhere at all. If it appeared then
15094       --  the flag Has_Pragma_Suppress_All was set on the compilation unit
15095       --  node, and we insert a pragma Suppress (All_Checks) at the start of
15096       --  the context clause to ensure the correct processing.
15097
15098       if Has_Pragma_Suppress_All (N) then
15099          Prepend_To (Context_Items (N),
15100            Make_Pragma (Sloc (N),
15101              Chars                        => Name_Suppress,
15102              Pragma_Argument_Associations => New_List (
15103                Make_Pragma_Argument_Association (Sloc (N),
15104                  Expression => Make_Identifier (Sloc (N), Name_All_Checks)))));
15105       end if;
15106
15107       --  Nothing else to do at the current time!
15108
15109    end Process_Compilation_Unit_Pragmas;
15110
15111    --------
15112    -- rv --
15113    --------
15114
15115    procedure rv is
15116    begin
15117       null;
15118    end rv;
15119
15120    --------------------------------
15121    -- Set_Encoded_Interface_Name --
15122    --------------------------------
15123
15124    procedure Set_Encoded_Interface_Name (E : Entity_Id; S : Node_Id) is
15125       Str : constant String_Id := Strval (S);
15126       Len : constant Int       := String_Length (Str);
15127       CC  : Char_Code;
15128       C   : Character;
15129       J   : Int;
15130
15131       Hex : constant array (0 .. 15) of Character := "0123456789abcdef";
15132
15133       procedure Encode;
15134       --  Stores encoded value of character code CC. The encoding we use an
15135       --  underscore followed by four lower case hex digits.
15136
15137       ------------
15138       -- Encode --
15139       ------------
15140
15141       procedure Encode is
15142       begin
15143          Store_String_Char (Get_Char_Code ('_'));
15144          Store_String_Char
15145            (Get_Char_Code (Hex (Integer (CC / 2 ** 12))));
15146          Store_String_Char
15147            (Get_Char_Code (Hex (Integer (CC / 2 ** 8 and 16#0F#))));
15148          Store_String_Char
15149            (Get_Char_Code (Hex (Integer (CC / 2 ** 4 and 16#0F#))));
15150          Store_String_Char
15151            (Get_Char_Code (Hex (Integer (CC and 16#0F#))));
15152       end Encode;
15153
15154    --  Start of processing for Set_Encoded_Interface_Name
15155
15156    begin
15157       --  If first character is asterisk, this is a link name, and we leave it
15158       --  completely unmodified. We also ignore null strings (the latter case
15159       --  happens only in error cases) and no encoding should occur for Java or
15160       --  AAMP interface names.
15161
15162       if Len = 0
15163         or else Get_String_Char (Str, 1) = Get_Char_Code ('*')
15164         or else VM_Target /= No_VM
15165         or else AAMP_On_Target
15166       then
15167          Set_Interface_Name (E, S);
15168
15169       else
15170          J := 1;
15171          loop
15172             CC := Get_String_Char (Str, J);
15173
15174             exit when not In_Character_Range (CC);
15175
15176             C := Get_Character (CC);
15177
15178             exit when C /= '_' and then C /= '$'
15179               and then C not in '0' .. '9'
15180               and then C not in 'a' .. 'z'
15181               and then C not in 'A' .. 'Z';
15182
15183             if J = Len then
15184                Set_Interface_Name (E, S);
15185                return;
15186
15187             else
15188                J := J + 1;
15189             end if;
15190          end loop;
15191
15192          --  Here we need to encode. The encoding we use as follows:
15193          --     three underscores  + four hex digits (lower case)
15194
15195          Start_String;
15196
15197          for J in 1 .. String_Length (Str) loop
15198             CC := Get_String_Char (Str, J);
15199
15200             if not In_Character_Range (CC) then
15201                Encode;
15202             else
15203                C := Get_Character (CC);
15204
15205                if C = '_' or else C = '$'
15206                  or else C in '0' .. '9'
15207                  or else C in 'a' .. 'z'
15208                  or else C in 'A' .. 'Z'
15209                then
15210                   Store_String_Char (CC);
15211                else
15212                   Encode;
15213                end if;
15214             end if;
15215          end loop;
15216
15217          Set_Interface_Name (E,
15218            Make_String_Literal (Sloc (S),
15219              Strval => End_String));
15220       end if;
15221    end Set_Encoded_Interface_Name;
15222
15223    -------------------
15224    -- Set_Unit_Name --
15225    -------------------
15226
15227    procedure Set_Unit_Name (N : Node_Id; With_Item : Node_Id) is
15228       Pref : Node_Id;
15229       Scop : Entity_Id;
15230
15231    begin
15232       if Nkind (N) = N_Identifier
15233         and then Nkind (With_Item) = N_Identifier
15234       then
15235          Set_Entity (N, Entity (With_Item));
15236
15237       elsif Nkind (N) = N_Selected_Component then
15238          Change_Selected_Component_To_Expanded_Name (N);
15239          Set_Entity (N, Entity (With_Item));
15240          Set_Entity (Selector_Name (N), Entity (N));
15241
15242          Pref := Prefix (N);
15243          Scop := Scope (Entity (N));
15244          while Nkind (Pref) = N_Selected_Component loop
15245             Change_Selected_Component_To_Expanded_Name (Pref);
15246             Set_Entity (Selector_Name (Pref), Scop);
15247             Set_Entity (Pref, Scop);
15248             Pref := Prefix (Pref);
15249             Scop := Scope (Scop);
15250          end loop;
15251
15252          Set_Entity (Pref, Scop);
15253       end if;
15254    end Set_Unit_Name;
15255
15256 end Sem_Prag;