OSDN Git Service

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