OSDN Git Service

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