OSDN Git Service

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