OSDN Git Service

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