OSDN Git Service

2007-08-31 Bob Duff <duff@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             Store_String_Chars (String_Val);
3740             Link_Nam :=
3741               Make_String_Literal (Sloc (Link_Nam),
3742                 Strval => End_String);
3743          end if;
3744
3745          Set_Encoded_Interface_Name
3746            (Get_Base_Subprogram (Subprogram_Def), Link_Nam);
3747          Check_Duplicated_Export_Name (Link_Nam);
3748       end Process_Interface_Name;
3749
3750       -----------------------------------------
3751       -- Process_Interrupt_Or_Attach_Handler --
3752       -----------------------------------------
3753
3754       procedure Process_Interrupt_Or_Attach_Handler is
3755          Arg1_X       : constant Node_Id   := Expression (Arg1);
3756          Handler_Proc : constant Entity_Id := Entity (Arg1_X);
3757          Proc_Scope   : constant Entity_Id := Scope (Handler_Proc);
3758
3759       begin
3760          Set_Is_Interrupt_Handler (Handler_Proc);
3761
3762          --  If the pragma is not associated with a handler procedure
3763          --  within a protected type, then it must be for a nonprotected
3764          --  procedure for the AAMP target, in which case we don't
3765          --  associate a representation item with the procedure's scope.
3766
3767          if Ekind (Proc_Scope) = E_Protected_Type then
3768             if Prag_Id = Pragma_Interrupt_Handler
3769                  or else
3770                Prag_Id = Pragma_Attach_Handler
3771             then
3772                Record_Rep_Item (Proc_Scope, N);
3773             end if;
3774          end if;
3775       end Process_Interrupt_Or_Attach_Handler;
3776
3777       --------------------------------------------------
3778       -- Process_Restrictions_Or_Restriction_Warnings --
3779       --------------------------------------------------
3780
3781       --  Note: some of the simple identifier cases were handled in par-prag,
3782       --  but it is harmless (and more straightforward) to simply handle all
3783       --  cases here, even if it means we repeat a bit of work in some cases.
3784
3785       procedure Process_Restrictions_Or_Restriction_Warnings
3786         (Warn : Boolean)
3787       is
3788          Arg   : Node_Id;
3789          R_Id  : Restriction_Id;
3790          Id    : Name_Id;
3791          Expr  : Node_Id;
3792          Val   : Uint;
3793
3794          procedure Check_Unit_Name (N : Node_Id);
3795          --  Checks unit name parameter for No_Dependence. Returns if it has
3796          --  an appropriate form, otherwise raises pragma argument error.
3797
3798          ---------------------
3799          -- Check_Unit_Name --
3800          ---------------------
3801
3802          procedure Check_Unit_Name (N : Node_Id) is
3803          begin
3804             if Nkind (N) = N_Selected_Component then
3805                Check_Unit_Name (Prefix (N));
3806                Check_Unit_Name (Selector_Name (N));
3807
3808             elsif Nkind (N) = N_Identifier then
3809                return;
3810
3811             else
3812                Error_Pragma_Arg
3813                  ("wrong form for unit name for No_Dependence", N);
3814             end if;
3815          end Check_Unit_Name;
3816
3817       --  Start of processing for Process_Restrictions_Or_Restriction_Warnings
3818
3819       begin
3820          Check_Ada_83_Warning;
3821          Check_At_Least_N_Arguments (1);
3822          Check_Valid_Configuration_Pragma;
3823
3824          Arg := Arg1;
3825          while Present (Arg) loop
3826             Id := Chars (Arg);
3827             Expr := Expression (Arg);
3828
3829             --  Case of no restriction identifier present
3830
3831             if Id = No_Name then
3832                if Nkind (Expr) /= N_Identifier then
3833                   Error_Pragma_Arg
3834                     ("invalid form for restriction", Arg);
3835                end if;
3836
3837                R_Id :=
3838                  Get_Restriction_Id
3839                    (Process_Restriction_Synonyms (Expr));
3840
3841                if R_Id not in All_Boolean_Restrictions then
3842                   Error_Pragma_Arg
3843                     ("invalid restriction identifier", Arg);
3844                end if;
3845
3846                if Implementation_Restriction (R_Id) then
3847                   Check_Restriction
3848                     (No_Implementation_Restrictions, Arg);
3849                end if;
3850
3851                --  If this is a warning, then set the warning unless we already
3852                --  have a real restriction active (we never want a warning to
3853                --  override a real restriction).
3854
3855                if Warn then
3856                   if not Restriction_Active (R_Id) then
3857                      Set_Restriction (R_Id, N);
3858                      Restriction_Warnings (R_Id) := True;
3859                   end if;
3860
3861                --  If real restriction case, then set it and make sure that the
3862                --  restriction warning flag is off, since a real restriction
3863                --  always overrides a warning.
3864
3865                else
3866                   Set_Restriction (R_Id, N);
3867                   Restriction_Warnings (R_Id) := False;
3868                end if;
3869
3870                --  A very special case that must be processed here: pragma
3871                --  Restrictions (No_Exceptions) turns off all run-time
3872                --  checking. This is a bit dubious in terms of the formal
3873                --  language definition, but it is what is intended by RM
3874                --  H.4(12). Restriction_Warnings never affects generated code
3875                --  so this is done only in the real restriction case.
3876
3877                if R_Id = No_Exceptions and then not Warn then
3878                   Scope_Suppress := (others => True);
3879                end if;
3880
3881             --  Case of No_Dependence => unit-name. Note that the parser
3882             --  already made the necessary entry in the No_Dependence table.
3883
3884             elsif Id = Name_No_Dependence then
3885                Check_Unit_Name (Expr);
3886
3887             --  All other cases of restriction identifier present
3888
3889             else
3890                R_Id := Get_Restriction_Id (Process_Restriction_Synonyms (Arg));
3891                Analyze_And_Resolve (Expr, Any_Integer);
3892
3893                if R_Id not in All_Parameter_Restrictions then
3894                   Error_Pragma_Arg
3895                     ("invalid restriction parameter identifier", Arg);
3896
3897                elsif not Is_OK_Static_Expression (Expr) then
3898                   Flag_Non_Static_Expr
3899                     ("value must be static expression!", Expr);
3900                   raise Pragma_Exit;
3901
3902                elsif not Is_Integer_Type (Etype (Expr))
3903                  or else Expr_Value (Expr) < 0
3904                then
3905                   Error_Pragma_Arg
3906                     ("value must be non-negative integer", Arg);
3907                end if;
3908
3909                --  Restriction pragma is active
3910
3911                Val := Expr_Value (Expr);
3912
3913                if not UI_Is_In_Int_Range (Val) then
3914                   Error_Pragma_Arg
3915                     ("pragma ignored, value too large?", Arg);
3916                end if;
3917
3918                --  Warning case. If the real restriction is active, then we
3919                --  ignore the request, since warning never overrides a real
3920                --  restriction. Otherwise we set the proper warning. Note that
3921                --  this circuit sets the warning again if it is already set,
3922                --  which is what we want, since the constant may have changed.
3923
3924                if Warn then
3925                   if not Restriction_Active (R_Id) then
3926                      Set_Restriction
3927                        (R_Id, N, Integer (UI_To_Int (Val)));
3928                      Restriction_Warnings (R_Id) := True;
3929                   end if;
3930
3931                --  Real restriction case, set restriction and make sure warning
3932                --  flag is off since real restriction always overrides warning.
3933
3934                else
3935                   Set_Restriction (R_Id, N, Integer (UI_To_Int (Val)));
3936                   Restriction_Warnings (R_Id) := False;
3937                end if;
3938             end if;
3939
3940             Next (Arg);
3941          end loop;
3942       end Process_Restrictions_Or_Restriction_Warnings;
3943
3944       ---------------------------------
3945       -- Process_Suppress_Unsuppress --
3946       ---------------------------------
3947
3948       --  Note: this procedure makes entries in the check suppress data
3949       --  structures managed by Sem. See spec of package Sem for full
3950       --  details on how we handle recording of check suppression.
3951
3952       procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean) is
3953          C    : Check_Id;
3954          E_Id : Node_Id;
3955          E    : Entity_Id;
3956
3957          In_Package_Spec : constant Boolean :=
3958                              (Ekind (Current_Scope) = E_Package
3959                                 or else
3960                               Ekind (Current_Scope) = E_Generic_Package)
3961                                and then not In_Package_Body (Current_Scope);
3962
3963          procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id);
3964          --  Used to suppress a single check on the given entity
3965
3966          --------------------------------
3967          -- Suppress_Unsuppress_Echeck --
3968          --------------------------------
3969
3970          procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id) is
3971          begin
3972             Set_Checks_May_Be_Suppressed (E);
3973
3974             if In_Package_Spec then
3975                Push_Global_Suppress_Stack_Entry
3976                  (Entity   => E,
3977                   Check    => C,
3978                   Suppress => Suppress_Case);
3979
3980             else
3981                Push_Local_Suppress_Stack_Entry
3982                  (Entity   => E,
3983                   Check    => C,
3984                   Suppress => Suppress_Case);
3985             end if;
3986
3987             --  If this is a first subtype, and the base type is distinct,
3988             --  then also set the suppress flags on the base type.
3989
3990             if Is_First_Subtype (E)
3991               and then Etype (E) /= E
3992             then
3993                Suppress_Unsuppress_Echeck (Etype (E), C);
3994             end if;
3995          end Suppress_Unsuppress_Echeck;
3996
3997       --  Start of processing for Process_Suppress_Unsuppress
3998
3999       begin
4000          --  Suppress/Unsuppress can appear as a configuration pragma,
4001          --  or in a declarative part or a package spec (RM 11.5(5))
4002
4003          if not Is_Configuration_Pragma then
4004             Check_Is_In_Decl_Part_Or_Package_Spec;
4005          end if;
4006
4007          Check_At_Least_N_Arguments (1);
4008          Check_At_Most_N_Arguments (2);
4009          Check_No_Identifier (Arg1);
4010          Check_Arg_Is_Identifier (Arg1);
4011
4012          C := Get_Check_Id (Chars (Expression (Arg1)));
4013
4014          if C = No_Check_Id then
4015             Error_Pragma_Arg
4016               ("argument of pragma% is not valid check name", Arg1);
4017          end if;
4018
4019          if not Suppress_Case
4020            and then (C = All_Checks or else C = Overflow_Check)
4021          then
4022             Opt.Overflow_Checks_Unsuppressed := True;
4023          end if;
4024
4025          if Arg_Count = 1 then
4026
4027             --  Make an entry in the local scope suppress table. This is the
4028             --  table that directly shows the current value of the scope
4029             --  suppress check for any check id value.
4030
4031             if C = All_Checks then
4032
4033                --  For All_Checks, we set all specific predefined checks with
4034                --  the exception of Elaboration_Check, which is handled
4035                --  specially because of not wanting All_Checks to have the
4036                --  effect of deactivating static elaboration order processing.
4037
4038                for J in Scope_Suppress'Range loop
4039                   if J /= Elaboration_Check then
4040                      Scope_Suppress (J) := Suppress_Case;
4041                   end if;
4042                end loop;
4043
4044             --  If not All_Checks, and predefined check, then set appropriate
4045             --  scope entry. Note that we will set Elaboration_Check if this
4046             --  is explicitly specified.
4047
4048             elsif C in Predefined_Check_Id then
4049                Scope_Suppress (C) := Suppress_Case;
4050             end if;
4051
4052             --  Also make an entry in the Local_Entity_Suppress table
4053
4054             Push_Local_Suppress_Stack_Entry
4055               (Entity   => Empty,
4056                Check    => C,
4057                Suppress => Suppress_Case);
4058
4059          --  Case of two arguments present, where the check is suppressed for
4060          --  a specified entity (given as the second argument of the pragma)
4061
4062          else
4063             Check_Optional_Identifier (Arg2, Name_On);
4064             E_Id := Expression (Arg2);
4065             Analyze (E_Id);
4066
4067             if not Is_Entity_Name (E_Id) then
4068                Error_Pragma_Arg
4069                  ("second argument of pragma% must be entity name", Arg2);
4070             end if;
4071
4072             E := Entity (E_Id);
4073
4074             if E = Any_Id then
4075                return;
4076             end if;
4077
4078             --  Enforce RM 11.5(7) which requires that for a pragma that
4079             --  appears within a package spec, the named entity must be
4080             --  within the package spec. We allow the package name itself
4081             --  to be mentioned since that makes sense, although it is not
4082             --  strictly allowed by 11.5(7).
4083
4084             if In_Package_Spec
4085               and then E /= Current_Scope
4086               and then Scope (E) /= Current_Scope
4087             then
4088                Error_Pragma_Arg
4089                  ("entity in pragma% is not in package spec (RM 11.5(7))",
4090                   Arg2);
4091             end if;
4092
4093             --  Loop through homonyms. As noted below, in the case of a package
4094             --  spec, only homonyms within the package spec are considered.
4095
4096             loop
4097                Suppress_Unsuppress_Echeck (E, C);
4098
4099                if Is_Generic_Instance (E)
4100                  and then Is_Subprogram (E)
4101                  and then Present (Alias (E))
4102                then
4103                   Suppress_Unsuppress_Echeck (Alias (E), C);
4104                end if;
4105
4106                --  Move to next homonym
4107
4108                E := Homonym (E);
4109                exit when No (E);
4110
4111                --  If we are within a package specification, the
4112                --  pragma only applies to homonyms in the same scope.
4113
4114                exit when In_Package_Spec
4115                  and then Scope (E) /= Current_Scope;
4116             end loop;
4117          end if;
4118       end Process_Suppress_Unsuppress;
4119
4120       ------------------
4121       -- Set_Exported --
4122       ------------------
4123
4124       procedure Set_Exported (E : Entity_Id; Arg : Node_Id) is
4125       begin
4126          if Is_Imported (E) then
4127             Error_Pragma_Arg
4128               ("cannot export entity& that was previously imported", Arg);
4129
4130          elsif Present (Address_Clause (E)) then
4131             Error_Pragma_Arg
4132               ("cannot export entity& that has an address clause", Arg);
4133          end if;
4134
4135          Set_Is_Exported (E);
4136
4137          --  Generate a reference for entity explicitly, because the
4138          --  identifier may be overloaded and name resolution will not
4139          --  generate one.
4140
4141          Generate_Reference (E, Arg);
4142
4143          --  Deal with exporting non-library level entity
4144
4145          if not Is_Library_Level_Entity (E) then
4146
4147             --  Not allowed at all for subprograms
4148
4149             if Is_Subprogram (E) then
4150                Error_Pragma_Arg ("local subprogram& cannot be exported", Arg);
4151
4152             --  Otherwise set public and statically allocated
4153
4154             else
4155                Set_Is_Public (E);
4156                Set_Is_Statically_Allocated (E);
4157
4158                --  Warn if the corresponding W flag is set and the pragma
4159                --  comes from source. The latter may not be true e.g. on
4160                --  VMS where we expand export pragmas for exception codes
4161                --  associated with imported or exported exceptions. We do
4162                --  not want to generate a warning for something that the
4163                --  user did not write.
4164
4165                if Warn_On_Export_Import
4166                  and then Comes_From_Source (Arg)
4167                then
4168                   Error_Msg_NE
4169                     ("?& has been made static as a result of Export", Arg, E);
4170                   Error_Msg_N
4171                     ("\this usage is non-standard and non-portable", Arg);
4172                end if;
4173             end if;
4174          end if;
4175
4176          if Warn_On_Export_Import and then Is_Type (E) then
4177             Error_Msg_NE
4178               ("exporting a type has no effect?", Arg, E);
4179          end if;
4180
4181          if Warn_On_Export_Import and Inside_A_Generic then
4182             Error_Msg_NE
4183               ("all instances of& will have the same external name?", Arg, E);
4184          end if;
4185       end Set_Exported;
4186
4187       ----------------------------------------------
4188       -- Set_Extended_Import_Export_External_Name --
4189       ----------------------------------------------
4190
4191       procedure Set_Extended_Import_Export_External_Name
4192         (Internal_Ent : Entity_Id;
4193          Arg_External : Node_Id)
4194       is
4195          Old_Name : constant Node_Id := Interface_Name (Internal_Ent);
4196          New_Name : Node_Id;
4197
4198       begin
4199          if No (Arg_External) then
4200             return;
4201          end if;
4202
4203          Check_Arg_Is_External_Name (Arg_External);
4204
4205          if Nkind (Arg_External) = N_String_Literal then
4206             if String_Length (Strval (Arg_External)) = 0 then
4207                return;
4208             else
4209                New_Name := Adjust_External_Name_Case (Arg_External);
4210             end if;
4211
4212          elsif Nkind (Arg_External) = N_Identifier then
4213             New_Name := Get_Default_External_Name (Arg_External);
4214
4215          --  Check_Arg_Is_External_Name should let through only
4216          --  identifiers and string literals or static string
4217          --  expressions (which are folded to string literals).
4218
4219          else
4220             raise Program_Error;
4221          end if;
4222
4223          --  If we already have an external name set (by a prior normal
4224          --  Import or Export pragma), then the external names must match
4225
4226          if Present (Interface_Name (Internal_Ent)) then
4227             Check_Matching_Internal_Names : declare
4228                S1 : constant String_Id := Strval (Old_Name);
4229                S2 : constant String_Id := Strval (New_Name);
4230
4231                procedure Mismatch;
4232                --  Called if names do not match
4233
4234                --------------
4235                -- Mismatch --
4236                --------------
4237
4238                procedure Mismatch is
4239                begin
4240                   Error_Msg_Sloc := Sloc (Old_Name);
4241                   Error_Pragma_Arg
4242                     ("external name does not match that given #",
4243                      Arg_External);
4244                end Mismatch;
4245
4246             --  Start of processing for Check_Matching_Internal_Names
4247
4248             begin
4249                if String_Length (S1) /= String_Length (S2) then
4250                   Mismatch;
4251
4252                else
4253                   for J in 1 .. String_Length (S1) loop
4254                      if Get_String_Char (S1, J) /= Get_String_Char (S2, J) then
4255                         Mismatch;
4256                      end if;
4257                   end loop;
4258                end if;
4259             end Check_Matching_Internal_Names;
4260
4261          --  Otherwise set the given name
4262
4263          else
4264             Set_Encoded_Interface_Name (Internal_Ent, New_Name);
4265             Check_Duplicated_Export_Name (New_Name);
4266          end if;
4267       end Set_Extended_Import_Export_External_Name;
4268
4269       ------------------
4270       -- Set_Imported --
4271       ------------------
4272
4273       procedure Set_Imported (E : Entity_Id) is
4274       begin
4275          --  Error message if already imported or exported
4276
4277          if Is_Exported (E) or else Is_Imported (E) then
4278             if Is_Exported (E) then
4279                Error_Msg_NE ("entity& was previously exported", N, E);
4280             else
4281                Error_Msg_NE ("entity& was previously imported", N, E);
4282             end if;
4283
4284             Error_Msg_Name_1 := Chars (N);
4285             Error_Msg_N
4286               ("\(pragma% applies to all previous entities)", N);
4287
4288             Error_Msg_Sloc  := Sloc (E);
4289             Error_Msg_NE ("\import not allowed for& declared#", N, E);
4290
4291          --  Here if not previously imported or exported, OK to import
4292
4293          else
4294             Set_Is_Imported (E);
4295
4296             --  If the entity is an object that is not at the library
4297             --  level, then it is statically allocated. We do not worry
4298             --  about objects with address clauses in this context since
4299             --  they are not really imported in the linker sense.
4300
4301             if Is_Object (E)
4302               and then not Is_Library_Level_Entity (E)
4303               and then No (Address_Clause (E))
4304             then
4305                Set_Is_Statically_Allocated (E);
4306             end if;
4307          end if;
4308       end Set_Imported;
4309
4310       -------------------------
4311       -- Set_Mechanism_Value --
4312       -------------------------
4313
4314       --  Note: the mechanism name has not been analyzed (and cannot indeed
4315       --  be analyzed, since it is semantic nonsense), so we get it in the
4316       --  exact form created by the parser.
4317
4318       procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id) is
4319          Class : Node_Id;
4320          Param : Node_Id;
4321
4322          procedure Bad_Class;
4323          --  Signal bad descriptor class name
4324
4325          procedure Bad_Mechanism;
4326          --  Signal bad mechanism name
4327
4328          ---------------
4329          -- Bad_Class --
4330          ---------------
4331
4332          procedure Bad_Class is
4333          begin
4334             Error_Pragma_Arg ("unrecognized descriptor class name", Class);
4335          end Bad_Class;
4336
4337          -------------------------
4338          -- Bad_Mechanism_Value --
4339          -------------------------
4340
4341          procedure Bad_Mechanism is
4342          begin
4343             Error_Pragma_Arg ("unrecognized mechanism name", Mech_Name);
4344          end Bad_Mechanism;
4345
4346       --  Start of processing for Set_Mechanism_Value
4347
4348       begin
4349          if Mechanism (Ent) /= Default_Mechanism then
4350             Error_Msg_NE
4351               ("mechanism for & has already been set", Mech_Name, Ent);
4352          end if;
4353
4354          --  MECHANISM_NAME ::= value | reference | descriptor
4355
4356          if Nkind (Mech_Name) = N_Identifier then
4357             if Chars (Mech_Name) = Name_Value then
4358                Set_Mechanism (Ent, By_Copy);
4359                return;
4360
4361             elsif Chars (Mech_Name) = Name_Reference then
4362                Set_Mechanism (Ent, By_Reference);
4363                return;
4364
4365             elsif Chars (Mech_Name) = Name_Descriptor then
4366                Check_VMS (Mech_Name);
4367                Set_Mechanism (Ent, By_Descriptor);
4368                return;
4369
4370             elsif Chars (Mech_Name) = Name_Copy then
4371                Error_Pragma_Arg
4372                  ("bad mechanism name, Value assumed", Mech_Name);
4373
4374             else
4375                Bad_Mechanism;
4376             end if;
4377
4378          --  MECHANISM_NAME ::= descriptor (CLASS_NAME)
4379          --  CLASS_NAME     ::= ubs | ubsb | uba | s | sb | a | nca
4380
4381          --  Note: this form is parsed as an indexed component
4382
4383          elsif Nkind (Mech_Name) = N_Indexed_Component then
4384             Class := First (Expressions (Mech_Name));
4385
4386             if Nkind (Prefix (Mech_Name)) /= N_Identifier
4387               or else Chars (Prefix (Mech_Name)) /= Name_Descriptor
4388               or else Present (Next (Class))
4389             then
4390                Bad_Mechanism;
4391             end if;
4392
4393          --  MECHANISM_NAME ::= descriptor (Class => CLASS_NAME)
4394          --  CLASS_NAME     ::= ubs | ubsb | uba | s | sb | a | nca
4395
4396          --  Note: this form is parsed as a function call
4397
4398          elsif Nkind (Mech_Name) = N_Function_Call then
4399
4400             Param := First (Parameter_Associations (Mech_Name));
4401
4402             if Nkind (Name (Mech_Name)) /= N_Identifier
4403               or else Chars (Name (Mech_Name)) /= Name_Descriptor
4404               or else Present (Next (Param))
4405               or else No (Selector_Name (Param))
4406               or else Chars (Selector_Name (Param)) /= Name_Class
4407             then
4408                Bad_Mechanism;
4409             else
4410                Class := Explicit_Actual_Parameter (Param);
4411             end if;
4412
4413          else
4414             Bad_Mechanism;
4415          end if;
4416
4417          --  Fall through here with Class set to descriptor class name
4418
4419          Check_VMS (Mech_Name);
4420
4421          if Nkind (Class) /= N_Identifier then
4422             Bad_Class;
4423
4424          elsif Chars (Class) = Name_UBS then
4425             Set_Mechanism (Ent, By_Descriptor_UBS);
4426
4427          elsif Chars (Class) = Name_UBSB then
4428             Set_Mechanism (Ent, By_Descriptor_UBSB);
4429
4430          elsif Chars (Class) = Name_UBA then
4431             Set_Mechanism (Ent, By_Descriptor_UBA);
4432
4433          elsif Chars (Class) = Name_S then
4434             Set_Mechanism (Ent, By_Descriptor_S);
4435
4436          elsif Chars (Class) = Name_SB then
4437             Set_Mechanism (Ent, By_Descriptor_SB);
4438
4439          elsif Chars (Class) = Name_A then
4440             Set_Mechanism (Ent, By_Descriptor_A);
4441
4442          elsif Chars (Class) = Name_NCA then
4443             Set_Mechanism (Ent, By_Descriptor_NCA);
4444
4445          else
4446             Bad_Class;
4447          end if;
4448       end Set_Mechanism_Value;
4449
4450       ---------------------------
4451       -- Set_Ravenscar_Profile --
4452       ---------------------------
4453
4454       --  The tasks to be done here are
4455
4456       --    Set required policies
4457
4458       --      pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
4459       --      pragma Locking_Policy (Ceiling_Locking)
4460
4461       --    Set Detect_Blocking mode
4462
4463       --    Set required restrictions (see System.Rident for detailed list)
4464
4465       procedure Set_Ravenscar_Profile (N : Node_Id) is
4466       begin
4467          --  pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
4468
4469          if Task_Dispatching_Policy /= ' '
4470            and then Task_Dispatching_Policy /= 'F'
4471          then
4472             Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
4473             Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
4474
4475          --  Set the FIFO_Within_Priorities policy, but always preserve
4476          --  System_Location since we like the error message with the run time
4477          --  name.
4478
4479          else
4480             Task_Dispatching_Policy := 'F';
4481
4482             if Task_Dispatching_Policy_Sloc /= System_Location then
4483                Task_Dispatching_Policy_Sloc := Loc;
4484             end if;
4485          end if;
4486
4487          --  pragma Locking_Policy (Ceiling_Locking)
4488
4489          if Locking_Policy /= ' '
4490            and then Locking_Policy /= 'C'
4491          then
4492             Error_Msg_Sloc := Locking_Policy_Sloc;
4493             Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
4494
4495          --  Set the Ceiling_Locking policy, but preserve System_Location since
4496          --  we like the error message with the run time name.
4497
4498          else
4499             Locking_Policy := 'C';
4500
4501             if Locking_Policy_Sloc /= System_Location then
4502                Locking_Policy_Sloc := Loc;
4503             end if;
4504          end if;
4505
4506          --  pragma Detect_Blocking
4507
4508          Detect_Blocking := True;
4509
4510          --  Set the corresponding restrictions
4511
4512          Set_Profile_Restrictions (Ravenscar, N, Warn => False);
4513       end Set_Ravenscar_Profile;
4514
4515    --  Start of processing for Analyze_Pragma
4516
4517    begin
4518       --  Deal with unrecognized pragma
4519
4520       if not Is_Pragma_Name (Chars (N)) then
4521          if Warn_On_Unrecognized_Pragma then
4522             Error_Msg_Name_1 := Chars (N);
4523             Error_Msg_N ("?unrecognized pragma%!", N);
4524
4525             for PN in First_Pragma_Name .. Last_Pragma_Name loop
4526                if Is_Bad_Spelling_Of
4527                  (Get_Name_String (Chars (N)),
4528                   Get_Name_String (PN))
4529                then
4530                   Error_Msg_Name_1 := PN;
4531                   Error_Msg_N ("\?possible misspelling of %!", N);
4532                   exit;
4533                end if;
4534             end loop;
4535          end if;
4536
4537          return;
4538       end if;
4539
4540       --  Here to start processing for recognized pragma
4541
4542       Prag_Id := Get_Pragma_Id (Chars (N));
4543
4544       --  Preset arguments
4545
4546       Arg1 := Empty;
4547       Arg2 := Empty;
4548       Arg3 := Empty;
4549       Arg4 := Empty;
4550
4551       if Present (Pragma_Argument_Associations (N)) then
4552          Arg1 := First (Pragma_Argument_Associations (N));
4553
4554          if Present (Arg1) then
4555             Arg2 := Next (Arg1);
4556
4557             if Present (Arg2) then
4558                Arg3 := Next (Arg2);
4559
4560                if Present (Arg3) then
4561                   Arg4 := Next (Arg3);
4562                end if;
4563             end if;
4564          end if;
4565       end if;
4566
4567       --  Count number of arguments
4568
4569       declare
4570          Arg_Node : Node_Id;
4571       begin
4572          Arg_Count := 0;
4573          Arg_Node := Arg1;
4574          while Present (Arg_Node) loop
4575             Arg_Count := Arg_Count + 1;
4576             Next (Arg_Node);
4577          end loop;
4578       end;
4579
4580       --  An enumeration type defines the pragmas that are supported by the
4581       --  implementation. Get_Pragma_Id (in package Prag) transorms a name
4582       --  into the corresponding enumeration value for the following case.
4583
4584       case Prag_Id is
4585
4586          -----------------
4587          -- Abort_Defer --
4588          -----------------
4589
4590          --  pragma Abort_Defer;
4591
4592          when Pragma_Abort_Defer =>
4593             GNAT_Pragma;
4594             Check_Arg_Count (0);
4595
4596             --  The only required semantic processing is to check the
4597             --  placement. This pragma must appear at the start of the
4598             --  statement sequence of a handled sequence of statements.
4599
4600             if Nkind (Parent (N)) /= N_Handled_Sequence_Of_Statements
4601               or else N /= First (Statements (Parent (N)))
4602             then
4603                Pragma_Misplaced;
4604             end if;
4605
4606          ------------
4607          -- Ada_83 --
4608          ------------
4609
4610          --  pragma Ada_83;
4611
4612          --  Note: this pragma also has some specific processing in Par.Prag
4613          --  because we want to set the Ada version mode during parsing.
4614
4615          when Pragma_Ada_83 =>
4616             GNAT_Pragma;
4617             Check_Arg_Count (0);
4618
4619             --  We really should check unconditionally for proper configuration
4620             --  pragma placement, since we really don't want mixed Ada modes
4621             --  within a single unit, and the GNAT reference manual has always
4622             --  said this was a configuration pragma, but we did not check and
4623             --  are hesitant to add the check now.
4624
4625             --  However, we really cannot tolerate mixing Ada 2005 with Ada 83
4626             --  or Ada 95, so we must check if we are in Ada 2005 mode.
4627
4628             if Ada_Version >= Ada_05 then
4629                Check_Valid_Configuration_Pragma;
4630             end if;
4631
4632             --  Now set Ada 83 mode
4633
4634             Ada_Version := Ada_83;
4635             Ada_Version_Explicit := Ada_Version;
4636
4637          ------------
4638          -- Ada_95 --
4639          ------------
4640
4641          --  pragma Ada_95;
4642
4643          --  Note: this pragma also has some specific processing in Par.Prag
4644          --  because we want to set the Ada 83 version mode during parsing.
4645
4646          when Pragma_Ada_95 =>
4647             GNAT_Pragma;
4648             Check_Arg_Count (0);
4649
4650             --  We really should check unconditionally for proper configuration
4651             --  pragma placement, since we really don't want mixed Ada modes
4652             --  within a single unit, and the GNAT reference manual has always
4653             --  said this was a configuration pragma, but we did not check and
4654             --  are hesitant to add the check now.
4655
4656             --  However, we really cannot tolerate mixing Ada 2005 with Ada 83
4657             --  or Ada 95, so we must check if we are in Ada 2005 mode.
4658
4659             if Ada_Version >= Ada_05 then
4660                Check_Valid_Configuration_Pragma;
4661             end if;
4662
4663             --  Now set Ada 95 mode
4664
4665             Ada_Version := Ada_95;
4666             Ada_Version_Explicit := Ada_Version;
4667
4668          ---------------------
4669          -- Ada_05/Ada_2005 --
4670          ---------------------
4671
4672          --  pragma Ada_05;
4673          --  pragma Ada_05 (LOCAL_NAME);
4674
4675          --  pragma Ada_2005;
4676          --  pragma Ada_2005 (LOCAL_NAME):
4677
4678          --  Note: these pragma also have some specific processing in Par.Prag
4679          --  because we want to set the Ada 2005 version mode during parsing.
4680
4681          when Pragma_Ada_05 | Pragma_Ada_2005 => declare
4682             E_Id : Node_Id;
4683
4684          begin
4685             GNAT_Pragma;
4686
4687             if Arg_Count = 1 then
4688                Check_Arg_Is_Local_Name (Arg1);
4689                E_Id := Expression (Arg1);
4690
4691                if Etype (E_Id) = Any_Type then
4692                   return;
4693                end if;
4694
4695                Set_Is_Ada_2005_Only (Entity (E_Id));
4696
4697             else
4698                Check_Arg_Count (0);
4699
4700                --  For Ada_2005 we unconditionally enforce the documented
4701                --  configuration pragma placement, since we do not want to
4702                --  tolerate mixed modes in a unit involving Ada 2005. That
4703                --  would cause real difficulties for those cases where there
4704                --  are incompatibilities between Ada 95 and Ada 2005.
4705
4706                Check_Valid_Configuration_Pragma;
4707
4708                --  Now set Ada 2005 mode
4709
4710                Ada_Version := Ada_05;
4711                Ada_Version_Explicit := Ada_05;
4712             end if;
4713          end;
4714
4715          ----------------------
4716          -- All_Calls_Remote --
4717          ----------------------
4718
4719          --  pragma All_Calls_Remote [(library_package_NAME)];
4720
4721          when Pragma_All_Calls_Remote => All_Calls_Remote : declare
4722             Lib_Entity : Entity_Id;
4723
4724          begin
4725             Check_Ada_83_Warning;
4726             Check_Valid_Library_Unit_Pragma;
4727
4728             if Nkind (N) = N_Null_Statement then
4729                return;
4730             end if;
4731
4732             Lib_Entity := Find_Lib_Unit_Name;
4733
4734             --  This pragma should only apply to a RCI unit (RM E.2.3(23))
4735
4736             if Present (Lib_Entity)
4737               and then not Debug_Flag_U
4738             then
4739                if not Is_Remote_Call_Interface (Lib_Entity) then
4740                   Error_Pragma ("pragma% only apply to rci unit");
4741
4742                --  Set flag for entity of the library unit
4743
4744                else
4745                   Set_Has_All_Calls_Remote (Lib_Entity);
4746                end if;
4747
4748             end if;
4749          end All_Calls_Remote;
4750
4751          --------------
4752          -- Annotate --
4753          --------------
4754
4755          --  pragma Annotate (IDENTIFIER {, ARG});
4756          --  ARG ::= NAME | EXPRESSION
4757
4758          when Pragma_Annotate => Annotate : begin
4759             GNAT_Pragma;
4760             Check_At_Least_N_Arguments (1);
4761             Check_Arg_Is_Identifier (Arg1);
4762
4763             declare
4764                Arg : Node_Id;
4765                Exp : Node_Id;
4766
4767             begin
4768                Arg := Arg2;
4769                while Present (Arg) loop
4770                   Exp := Expression (Arg);
4771                   Analyze (Exp);
4772
4773                   if Is_Entity_Name (Exp) then
4774                      null;
4775
4776                   elsif Nkind (Exp) = N_String_Literal then
4777                      Resolve (Exp, Standard_String);
4778
4779                   elsif Is_Overloaded (Exp) then
4780                      Error_Pragma_Arg ("ambiguous argument for pragma%", Exp);
4781
4782                   else
4783                      Resolve (Exp);
4784                   end if;
4785
4786                   Next (Arg);
4787                end loop;
4788             end;
4789          end Annotate;
4790
4791          ------------
4792          -- Assert --
4793          ------------
4794
4795          --  pragma Assert ([Check =>] Boolean_EXPRESSION
4796          --                 [, [Message =>] Static_String_EXPRESSION]);
4797
4798          when Pragma_Assert => Assert : declare
4799             Expr : Node_Id;
4800
4801          begin
4802             Ada_2005_Pragma;
4803             Check_At_Least_N_Arguments (1);
4804             Check_At_Most_N_Arguments (2);
4805             Check_Arg_Order ((Name_Check, Name_Message));
4806             Check_Optional_Identifier (Arg1, Name_Check);
4807
4808             if Arg_Count > 1 then
4809                Check_Optional_Identifier (Arg2, Name_Message);
4810                Check_Arg_Is_Static_Expression (Arg2, Standard_String);
4811             end if;
4812
4813             --  If expansion is active and assertions are inactive, then
4814             --  we rewrite the Assertion as:
4815
4816             --    if False and then condition then
4817             --       null;
4818             --    end if;
4819
4820             --  The reason we do this rewriting during semantic analysis
4821             --  rather than as part of normal expansion is that we cannot
4822             --  analyze and expand the code for the boolean expression
4823             --  directly, or it may cause insertion of actions that would
4824             --  escape the attempt to suppress the assertion code.
4825
4826             Expr := Expression (Arg1);
4827
4828             if Expander_Active and not Assertions_Enabled then
4829                Rewrite (N,
4830                  Make_If_Statement (Loc,
4831                    Condition =>
4832                      Make_And_Then (Loc,
4833                        Left_Opnd  => New_Occurrence_Of (Standard_False, Loc),
4834                        Right_Opnd => Expr),
4835                    Then_Statements => New_List (
4836                      Make_Null_Statement (Loc))));
4837
4838                Analyze (N);
4839
4840             --  Otherwise (if assertions are enabled, or if we are not
4841             --  operating with expansion active), then we just analyze
4842             --  and resolve the expression.
4843
4844             else
4845                Analyze_And_Resolve (Expr, Any_Boolean);
4846             end if;
4847
4848             --  If assertion is of the form (X'First = literal), where X is
4849             --  formal parameter, then set Low_Bound_Known flag on this formal.
4850
4851             if Nkind (Expr) = N_Op_Eq then
4852                declare
4853                   Right : constant Node_Id := Right_Opnd (Expr);
4854                   Left  : constant Node_Id := Left_Opnd  (Expr);
4855                begin
4856                   if Nkind (Left) = N_Attribute_Reference
4857                     and then Attribute_Name (Left) = Name_First
4858                     and then Is_Entity_Name (Prefix (Left))
4859                     and then Is_Formal (Entity (Prefix (Left)))
4860                     and then Nkind (Right) = N_Integer_Literal
4861                   then
4862                      Set_Low_Bound_Known (Entity (Prefix (Left)));
4863                   end if;
4864                end;
4865             end if;
4866          end Assert;
4867
4868          ----------------------
4869          -- Assertion_Policy --
4870          ----------------------
4871
4872          --  pragma Assertion_Policy (Check | Ignore)
4873
4874          when Pragma_Assertion_Policy =>
4875             Ada_2005_Pragma;
4876             Check_Arg_Count (1);
4877             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Ignore);
4878             Assertions_Enabled := Chars (Expression (Arg1)) = Name_Check;
4879
4880          ---------------
4881          -- AST_Entry --
4882          ---------------
4883
4884          --  pragma AST_Entry (entry_IDENTIFIER);
4885
4886          when Pragma_AST_Entry => AST_Entry : declare
4887             Ent : Node_Id;
4888
4889          begin
4890             GNAT_Pragma;
4891             Check_VMS (N);
4892             Check_Arg_Count (1);
4893             Check_No_Identifiers;
4894             Check_Arg_Is_Local_Name (Arg1);
4895             Ent := Entity (Expression (Arg1));
4896
4897             --  Note: the implementation of the AST_Entry pragma could handle
4898             --  the entry family case fine, but for now we are consistent with
4899             --  the DEC rules, and do not allow the pragma, which of course
4900             --  has the effect of also forbidding the attribute.
4901
4902             if Ekind (Ent) /= E_Entry then
4903                Error_Pragma_Arg
4904                  ("pragma% argument must be simple entry name", Arg1);
4905
4906             elsif Is_AST_Entry (Ent) then
4907                Error_Pragma_Arg
4908                  ("duplicate % pragma for entry", Arg1);
4909
4910             elsif Has_Homonym (Ent) then
4911                Error_Pragma_Arg
4912                  ("pragma% argument cannot specify overloaded entry", Arg1);
4913
4914             else
4915                declare
4916                   FF : constant Entity_Id := First_Formal (Ent);
4917
4918                begin
4919                   if Present (FF) then
4920                      if Present (Next_Formal (FF)) then
4921                         Error_Pragma_Arg
4922                           ("entry for pragma% can have only one argument",
4923                            Arg1);
4924
4925                      elsif Parameter_Mode (FF) /= E_In_Parameter then
4926                         Error_Pragma_Arg
4927                           ("entry parameter for pragma% must have mode IN",
4928                            Arg1);
4929                      end if;
4930                   end if;
4931                end;
4932
4933                Set_Is_AST_Entry (Ent);
4934             end if;
4935          end AST_Entry;
4936
4937          ------------------
4938          -- Asynchronous --
4939          ------------------
4940
4941          --  pragma Asynchronous (LOCAL_NAME);
4942
4943          when Pragma_Asynchronous => Asynchronous : declare
4944             Nm     : Entity_Id;
4945             C_Ent  : Entity_Id;
4946             L      : List_Id;
4947             S      : Node_Id;
4948             N      : Node_Id;
4949             Formal : Entity_Id;
4950
4951             procedure Process_Async_Pragma;
4952             --  Common processing for procedure and access-to-procedure case
4953
4954             --------------------------
4955             -- Process_Async_Pragma --
4956             --------------------------
4957
4958             procedure Process_Async_Pragma is
4959             begin
4960                if No (L) then
4961                   Set_Is_Asynchronous (Nm);
4962                   return;
4963                end if;
4964
4965                --  The formals should be of mode IN (RM E.4.1(6))
4966
4967                S := First (L);
4968                while Present (S) loop
4969                   Formal := Defining_Identifier (S);
4970
4971                   if Nkind (Formal) = N_Defining_Identifier
4972                     and then Ekind (Formal) /= E_In_Parameter
4973                   then
4974                      Error_Pragma_Arg
4975                        ("pragma% procedure can only have IN parameter",
4976                         Arg1);
4977                   end if;
4978
4979                   Next (S);
4980                end loop;
4981
4982                Set_Is_Asynchronous (Nm);
4983             end Process_Async_Pragma;
4984
4985          --  Start of processing for pragma Asynchronous
4986
4987          begin
4988             Check_Ada_83_Warning;
4989             Check_No_Identifiers;
4990             Check_Arg_Count (1);
4991             Check_Arg_Is_Local_Name (Arg1);
4992
4993             if Debug_Flag_U then
4994                return;
4995             end if;
4996
4997             C_Ent := Cunit_Entity (Current_Sem_Unit);
4998             Analyze (Expression (Arg1));
4999             Nm := Entity (Expression (Arg1));
5000
5001             if not Is_Remote_Call_Interface (C_Ent)
5002               and then not Is_Remote_Types (C_Ent)
5003             then
5004                --  This pragma should only appear in an RCI or Remote Types
5005                --  unit (RM E.4.1(4))
5006
5007                Error_Pragma
5008                  ("pragma% not in Remote_Call_Interface or " &
5009                   "Remote_Types unit");
5010             end if;
5011
5012             if Ekind (Nm) = E_Procedure
5013               and then Nkind (Parent (Nm)) = N_Procedure_Specification
5014             then
5015                if not Is_Remote_Call_Interface (Nm) then
5016                   Error_Pragma_Arg
5017                     ("pragma% cannot be applied on non-remote procedure",
5018                      Arg1);
5019                end if;
5020
5021                L := Parameter_Specifications (Parent (Nm));
5022                Process_Async_Pragma;
5023                return;
5024
5025             elsif Ekind (Nm) = E_Function then
5026                Error_Pragma_Arg
5027                  ("pragma% cannot be applied to function", Arg1);
5028
5029             elsif Is_Remote_Access_To_Subprogram_Type (Nm) then
5030
5031                if Is_Record_Type (Nm) then
5032                   --  A record type that is the Equivalent_Type for
5033                   --  a remote access-to-subprogram type.
5034
5035                   N := Declaration_Node (Corresponding_Remote_Type (Nm));
5036
5037                else
5038                   --  A non-expanded RAS type (case where distribution is
5039                   --  not enabled).
5040
5041                   N := Declaration_Node (Nm);
5042                end if;
5043
5044                if Nkind (N) = N_Full_Type_Declaration
5045                  and then Nkind (Type_Definition (N)) =
5046                                      N_Access_Procedure_Definition
5047                then
5048                   L := Parameter_Specifications (Type_Definition (N));
5049                   Process_Async_Pragma;
5050
5051                   if Is_Asynchronous (Nm)
5052                     and then Expander_Active
5053                     and then Get_PCS_Name /= Name_No_DSA
5054                   then
5055                      RACW_Type_Is_Asynchronous (Underlying_RACW_Type (Nm));
5056                   end if;
5057
5058                else
5059                   Error_Pragma_Arg
5060                     ("pragma% cannot reference access-to-function type",
5061                     Arg1);
5062                end if;
5063
5064             --  Only other possibility is Access-to-class-wide type
5065
5066             elsif Is_Access_Type (Nm)
5067               and then Is_Class_Wide_Type (Designated_Type (Nm))
5068             then
5069                Check_First_Subtype (Arg1);
5070                Set_Is_Asynchronous (Nm);
5071                if Expander_Active then
5072                   RACW_Type_Is_Asynchronous (Nm);
5073                end if;
5074
5075             else
5076                Error_Pragma_Arg ("inappropriate argument for pragma%", Arg1);
5077             end if;
5078          end Asynchronous;
5079
5080          ------------
5081          -- Atomic --
5082          ------------
5083
5084          --  pragma Atomic (LOCAL_NAME);
5085
5086          when Pragma_Atomic =>
5087             Process_Atomic_Shared_Volatile;
5088
5089          -----------------------
5090          -- Atomic_Components --
5091          -----------------------
5092
5093          --  pragma Atomic_Components (array_LOCAL_NAME);
5094
5095          --  This processing is shared by Volatile_Components
5096
5097          when Pragma_Atomic_Components   |
5098               Pragma_Volatile_Components =>
5099
5100          Atomic_Components : declare
5101             E_Id : Node_Id;
5102             E    : Entity_Id;
5103             D    : Node_Id;
5104             K    : Node_Kind;
5105
5106          begin
5107             Check_Ada_83_Warning;
5108             Check_No_Identifiers;
5109             Check_Arg_Count (1);
5110             Check_Arg_Is_Local_Name (Arg1);
5111             E_Id := Expression (Arg1);
5112
5113             if Etype (E_Id) = Any_Type then
5114                return;
5115             end if;
5116
5117             E := Entity (E_Id);
5118
5119             if Rep_Item_Too_Early (E, N)
5120                  or else
5121                Rep_Item_Too_Late (E, N)
5122             then
5123                return;
5124             end if;
5125
5126             D := Declaration_Node (E);
5127             K := Nkind (D);
5128
5129             if (K = N_Full_Type_Declaration and then Is_Array_Type (E))
5130               or else
5131                 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
5132                    and then Nkind (D) = N_Object_Declaration
5133                    and then Nkind (Object_Definition (D)) =
5134                                        N_Constrained_Array_Definition)
5135             then
5136                --  The flag is set on the object, or on the base type
5137
5138                if Nkind (D) /= N_Object_Declaration then
5139                   E := Base_Type (E);
5140                end if;
5141
5142                Set_Has_Volatile_Components (E);
5143
5144                if Prag_Id = Pragma_Atomic_Components then
5145                   Set_Has_Atomic_Components (E);
5146
5147                   if Is_Packed (E) then
5148                      Set_Is_Packed (E, False);
5149
5150                      Error_Pragma_Arg
5151                        ("?Pack canceled, cannot pack atomic components",
5152                         Arg1);
5153                   end if;
5154                end if;
5155
5156             else
5157                Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
5158             end if;
5159          end Atomic_Components;
5160
5161          --------------------
5162          -- Attach_Handler --
5163          --------------------
5164
5165          --  pragma Attach_Handler (handler_NAME, EXPRESSION);
5166
5167          when Pragma_Attach_Handler =>
5168             Check_Ada_83_Warning;
5169             Check_No_Identifiers;
5170             Check_Arg_Count (2);
5171
5172             if No_Run_Time_Mode then
5173                Error_Msg_CRT ("Attach_Handler pragma", N);
5174             else
5175                Check_Interrupt_Or_Attach_Handler;
5176
5177                --  The expression that designates the attribute may
5178                --  depend on a discriminant, and is therefore a per-
5179                --  object expression, to be expanded in the init proc.
5180                --  If expansion is enabled, perform semantic checks
5181                --  on a copy only.
5182
5183                if Expander_Active then
5184                   declare
5185                      Temp : constant Node_Id :=
5186                               New_Copy_Tree (Expression (Arg2));
5187                   begin
5188                      Set_Parent (Temp, N);
5189                      Pre_Analyze_And_Resolve (Temp, RTE (RE_Interrupt_ID));
5190                   end;
5191
5192                else
5193                   Analyze (Expression (Arg2));
5194                   Resolve (Expression (Arg2), RTE (RE_Interrupt_ID));
5195                end if;
5196
5197                Process_Interrupt_Or_Attach_Handler;
5198             end if;
5199
5200          --------------------
5201          -- C_Pass_By_Copy --
5202          --------------------
5203
5204          --  pragma C_Pass_By_Copy ([Max_Size =>] static_integer_EXPRESSION);
5205
5206          when Pragma_C_Pass_By_Copy => C_Pass_By_Copy : declare
5207             Arg : Node_Id;
5208             Val : Uint;
5209
5210          begin
5211             GNAT_Pragma;
5212             Check_Valid_Configuration_Pragma;
5213             Check_Arg_Count (1);
5214             Check_Optional_Identifier (Arg1, "max_size");
5215
5216             Arg := Expression (Arg1);
5217             Check_Arg_Is_Static_Expression (Arg, Any_Integer);
5218
5219             Val := Expr_Value (Arg);
5220
5221             if Val <= 0 then
5222                Error_Pragma_Arg
5223                  ("maximum size for pragma% must be positive", Arg1);
5224
5225             elsif UI_Is_In_Int_Range (Val) then
5226                Default_C_Record_Mechanism := UI_To_Int (Val);
5227
5228             --  If a giant value is given, Int'Last will do well enough.
5229             --  If sometime someone complains that a record larger than
5230             --  two gigabytes is not copied, we will worry about it then!
5231
5232             else
5233                Default_C_Record_Mechanism := Mechanism_Type'Last;
5234             end if;
5235          end C_Pass_By_Copy;
5236
5237          ----------------
5238          -- Check_Name --
5239          ----------------
5240
5241          --  pragma Check_Name (check_IDENTIFIER);
5242
5243          when Pragma_Check_Name =>
5244             Check_No_Identifiers;
5245             GNAT_Pragma;
5246             Check_Valid_Configuration_Pragma;
5247             Check_Arg_Count (1);
5248             Check_Arg_Is_Identifier (Arg1);
5249
5250             declare
5251                Nam : constant Name_Id := Chars (Expression (Arg1));
5252
5253             begin
5254                for J in Check_Names.First .. Check_Names.Last loop
5255                   if Check_Names.Table (J) = Nam then
5256                      return;
5257                   end if;
5258                end loop;
5259
5260                Check_Names.Append (Nam);
5261             end;
5262
5263          ---------------------
5264          -- CIL_Constructor --
5265          ---------------------
5266
5267          --  pragma CIL_Constructor ([Entity =>] LOCAL_NAME);
5268
5269          --  Processing for this pragma is shared with Java_Constructor
5270
5271          -------------
5272          -- Comment --
5273          -------------
5274
5275          --  pragma Comment (static_string_EXPRESSION)
5276
5277          --  Processing for pragma Comment shares the circuitry for
5278          --  pragma Ident. The only differences are that Ident enforces
5279          --  a limit of 31 characters on its argument, and also enforces
5280          --  limitations on placement for DEC compatibility. Pragma
5281          --  Comment shares neither of these restrictions.
5282
5283          -------------------
5284          -- Common_Object --
5285          -------------------
5286
5287          --  pragma Common_Object (
5288          --        [Internal =>] LOCAL_NAME,
5289          --     [, [External =>] EXTERNAL_SYMBOL]
5290          --     [, [Size     =>] EXTERNAL_SYMBOL]);
5291
5292          --  Processing for this pragma is shared with Psect_Object
5293
5294          ------------------------
5295          -- Compile_Time_Error --
5296          ------------------------
5297
5298          --  pragma Compile_Time_Error
5299          --    (boolean_EXPRESSION, static_string_EXPRESSION);
5300
5301          when Pragma_Compile_Time_Error =>
5302             Process_Compile_Time_Warning_Or_Error;
5303
5304          --------------------------
5305          -- Compile_Time_Warning --
5306          --------------------------
5307
5308          --  pragma Compile_Time_Warning
5309          --    (boolean_EXPRESSION, static_string_EXPRESSION);
5310
5311          when Pragma_Compile_Time_Warning =>
5312             Process_Compile_Time_Warning_Or_Error;
5313
5314          -----------------------------
5315          -- Complete_Representation --
5316          -----------------------------
5317
5318          --  pragma Complete_Representation;
5319
5320          when Pragma_Complete_Representation =>
5321             GNAT_Pragma;
5322             Check_Arg_Count (0);
5323
5324             if Nkind (Parent (N)) /= N_Record_Representation_Clause then
5325                Error_Pragma
5326                  ("pragma & must appear within record representation clause");
5327             end if;
5328
5329          ----------------------------
5330          -- Complex_Representation --
5331          ----------------------------
5332
5333          --  pragma Complex_Representation ([Entity =>] LOCAL_NAME);
5334
5335          when Pragma_Complex_Representation => Complex_Representation : declare
5336             E_Id : Entity_Id;
5337             E    : Entity_Id;
5338             Ent  : Entity_Id;
5339
5340          begin
5341             GNAT_Pragma;
5342             Check_Arg_Count (1);
5343             Check_Optional_Identifier (Arg1, Name_Entity);
5344             Check_Arg_Is_Local_Name (Arg1);
5345             E_Id := Expression (Arg1);
5346
5347             if Etype (E_Id) = Any_Type then
5348                return;
5349             end if;
5350
5351             E := Entity (E_Id);
5352
5353             if not Is_Record_Type (E) then
5354                Error_Pragma_Arg
5355                  ("argument for pragma% must be record type", Arg1);
5356             end if;
5357
5358             Ent := First_Entity (E);
5359
5360             if No (Ent)
5361               or else No (Next_Entity (Ent))
5362               or else Present (Next_Entity (Next_Entity (Ent)))
5363               or else not Is_Floating_Point_Type (Etype (Ent))
5364               or else Etype (Ent) /= Etype (Next_Entity (Ent))
5365             then
5366                Error_Pragma_Arg
5367                  ("record for pragma% must have two fields of same fpt type",
5368                   Arg1);
5369
5370             else
5371                Set_Has_Complex_Representation (Base_Type (E));
5372
5373                --  We need to treat the type has having a non-standard
5374                --  representation, for back-end purposes, even though in
5375                --  general a complex will have the default representation
5376                --  of a record with two real components.
5377
5378                Set_Has_Non_Standard_Rep (Base_Type (E));
5379             end if;
5380          end Complex_Representation;
5381
5382          -------------------------
5383          -- Component_Alignment --
5384          -------------------------
5385
5386          --  pragma Component_Alignment (
5387          --        [Form =>] ALIGNMENT_CHOICE
5388          --     [, [Name =>] type_LOCAL_NAME]);
5389          --
5390          --   ALIGNMENT_CHOICE ::=
5391          --     Component_Size
5392          --   | Component_Size_4
5393          --   | Storage_Unit
5394          --   | Default
5395
5396          when Pragma_Component_Alignment => Component_AlignmentP : declare
5397             Args  : Args_List (1 .. 2);
5398             Names : constant Name_List (1 .. 2) := (
5399                       Name_Form,
5400                       Name_Name);
5401
5402             Form  : Node_Id renames Args (1);
5403             Name  : Node_Id renames Args (2);
5404
5405             Atype : Component_Alignment_Kind;
5406             Typ   : Entity_Id;
5407
5408          begin
5409             GNAT_Pragma;
5410             Gather_Associations (Names, Args);
5411
5412             if No (Form) then
5413                Error_Pragma ("missing Form argument for pragma%");
5414             end if;
5415
5416             Check_Arg_Is_Identifier (Form);
5417
5418             --  Get proper alignment, note that Default = Component_Size
5419             --  on all machines we have so far, and we want to set this
5420             --  value rather than the default value to indicate that it
5421             --  has been explicitly set (and thus will not get overridden
5422             --  by the default component alignment for the current scope)
5423
5424             if Chars (Form) = Name_Component_Size then
5425                Atype := Calign_Component_Size;
5426
5427             elsif Chars (Form) = Name_Component_Size_4 then
5428                Atype := Calign_Component_Size_4;
5429
5430             elsif Chars (Form) = Name_Default then
5431                Atype := Calign_Component_Size;
5432
5433             elsif Chars (Form) = Name_Storage_Unit then
5434                Atype := Calign_Storage_Unit;
5435
5436             else
5437                Error_Pragma_Arg
5438                  ("invalid Form parameter for pragma%", Form);
5439             end if;
5440
5441             --  Case with no name, supplied, affects scope table entry
5442
5443             if No (Name) then
5444                Scope_Stack.Table
5445                  (Scope_Stack.Last).Component_Alignment_Default := Atype;
5446
5447             --  Case of name supplied
5448
5449             else
5450                Check_Arg_Is_Local_Name (Name);
5451                Find_Type (Name);
5452                Typ := Entity (Name);
5453
5454                if Typ = Any_Type
5455                  or else Rep_Item_Too_Early (Typ, N)
5456                then
5457                   return;
5458                else
5459                   Typ := Underlying_Type (Typ);
5460                end if;
5461
5462                if not Is_Record_Type (Typ)
5463                  and then not Is_Array_Type (Typ)
5464                then
5465                   Error_Pragma_Arg
5466                     ("Name parameter of pragma% must identify record or " &
5467                      "array type", Name);
5468                end if;
5469
5470                --  An explicit Component_Alignment pragma overrides an
5471                --  implicit pragma Pack, but not an explicit one.
5472
5473                if not Has_Pragma_Pack (Base_Type (Typ)) then
5474                   Set_Is_Packed (Base_Type (Typ), False);
5475                   Set_Component_Alignment (Base_Type (Typ), Atype);
5476                end if;
5477             end if;
5478          end Component_AlignmentP;
5479
5480          ----------------
5481          -- Controlled --
5482          ----------------
5483
5484          --  pragma Controlled (first_subtype_LOCAL_NAME);
5485
5486          when Pragma_Controlled => Controlled : declare
5487             Arg : Node_Id;
5488
5489          begin
5490             Check_No_Identifiers;
5491             Check_Arg_Count (1);
5492             Check_Arg_Is_Local_Name (Arg1);
5493             Arg := Expression (Arg1);
5494
5495             if not Is_Entity_Name (Arg)
5496               or else not Is_Access_Type (Entity (Arg))
5497             then
5498                Error_Pragma_Arg ("pragma% requires access type", Arg1);
5499             else
5500                Set_Has_Pragma_Controlled (Base_Type (Entity (Arg)));
5501             end if;
5502          end Controlled;
5503
5504          ----------------
5505          -- Convention --
5506          ----------------
5507
5508          --  pragma Convention ([Convention =>] convention_IDENTIFIER,
5509          --    [Entity =>] LOCAL_NAME);
5510
5511          when Pragma_Convention => Convention : declare
5512             C : Convention_Id;
5513             E : Entity_Id;
5514          begin
5515             Check_Arg_Order ((Name_Convention, Name_Entity));
5516             Check_Ada_83_Warning;
5517             Check_Arg_Count (2);
5518             Process_Convention (C, E);
5519          end Convention;
5520
5521          ---------------------------
5522          -- Convention_Identifier --
5523          ---------------------------
5524
5525          --  pragma Convention_Identifier ([Name =>] IDENTIFIER,
5526          --    [Convention =>] convention_IDENTIFIER);
5527
5528          when Pragma_Convention_Identifier => Convention_Identifier : declare
5529             Idnam : Name_Id;
5530             Cname : Name_Id;
5531
5532          begin
5533             GNAT_Pragma;
5534             Check_Arg_Order ((Name_Name, Name_Convention));
5535             Check_Arg_Count (2);
5536             Check_Optional_Identifier (Arg1, Name_Name);
5537             Check_Optional_Identifier (Arg2, Name_Convention);
5538             Check_Arg_Is_Identifier (Arg1);
5539             Check_Arg_Is_Identifier (Arg2);
5540             Idnam := Chars (Expression (Arg1));
5541             Cname := Chars (Expression (Arg2));
5542
5543             if Is_Convention_Name (Cname) then
5544                Record_Convention_Identifier
5545                  (Idnam, Get_Convention_Id (Cname));
5546             else
5547                Error_Pragma_Arg
5548                  ("second arg for % pragma must be convention", Arg2);
5549             end if;
5550          end Convention_Identifier;
5551
5552          ---------------
5553          -- CPP_Class --
5554          ---------------
5555
5556          --  pragma CPP_Class ([Entity =>] local_NAME)
5557
5558          when Pragma_CPP_Class => CPP_Class : declare
5559             Arg : Node_Id;
5560             Typ : Entity_Id;
5561
5562          begin
5563             if Warn_On_Obsolescent_Feature then
5564                Error_Msg_N
5565                  ("'G'N'A'T pragma cpp'_class is now obsolete; replace it" &
5566                   " by pragma import?", N);
5567             end if;
5568
5569             GNAT_Pragma;
5570             Check_Arg_Count (1);
5571             Check_Optional_Identifier (Arg1, Name_Entity);
5572             Check_Arg_Is_Local_Name (Arg1);
5573
5574             Arg := Expression (Arg1);
5575             Analyze (Arg);
5576
5577             if Etype (Arg) = Any_Type then
5578                return;
5579             end if;
5580
5581             if not Is_Entity_Name (Arg)
5582               or else not Is_Type (Entity (Arg))
5583             then
5584                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
5585             end if;
5586
5587             Typ := Entity (Arg);
5588
5589             if not Is_Tagged_Type (Typ) then
5590                Error_Pragma_Arg ("pragma% applicable to tagged types ", Arg1);
5591             end if;
5592
5593             --  Types treated as CPP classes are treated as limited, but we
5594             --  don't require them to be declared this way. A warning is issued
5595             --  to encourage the user to declare them as limited. This is not
5596             --  an error, for compatibility reasons, because these types have
5597             --  been supported this way for some time.
5598
5599             if not Is_Limited_Type (Typ) then
5600                Error_Msg_N
5601                  ("imported 'C'P'P type should be " &
5602                     "explicitly declared limited?",
5603                   Get_Pragma_Arg (Arg1));
5604                Error_Msg_N
5605                  ("\type will be considered limited",
5606                   Get_Pragma_Arg (Arg1));
5607             end if;
5608
5609             Set_Is_CPP_Class      (Typ);
5610             Set_Is_Limited_Record (Typ);
5611             Set_Convention        (Typ, Convention_CPP);
5612          end CPP_Class;
5613
5614          ---------------------
5615          -- CPP_Constructor --
5616          ---------------------
5617
5618          --  pragma CPP_Constructor ([Entity =>] LOCAL_NAME
5619          --    [, [External_Name =>] static_string_EXPRESSION ]
5620          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
5621
5622          when Pragma_CPP_Constructor => CPP_Constructor : declare
5623             Id     : Entity_Id;
5624             Def_Id : Entity_Id;
5625
5626          begin
5627             GNAT_Pragma;
5628             Check_At_Least_N_Arguments (1);
5629             Check_At_Most_N_Arguments (3);
5630             Check_Optional_Identifier (Arg1, Name_Entity);
5631             Check_Arg_Is_Local_Name (Arg1);
5632
5633             Id := Expression (Arg1);
5634             Find_Program_Unit_Name (Id);
5635
5636             --  If we did not find the name, we are done
5637
5638             if Etype (Id) = Any_Type then
5639                return;
5640             end if;
5641
5642             Def_Id := Entity (Id);
5643
5644             if Ekind (Def_Id) = E_Function
5645               and then Is_Class_Wide_Type (Etype (Def_Id))
5646               and then Is_CPP_Class (Etype (Etype (Def_Id)))
5647             then
5648                if Arg_Count >= 2 then
5649                   Set_Imported (Def_Id);
5650                   Set_Is_Public (Def_Id);
5651                   Process_Interface_Name (Def_Id, Arg2, Arg3);
5652                end if;
5653
5654                if No (Parameter_Specifications (Parent (Def_Id))) then
5655                   Set_Has_Completion (Def_Id);
5656                   Set_Is_Constructor (Def_Id);
5657                else
5658                   Error_Pragma_Arg
5659                     ("non-default constructors not implemented", Arg1);
5660                end if;
5661
5662             else
5663                Error_Pragma_Arg
5664                  ("pragma% requires function returning a 'C'P'P_Class type",
5665                    Arg1);
5666             end if;
5667          end CPP_Constructor;
5668
5669          -----------------
5670          -- CPP_Virtual --
5671          -----------------
5672
5673          when Pragma_CPP_Virtual => CPP_Virtual : declare
5674          begin
5675             if Warn_On_Obsolescent_Feature then
5676                Error_Msg_N
5677                  ("'G'N'A'T pragma cpp'_virtual is now obsolete and has " &
5678                   "no effect?", N);
5679             end if;
5680          end CPP_Virtual;
5681
5682          ----------------
5683          -- CPP_Vtable --
5684          ----------------
5685
5686          when Pragma_CPP_Vtable => CPP_Vtable : declare
5687          begin
5688             if Warn_On_Obsolescent_Feature then
5689                Error_Msg_N
5690                  ("'G'N'A'T pragma cpp'_vtable is now obsolete and has " &
5691                   "no effect?", N);
5692             end if;
5693          end CPP_Vtable;
5694
5695          -----------
5696          -- Debug --
5697          -----------
5698
5699          --  pragma Debug ([boolean_EXPRESSION,] PROCEDURE_CALL_STATEMENT);
5700
5701          when Pragma_Debug => Debug : declare
5702                Cond : Node_Id;
5703
5704          begin
5705             GNAT_Pragma;
5706
5707             Cond :=
5708               New_Occurrence_Of
5709                 (Boolean_Literals (Debug_Pragmas_Enabled and Expander_Active),
5710                  Loc);
5711
5712             if Arg_Count = 2 then
5713                Cond :=
5714                  Make_And_Then (Loc,
5715                    Left_Opnd   => Relocate_Node (Cond),
5716                    Right_Opnd  => Expression (Arg1));
5717             end if;
5718
5719             --  Rewrite into a conditional with an appropriate condition. We
5720             --  wrap the procedure call in a block so that overhead from e.g.
5721             --  use of the secondary stack does not generate execution overhead
5722             --  for suppressed conditions.
5723
5724             Rewrite (N, Make_Implicit_If_Statement (N,
5725               Condition => Cond,
5726                  Then_Statements => New_List (
5727                    Make_Block_Statement (Loc,
5728                      Handled_Statement_Sequence =>
5729                        Make_Handled_Sequence_Of_Statements (Loc,
5730                          Statements => New_List (
5731                            Relocate_Node (Debug_Statement (N))))))));
5732             Analyze (N);
5733          end Debug;
5734
5735          ------------------
5736          -- Debug_Policy --
5737          ------------------
5738
5739          --  pragma Debug_Policy (Check | Ignore)
5740
5741          when Pragma_Debug_Policy =>
5742             GNAT_Pragma;
5743             Check_Arg_Count (1);
5744             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Ignore);
5745             Debug_Pragmas_Enabled := Chars (Expression (Arg1)) = Name_Check;
5746
5747          ---------------------
5748          -- Detect_Blocking --
5749          ---------------------
5750
5751          --  pragma Detect_Blocking;
5752
5753          when Pragma_Detect_Blocking =>
5754             Ada_2005_Pragma;
5755             Check_Arg_Count (0);
5756             Check_Valid_Configuration_Pragma;
5757             Detect_Blocking := True;
5758
5759          -------------------
5760          -- Discard_Names --
5761          -------------------
5762
5763          --  pragma Discard_Names [([On =>] LOCAL_NAME)];
5764
5765          when Pragma_Discard_Names => Discard_Names : declare
5766             E_Id : Entity_Id;
5767             E    : Entity_Id;
5768
5769          begin
5770             Check_Ada_83_Warning;
5771
5772             --  Deal with configuration pragma case
5773
5774             if Arg_Count = 0 and then Is_Configuration_Pragma then
5775                Global_Discard_Names := True;
5776                return;
5777
5778             --  Otherwise, check correct appropriate context
5779
5780             else
5781                Check_Is_In_Decl_Part_Or_Package_Spec;
5782
5783                if Arg_Count = 0 then
5784
5785                   --  If there is no parameter, then from now on this pragma
5786                   --  applies to any enumeration, exception or tagged type
5787                   --  defined in the current declarative part, and recursively
5788                   --  to any nested scope.
5789
5790                   Set_Discard_Names (Current_Scope);
5791                   return;
5792
5793                else
5794                   Check_Arg_Count (1);
5795                   Check_Optional_Identifier (Arg1, Name_On);
5796                   Check_Arg_Is_Local_Name (Arg1);
5797                   E_Id := Expression (Arg1);
5798
5799                   if Etype (E_Id) = Any_Type then
5800                      return;
5801                   else
5802                      E := Entity (E_Id);
5803                   end if;
5804
5805                   if (Is_First_Subtype (E)
5806                        and then (Is_Enumeration_Type (E)
5807                                   or else Is_Tagged_Type (E)))
5808                     or else Ekind (E) = E_Exception
5809                   then
5810                      Set_Discard_Names (E);
5811                   else
5812                      Error_Pragma_Arg
5813                        ("inappropriate entity for pragma%", Arg1);
5814                   end if;
5815                end if;
5816             end if;
5817          end Discard_Names;
5818
5819          ---------------
5820          -- Elaborate --
5821          ---------------
5822
5823          --  pragma Elaborate (library_unit_NAME {, library_unit_NAME});
5824
5825          when Pragma_Elaborate => Elaborate : declare
5826             Arg   : Node_Id;
5827             Citem : Node_Id;
5828
5829          begin
5830             --  Pragma must be in context items list of a compilation unit
5831
5832             if not Is_In_Context_Clause then
5833                Pragma_Misplaced;
5834             end if;
5835
5836             --  Must be at least one argument
5837
5838             if Arg_Count = 0 then
5839                Error_Pragma ("pragma% requires at least one argument");
5840             end if;
5841
5842             --  In Ada 83 mode, there can be no items following it in the
5843             --  context list except other pragmas and implicit with clauses
5844             --  (e.g. those added by use of Rtsfind). In Ada 95 mode, this
5845             --  placement rule does not apply.
5846
5847             if Ada_Version = Ada_83 and then Comes_From_Source (N) then
5848                Citem := Next (N);
5849                while Present (Citem) loop
5850                   if Nkind (Citem) = N_Pragma
5851                     or else (Nkind (Citem) = N_With_Clause
5852                               and then Implicit_With (Citem))
5853                   then
5854                      null;
5855                   else
5856                      Error_Pragma
5857                        ("(Ada 83) pragma% must be at end of context clause");
5858                   end if;
5859
5860                   Next (Citem);
5861                end loop;
5862             end if;
5863
5864             --  Finally, the arguments must all be units mentioned in a with
5865             --  clause in the same context clause. Note we already checked (in
5866             --  Par.Prag) that the arguments are all identifiers or selected
5867             --  components.
5868
5869             Arg := Arg1;
5870             Outer : while Present (Arg) loop
5871                Citem := First (List_Containing (N));
5872                Inner : while Citem /= N loop
5873                   if Nkind (Citem) = N_With_Clause
5874                     and then Same_Name (Name (Citem), Expression (Arg))
5875                   then
5876                      Set_Elaborate_Present (Citem, True);
5877                      Set_Unit_Name (Expression (Arg), Name (Citem));
5878
5879                      --  With the pragma present, elaboration calls on
5880                      --  subprograms from the named unit need no further
5881                      --  checks, as long as the pragma appears in the current
5882                      --  compilation unit. If the pragma appears in some unit
5883                      --  in the context, there might still be a need for an
5884                      --  Elaborate_All_Desirable from the current compilation
5885                      --  to the the named unit, so we keep the check enabled.
5886
5887                      if In_Extended_Main_Source_Unit (N) then
5888                         Set_Suppress_Elaboration_Warnings
5889                           (Entity (Name (Citem)));
5890                      end if;
5891
5892                      exit Inner;
5893                   end if;
5894
5895                   Next (Citem);
5896                end loop Inner;
5897
5898                if Citem = N then
5899                   Error_Pragma_Arg
5900                     ("argument of pragma% is not with'ed unit", Arg);
5901                end if;
5902
5903                Next (Arg);
5904             end loop Outer;
5905
5906             --  Give a warning if operating in static mode with -gnatwl
5907             --  (elaboration warnings eanbled) switch set.
5908
5909             if Elab_Warnings and not Dynamic_Elaboration_Checks then
5910                Error_Msg_N
5911                  ("?use of pragma Elaborate may not be safe", N);
5912                Error_Msg_N
5913                  ("?use pragma Elaborate_All instead if possible", N);
5914             end if;
5915          end Elaborate;
5916
5917          -------------------
5918          -- Elaborate_All --
5919          -------------------
5920
5921          --  pragma Elaborate_All (library_unit_NAME {, library_unit_NAME});
5922
5923          when Pragma_Elaborate_All => Elaborate_All : declare
5924             Arg   : Node_Id;
5925             Citem : Node_Id;
5926
5927          begin
5928             Check_Ada_83_Warning;
5929
5930             --  Pragma must be in context items list of a compilation unit
5931
5932             if not Is_In_Context_Clause then
5933                Pragma_Misplaced;
5934             end if;
5935
5936             --  Must be at least one argument
5937
5938             if Arg_Count = 0 then
5939                Error_Pragma ("pragma% requires at least one argument");
5940             end if;
5941
5942             --  Note: unlike pragma Elaborate, pragma Elaborate_All does not
5943             --  have to appear at the end of the context clause, but may
5944             --  appear mixed in with other items, even in Ada 83 mode.
5945
5946             --  Final check: the arguments must all be units mentioned in
5947             --  a with clause in the same context clause. Note that we
5948             --  already checked (in Par.Prag) that all the arguments are
5949             --  either identifiers or selected components.
5950
5951             Arg := Arg1;
5952             Outr : while Present (Arg) loop
5953                Citem := First (List_Containing (N));
5954                Innr : while Citem /= N loop
5955                   if Nkind (Citem) = N_With_Clause
5956                     and then Same_Name (Name (Citem), Expression (Arg))
5957                   then
5958                      Set_Elaborate_All_Present (Citem, True);
5959                      Set_Unit_Name (Expression (Arg), Name (Citem));
5960
5961                      --  Suppress warnings and elaboration checks on the named
5962                      --  unit if the pragma is in the current compilation, as
5963                      --  for pragma Elaborate.
5964
5965                      if In_Extended_Main_Source_Unit (N) then
5966                         Set_Suppress_Elaboration_Warnings
5967                           (Entity (Name (Citem)));
5968                      end if;
5969                      exit Innr;
5970                   end if;
5971
5972                   Next (Citem);
5973                end loop Innr;
5974
5975                if Citem = N then
5976                   Set_Error_Posted (N);
5977                   Error_Pragma_Arg
5978                     ("argument of pragma% is not with'ed unit", Arg);
5979                end if;
5980
5981                Next (Arg);
5982             end loop Outr;
5983          end Elaborate_All;
5984
5985          --------------------
5986          -- Elaborate_Body --
5987          --------------------
5988
5989          --  pragma Elaborate_Body [( library_unit_NAME )];
5990
5991          when Pragma_Elaborate_Body => Elaborate_Body : declare
5992             Cunit_Node : Node_Id;
5993             Cunit_Ent  : Entity_Id;
5994
5995          begin
5996             Check_Ada_83_Warning;
5997             Check_Valid_Library_Unit_Pragma;
5998
5999             if Nkind (N) = N_Null_Statement then
6000                return;
6001             end if;
6002
6003             Cunit_Node := Cunit (Current_Sem_Unit);
6004             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
6005
6006             if Nkind (Unit (Cunit_Node)) = N_Package_Body
6007                  or else
6008                Nkind (Unit (Cunit_Node)) = N_Subprogram_Body
6009             then
6010                Error_Pragma ("pragma% must refer to a spec, not a body");
6011             else
6012                Set_Body_Required (Cunit_Node, True);
6013                Set_Has_Pragma_Elaborate_Body (Cunit_Ent);
6014
6015                --  If we are in dynamic elaboration mode, then we suppress
6016                --  elaboration warnings for the unit, since it is definitely
6017                --  fine NOT to do dynamic checks at the first level (and such
6018                --  checks will be suppressed because no elaboration boolean
6019                --  is created for Elaborate_Body packages).
6020
6021                --  But in the static model of elaboration, Elaborate_Body is
6022                --  definitely NOT good enough to ensure elaboration safety on
6023                --  its own, since the body may WITH other units that are not
6024                --  safe from an elaboration point of view, so a client must
6025                --  still do an Elaborate_All on such units.
6026
6027                --  Debug flag -gnatdD restores the old behavior of 3.13,
6028                --  where Elaborate_Body always suppressed elab warnings.
6029
6030                if Dynamic_Elaboration_Checks or Debug_Flag_DD then
6031                   Set_Suppress_Elaboration_Warnings (Cunit_Ent);
6032                end if;
6033             end if;
6034          end Elaborate_Body;
6035
6036          ------------------------
6037          -- Elaboration_Checks --
6038          ------------------------
6039
6040          --  pragma Elaboration_Checks (Static | Dynamic);
6041
6042          when Pragma_Elaboration_Checks =>
6043             GNAT_Pragma;
6044             Check_Arg_Count (1);
6045             Check_Arg_Is_One_Of (Arg1, Name_Static, Name_Dynamic);
6046             Dynamic_Elaboration_Checks :=
6047               (Chars (Get_Pragma_Arg (Arg1)) = Name_Dynamic);
6048
6049          ---------------
6050          -- Eliminate --
6051          ---------------
6052
6053          --  pragma Eliminate (
6054          --      [Unit_Name       =>]  IDENTIFIER |
6055          --                            SELECTED_COMPONENT
6056          --    [,[Entity          =>]  IDENTIFIER |
6057          --                            SELECTED_COMPONENT |
6058          --                            STRING_LITERAL]
6059          --    [,]OVERLOADING_RESOLUTION);
6060
6061          --  OVERLOADING_RESOLUTION ::= PARAMETER_AND_RESULT_TYPE_PROFILE |
6062          --                             SOURCE_LOCATION
6063
6064          --  PARAMETER_AND_RESULT_TYPE_PROFILE ::= PROCEDURE_PROFILE |
6065          --                                        FUNCTION_PROFILE
6066
6067          --  PROCEDURE_PROFILE ::= Parameter_Types => PARAMETER_TYPES
6068
6069          --  FUNCTION_PROFILE ::= [Parameter_Types => PARAMETER_TYPES,]
6070          --                       Result_Type => result_SUBTYPE_NAME]
6071
6072          --  PARAMETER_TYPES ::= (SUBTYPE_NAME {, SUBTYPE_NAME})
6073          --  SUBTYPE_NAME    ::= STRING_LITERAL
6074
6075          --  SOURCE_LOCATION ::= Source_Location => SOURCE_TRACE
6076          --  SOURCE_TRACE    ::= STRING_LITERAL
6077
6078          when Pragma_Eliminate => Eliminate : declare
6079             Args  : Args_List (1 .. 5);
6080             Names : constant Name_List (1 .. 5) := (
6081                       Name_Unit_Name,
6082                       Name_Entity,
6083                       Name_Parameter_Types,
6084                       Name_Result_Type,
6085                       Name_Source_Location);
6086
6087             Unit_Name       : Node_Id renames Args (1);
6088             Entity          : Node_Id renames Args (2);
6089             Parameter_Types : Node_Id renames Args (3);
6090             Result_Type     : Node_Id renames Args (4);
6091             Source_Location : Node_Id renames Args (5);
6092
6093          begin
6094             GNAT_Pragma;
6095             Check_Valid_Configuration_Pragma;
6096             Gather_Associations (Names, Args);
6097
6098             if No (Unit_Name) then
6099                Error_Pragma ("missing Unit_Name argument for pragma%");
6100             end if;
6101
6102             if No (Entity)
6103               and then (Present (Parameter_Types)
6104                           or else
6105                         Present (Result_Type)
6106                           or else
6107                         Present (Source_Location))
6108             then
6109                Error_Pragma ("missing Entity argument for pragma%");
6110             end if;
6111
6112             if (Present (Parameter_Types)
6113                        or else
6114                 Present (Result_Type))
6115               and then
6116                 Present (Source_Location)
6117             then
6118                Error_Pragma
6119                  ("parameter profile and source location cannot " &
6120                   "be used together in pragma%");
6121             end if;
6122
6123             Process_Eliminate_Pragma
6124               (N,
6125                Unit_Name,
6126                Entity,
6127                Parameter_Types,
6128                Result_Type,
6129                Source_Location);
6130          end Eliminate;
6131
6132          ------------
6133          -- Export --
6134          ------------
6135
6136          --  pragma Export (
6137          --    [   Convention    =>] convention_IDENTIFIER,
6138          --    [   Entity        =>] local_NAME
6139          --    [, [External_Name =>] static_string_EXPRESSION ]
6140          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
6141
6142          when Pragma_Export => Export : declare
6143             C      : Convention_Id;
6144             Def_Id : Entity_Id;
6145
6146          begin
6147             Check_Ada_83_Warning;
6148             Check_Arg_Order
6149               ((Name_Convention,
6150                 Name_Entity,
6151                 Name_External_Name,
6152                 Name_Link_Name));
6153             Check_At_Least_N_Arguments (2);
6154             Check_At_Most_N_Arguments  (4);
6155             Process_Convention (C, Def_Id);
6156
6157             if Ekind (Def_Id) /= E_Constant then
6158                Note_Possible_Modification (Expression (Arg2));
6159             end if;
6160
6161             Process_Interface_Name (Def_Id, Arg3, Arg4);
6162             Set_Exported (Def_Id, Arg2);
6163          end Export;
6164
6165          ----------------------
6166          -- Export_Exception --
6167          ----------------------
6168
6169          --  pragma Export_Exception (
6170          --        [Internal         =>] LOCAL_NAME,
6171          --     [, [External         =>] EXTERNAL_SYMBOL,]
6172          --     [, [Form     =>] Ada | VMS]
6173          --     [, [Code     =>] static_integer_EXPRESSION]);
6174
6175          when Pragma_Export_Exception => Export_Exception : declare
6176             Args  : Args_List (1 .. 4);
6177             Names : constant Name_List (1 .. 4) := (
6178                       Name_Internal,
6179                       Name_External,
6180                       Name_Form,
6181                       Name_Code);
6182
6183             Internal : Node_Id renames Args (1);
6184             External : Node_Id renames Args (2);
6185             Form     : Node_Id renames Args (3);
6186             Code     : Node_Id renames Args (4);
6187
6188          begin
6189             if Inside_A_Generic then
6190                Error_Pragma ("pragma% cannot be used for generic entities");
6191             end if;
6192
6193             Gather_Associations (Names, Args);
6194             Process_Extended_Import_Export_Exception_Pragma (
6195               Arg_Internal => Internal,
6196               Arg_External => External,
6197               Arg_Form     => Form,
6198               Arg_Code     => Code);
6199
6200             if not Is_VMS_Exception (Entity (Internal)) then
6201                Set_Exported (Entity (Internal), Internal);
6202             end if;
6203          end Export_Exception;
6204
6205          ---------------------
6206          -- Export_Function --
6207          ---------------------
6208
6209          --  pragma Export_Function (
6210          --        [Internal         =>] LOCAL_NAME,
6211          --     [, [External         =>] EXTERNAL_SYMBOL,]
6212          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
6213          --     [, [Result_Type      =>] TYPE_DESIGNATOR]
6214          --     [, [Mechanism        =>] MECHANISM]
6215          --     [, [Result_Mechanism =>] MECHANISM_NAME]);
6216
6217          --  EXTERNAL_SYMBOL ::=
6218          --    IDENTIFIER
6219          --  | static_string_EXPRESSION
6220
6221          --  PARAMETER_TYPES ::=
6222          --    null
6223          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
6224
6225          --  TYPE_DESIGNATOR ::=
6226          --    subtype_NAME
6227          --  | subtype_Name ' Access
6228
6229          --  MECHANISM ::=
6230          --    MECHANISM_NAME
6231          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
6232
6233          --  MECHANISM_ASSOCIATION ::=
6234          --    [formal_parameter_NAME =>] MECHANISM_NAME
6235
6236          --  MECHANISM_NAME ::=
6237          --    Value
6238          --  | Reference
6239          --  | Descriptor [([Class =>] CLASS_NAME)]
6240
6241          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
6242
6243          when Pragma_Export_Function => Export_Function : declare
6244             Args  : Args_List (1 .. 6);
6245             Names : constant Name_List (1 .. 6) := (
6246                       Name_Internal,
6247                       Name_External,
6248                       Name_Parameter_Types,
6249                       Name_Result_Type,
6250                       Name_Mechanism,
6251                       Name_Result_Mechanism);
6252
6253             Internal         : Node_Id renames Args (1);
6254             External         : Node_Id renames Args (2);
6255             Parameter_Types  : Node_Id renames Args (3);
6256             Result_Type      : Node_Id renames Args (4);
6257             Mechanism        : Node_Id renames Args (5);
6258             Result_Mechanism : Node_Id renames Args (6);
6259
6260          begin
6261             GNAT_Pragma;
6262             Gather_Associations (Names, Args);
6263             Process_Extended_Import_Export_Subprogram_Pragma (
6264               Arg_Internal         => Internal,
6265               Arg_External         => External,
6266               Arg_Parameter_Types  => Parameter_Types,
6267               Arg_Result_Type      => Result_Type,
6268               Arg_Mechanism        => Mechanism,
6269               Arg_Result_Mechanism => Result_Mechanism);
6270          end Export_Function;
6271
6272          -------------------
6273          -- Export_Object --
6274          -------------------
6275
6276          --  pragma Export_Object (
6277          --        [Internal =>] LOCAL_NAME,
6278          --     [, [External =>] EXTERNAL_SYMBOL]
6279          --     [, [Size     =>] EXTERNAL_SYMBOL]);
6280
6281          --  EXTERNAL_SYMBOL ::=
6282          --    IDENTIFIER
6283          --  | static_string_EXPRESSION
6284
6285          --  PARAMETER_TYPES ::=
6286          --    null
6287          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
6288
6289          --  TYPE_DESIGNATOR ::=
6290          --    subtype_NAME
6291          --  | subtype_Name ' Access
6292
6293          --  MECHANISM ::=
6294          --    MECHANISM_NAME
6295          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
6296
6297          --  MECHANISM_ASSOCIATION ::=
6298          --    [formal_parameter_NAME =>] MECHANISM_NAME
6299
6300          --  MECHANISM_NAME ::=
6301          --    Value
6302          --  | Reference
6303          --  | Descriptor [([Class =>] CLASS_NAME)]
6304
6305          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
6306
6307          when Pragma_Export_Object => Export_Object : declare
6308             Args  : Args_List (1 .. 3);
6309             Names : constant Name_List (1 .. 3) := (
6310                       Name_Internal,
6311                       Name_External,
6312                       Name_Size);
6313
6314             Internal : Node_Id renames Args (1);
6315             External : Node_Id renames Args (2);
6316             Size     : Node_Id renames Args (3);
6317
6318          begin
6319             GNAT_Pragma;
6320             Gather_Associations (Names, Args);
6321             Process_Extended_Import_Export_Object_Pragma (
6322               Arg_Internal => Internal,
6323               Arg_External => External,
6324               Arg_Size     => Size);
6325          end Export_Object;
6326
6327          ----------------------
6328          -- Export_Procedure --
6329          ----------------------
6330
6331          --  pragma Export_Procedure (
6332          --        [Internal         =>] LOCAL_NAME,
6333          --     [, [External         =>] EXTERNAL_SYMBOL,]
6334          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
6335          --     [, [Mechanism        =>] MECHANISM]);
6336
6337          --  EXTERNAL_SYMBOL ::=
6338          --    IDENTIFIER
6339          --  | static_string_EXPRESSION
6340
6341          --  PARAMETER_TYPES ::=
6342          --    null
6343          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
6344
6345          --  TYPE_DESIGNATOR ::=
6346          --    subtype_NAME
6347          --  | subtype_Name ' Access
6348
6349          --  MECHANISM ::=
6350          --    MECHANISM_NAME
6351          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
6352
6353          --  MECHANISM_ASSOCIATION ::=
6354          --    [formal_parameter_NAME =>] MECHANISM_NAME
6355
6356          --  MECHANISM_NAME ::=
6357          --    Value
6358          --  | Reference
6359          --  | Descriptor [([Class =>] CLASS_NAME)]
6360
6361          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
6362
6363          when Pragma_Export_Procedure => Export_Procedure : declare
6364             Args  : Args_List (1 .. 4);
6365             Names : constant Name_List (1 .. 4) := (
6366                       Name_Internal,
6367                       Name_External,
6368                       Name_Parameter_Types,
6369                       Name_Mechanism);
6370
6371             Internal        : Node_Id renames Args (1);
6372             External        : Node_Id renames Args (2);
6373             Parameter_Types : Node_Id renames Args (3);
6374             Mechanism       : Node_Id renames Args (4);
6375
6376          begin
6377             GNAT_Pragma;
6378             Gather_Associations (Names, Args);
6379             Process_Extended_Import_Export_Subprogram_Pragma (
6380               Arg_Internal        => Internal,
6381               Arg_External        => External,
6382               Arg_Parameter_Types => Parameter_Types,
6383               Arg_Mechanism       => Mechanism);
6384          end Export_Procedure;
6385
6386          ------------------
6387          -- Export_Value --
6388          ------------------
6389
6390          --  pragma Export_Value (
6391          --     [Value     =>] static_integer_EXPRESSION,
6392          --     [Link_Name =>] static_string_EXPRESSION);
6393
6394          when Pragma_Export_Value =>
6395             GNAT_Pragma;
6396             Check_Arg_Order ((Name_Value, Name_Link_Name));
6397             Check_Arg_Count (2);
6398
6399             Check_Optional_Identifier (Arg1, Name_Value);
6400             Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
6401
6402             Check_Optional_Identifier (Arg2, Name_Link_Name);
6403             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
6404
6405          -----------------------------
6406          -- Export_Valued_Procedure --
6407          -----------------------------
6408
6409          --  pragma Export_Valued_Procedure (
6410          --        [Internal         =>] LOCAL_NAME,
6411          --     [, [External         =>] EXTERNAL_SYMBOL,]
6412          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
6413          --     [, [Mechanism        =>] MECHANISM]);
6414
6415          --  EXTERNAL_SYMBOL ::=
6416          --    IDENTIFIER
6417          --  | static_string_EXPRESSION
6418
6419          --  PARAMETER_TYPES ::=
6420          --    null
6421          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
6422
6423          --  TYPE_DESIGNATOR ::=
6424          --    subtype_NAME
6425          --  | subtype_Name ' Access
6426
6427          --  MECHANISM ::=
6428          --    MECHANISM_NAME
6429          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
6430
6431          --  MECHANISM_ASSOCIATION ::=
6432          --    [formal_parameter_NAME =>] MECHANISM_NAME
6433
6434          --  MECHANISM_NAME ::=
6435          --    Value
6436          --  | Reference
6437          --  | Descriptor [([Class =>] CLASS_NAME)]
6438
6439          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
6440
6441          when Pragma_Export_Valued_Procedure =>
6442          Export_Valued_Procedure : declare
6443             Args  : Args_List (1 .. 4);
6444             Names : constant Name_List (1 .. 4) := (
6445                       Name_Internal,
6446                       Name_External,
6447                       Name_Parameter_Types,
6448                       Name_Mechanism);
6449
6450             Internal        : Node_Id renames Args (1);
6451             External        : Node_Id renames Args (2);
6452             Parameter_Types : Node_Id renames Args (3);
6453             Mechanism       : Node_Id renames Args (4);
6454
6455          begin
6456             GNAT_Pragma;
6457             Gather_Associations (Names, Args);
6458             Process_Extended_Import_Export_Subprogram_Pragma (
6459               Arg_Internal        => Internal,
6460               Arg_External        => External,
6461               Arg_Parameter_Types => Parameter_Types,
6462               Arg_Mechanism       => Mechanism);
6463          end Export_Valued_Procedure;
6464
6465          -------------------
6466          -- Extend_System --
6467          -------------------
6468
6469          --  pragma Extend_System ([Name =>] Identifier);
6470
6471          when Pragma_Extend_System => Extend_System : declare
6472          begin
6473             GNAT_Pragma;
6474             Check_Valid_Configuration_Pragma;
6475             Check_Arg_Count (1);
6476             Check_Optional_Identifier (Arg1, Name_Name);
6477             Check_Arg_Is_Identifier (Arg1);
6478
6479             Get_Name_String (Chars (Expression (Arg1)));
6480
6481             if Name_Len > 4
6482               and then Name_Buffer (1 .. 4) = "aux_"
6483             then
6484                if Present (System_Extend_Pragma_Arg) then
6485                   if Chars (Expression (Arg1)) =
6486                      Chars (Expression (System_Extend_Pragma_Arg))
6487                   then
6488                      null;
6489                   else
6490                      Error_Msg_Sloc := Sloc (System_Extend_Pragma_Arg);
6491                      Error_Pragma ("pragma% conflicts with that #");
6492                   end if;
6493
6494                else
6495                   System_Extend_Pragma_Arg := Arg1;
6496
6497                   if not GNAT_Mode then
6498                      System_Extend_Unit := Arg1;
6499                   end if;
6500                end if;
6501             else
6502                Error_Pragma ("incorrect name for pragma%, must be Aux_xxx");
6503             end if;
6504          end Extend_System;
6505
6506          ------------------------
6507          -- Extensions_Allowed --
6508          ------------------------
6509
6510          --  pragma Extensions_Allowed (ON | OFF);
6511
6512          when Pragma_Extensions_Allowed =>
6513             GNAT_Pragma;
6514             Check_Arg_Count (1);
6515             Check_No_Identifiers;
6516             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
6517
6518             if Chars (Expression (Arg1)) = Name_On then
6519                Extensions_Allowed := True;
6520             else
6521                Extensions_Allowed := False;
6522             end if;
6523
6524          --------------
6525          -- External --
6526          --------------
6527
6528          --  pragma External (
6529          --    [   Convention    =>] convention_IDENTIFIER,
6530          --    [   Entity        =>] local_NAME
6531          --    [, [External_Name =>] static_string_EXPRESSION ]
6532          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
6533
6534          when Pragma_External => External : declare
6535             C      : Convention_Id;
6536             Def_Id : Entity_Id;
6537          begin
6538             GNAT_Pragma;
6539             Check_Arg_Order
6540               ((Name_Convention,
6541                 Name_Entity,
6542                 Name_External_Name,
6543                 Name_Link_Name));
6544             Check_At_Least_N_Arguments (2);
6545             Check_At_Most_N_Arguments  (4);
6546             Process_Convention (C, Def_Id);
6547             Note_Possible_Modification (Expression (Arg2));
6548             Process_Interface_Name (Def_Id, Arg3, Arg4);
6549             Set_Exported (Def_Id, Arg2);
6550          end External;
6551
6552          --------------------------
6553          -- External_Name_Casing --
6554          --------------------------
6555
6556          --  pragma External_Name_Casing (
6557          --    UPPERCASE | LOWERCASE
6558          --    [, AS_IS | UPPERCASE | LOWERCASE]);
6559
6560          when Pragma_External_Name_Casing => External_Name_Casing : declare
6561          begin
6562             GNAT_Pragma;
6563             Check_No_Identifiers;
6564
6565             if Arg_Count = 2 then
6566                Check_Arg_Is_One_Of
6567                  (Arg2, Name_As_Is, Name_Uppercase, Name_Lowercase);
6568
6569                case Chars (Get_Pragma_Arg (Arg2)) is
6570                   when Name_As_Is     =>
6571                      Opt.External_Name_Exp_Casing := As_Is;
6572
6573                   when Name_Uppercase =>
6574                      Opt.External_Name_Exp_Casing := Uppercase;
6575
6576                   when Name_Lowercase =>
6577                      Opt.External_Name_Exp_Casing := Lowercase;
6578
6579                   when others =>
6580                      null;
6581                end case;
6582
6583             else
6584                Check_Arg_Count (1);
6585             end if;
6586
6587             Check_Arg_Is_One_Of (Arg1, Name_Uppercase, Name_Lowercase);
6588
6589             case Chars (Get_Pragma_Arg (Arg1)) is
6590                when Name_Uppercase =>
6591                   Opt.External_Name_Imp_Casing := Uppercase;
6592
6593                when Name_Lowercase =>
6594                   Opt.External_Name_Imp_Casing := Lowercase;
6595
6596                when others =>
6597                   null;
6598             end case;
6599          end External_Name_Casing;
6600
6601          ---------------------------
6602          -- Finalize_Storage_Only --
6603          ---------------------------
6604
6605          --  pragma Finalize_Storage_Only (first_subtype_LOCAL_NAME);
6606
6607          when Pragma_Finalize_Storage_Only => Finalize_Storage : declare
6608             Assoc   : constant Node_Id := Arg1;
6609             Type_Id : constant Node_Id := Expression (Assoc);
6610             Typ     : Entity_Id;
6611
6612          begin
6613             Check_No_Identifiers;
6614             Check_Arg_Count (1);
6615             Check_Arg_Is_Local_Name (Arg1);
6616
6617             Find_Type (Type_Id);
6618             Typ := Entity (Type_Id);
6619
6620             if Typ = Any_Type
6621               or else Rep_Item_Too_Early (Typ, N)
6622             then
6623                return;
6624             else
6625                Typ := Underlying_Type (Typ);
6626             end if;
6627
6628             if not Is_Controlled (Typ) then
6629                Error_Pragma ("pragma% must specify controlled type");
6630             end if;
6631
6632             Check_First_Subtype (Arg1);
6633
6634             if Finalize_Storage_Only (Typ) then
6635                Error_Pragma ("duplicate pragma%, only one allowed");
6636
6637             elsif not Rep_Item_Too_Late (Typ, N) then
6638                Set_Finalize_Storage_Only (Base_Type (Typ), True);
6639             end if;
6640          end Finalize_Storage;
6641
6642          --------------------------
6643          -- Float_Representation --
6644          --------------------------
6645
6646          --  pragma Float_Representation (FLOAT_REP[, float_type_LOCAL_NAME]);
6647
6648          --  FLOAT_REP ::= VAX_Float | IEEE_Float
6649
6650          when Pragma_Float_Representation => Float_Representation : declare
6651             Argx : Node_Id;
6652             Digs : Nat;
6653             Ent  : Entity_Id;
6654
6655          begin
6656             GNAT_Pragma;
6657
6658             if Arg_Count = 1 then
6659                Check_Valid_Configuration_Pragma;
6660             else
6661                Check_Arg_Count (2);
6662                Check_Optional_Identifier (Arg2, Name_Entity);
6663                Check_Arg_Is_Local_Name (Arg2);
6664             end if;
6665
6666             Check_No_Identifier (Arg1);
6667             Check_Arg_Is_One_Of (Arg1, Name_VAX_Float, Name_IEEE_Float);
6668
6669             if not OpenVMS_On_Target then
6670                if Chars (Expression (Arg1)) = Name_VAX_Float then
6671                   Error_Pragma
6672                     ("?pragma% ignored (applies only to Open'V'M'S)");
6673                end if;
6674
6675                return;
6676             end if;
6677
6678             --  One argument case
6679
6680             if Arg_Count = 1 then
6681                if Chars (Expression (Arg1)) = Name_VAX_Float then
6682                   if Opt.Float_Format = 'I' then
6683                      Error_Pragma ("'I'E'E'E format previously specified");
6684                   end if;
6685
6686                   Opt.Float_Format := 'V';
6687
6688                else
6689                   if Opt.Float_Format = 'V' then
6690                      Error_Pragma ("'V'A'X format previously specified");
6691                   end if;
6692
6693                   Opt.Float_Format := 'I';
6694                end if;
6695
6696                Set_Standard_Fpt_Formats;
6697
6698             --  Two argument case
6699
6700             else
6701                Argx := Get_Pragma_Arg (Arg2);
6702
6703                if not Is_Entity_Name (Argx)
6704                  or else not Is_Floating_Point_Type (Entity (Argx))
6705                then
6706                   Error_Pragma_Arg
6707                     ("second argument of% pragma must be floating-point type",
6708                      Arg2);
6709                end if;
6710
6711                Ent  := Entity (Argx);
6712                Digs := UI_To_Int (Digits_Value (Ent));
6713
6714                --  Two arguments, VAX_Float case
6715
6716                if Chars (Expression (Arg1)) = Name_VAX_Float then
6717                   case Digs is
6718                      when  6 => Set_F_Float (Ent);
6719                      when  9 => Set_D_Float (Ent);
6720                      when 15 => Set_G_Float (Ent);
6721
6722                      when others =>
6723                         Error_Pragma_Arg
6724                           ("wrong digits value, must be 6,9 or 15", Arg2);
6725                   end case;
6726
6727                --  Two arguments, IEEE_Float case
6728
6729                else
6730                   case Digs is
6731                      when  6 => Set_IEEE_Short (Ent);
6732                      when 15 => Set_IEEE_Long  (Ent);
6733
6734                      when others =>
6735                         Error_Pragma_Arg
6736                           ("wrong digits value, must be 6 or 15", Arg2);
6737                   end case;
6738                end if;
6739             end if;
6740          end Float_Representation;
6741
6742          -----------
6743          -- Ident --
6744          -----------
6745
6746          --  pragma Ident (static_string_EXPRESSION)
6747
6748          --  Note: pragma Comment shares this processing. Pragma Comment
6749          --  is identical to Ident, except that the restriction of the
6750          --  argument to 31 characters and the placement restrictions
6751          --  are not enforced for pragma Comment.
6752
6753          when Pragma_Ident | Pragma_Comment => Ident : declare
6754             Str : Node_Id;
6755
6756          begin
6757             GNAT_Pragma;
6758             Check_Arg_Count (1);
6759             Check_No_Identifiers;
6760             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
6761
6762             --  For pragma Ident, preserve DEC compatibility by requiring
6763             --  the pragma to appear in a declarative part or package spec.
6764
6765             if Prag_Id = Pragma_Ident then
6766                Check_Is_In_Decl_Part_Or_Package_Spec;
6767             end if;
6768
6769             Str := Expr_Value_S (Expression (Arg1));
6770
6771             declare
6772                CS : Node_Id;
6773                GP : Node_Id;
6774
6775             begin
6776                GP := Parent (Parent (N));
6777
6778                if Nkind (GP) = N_Package_Declaration
6779                     or else
6780                   Nkind (GP) = N_Generic_Package_Declaration
6781                then
6782                   GP := Parent (GP);
6783                end if;
6784
6785                --  If we have a compilation unit, then record the ident
6786                --  value, checking for improper duplication.
6787
6788                if Nkind (GP) = N_Compilation_Unit then
6789                   CS := Ident_String (Current_Sem_Unit);
6790
6791                   if Present (CS) then
6792
6793                      --  For Ident, we do not permit multiple instances
6794
6795                      if Prag_Id = Pragma_Ident then
6796                         Error_Pragma ("duplicate% pragma not permitted");
6797
6798                      --  For Comment, we concatenate the string, unless we
6799                      --  want to preserve the tree structure for ASIS.
6800
6801                      elsif not ASIS_Mode then
6802                         Start_String (Strval (CS));
6803                         Store_String_Char (' ');
6804                         Store_String_Chars (Strval (Str));
6805                         Set_Strval (CS, End_String);
6806                      end if;
6807
6808                   else
6809                      --  In VMS, the effect of IDENT is achieved by passing
6810                      --  IDENTIFICATION=name as a --for-linker switch.
6811
6812                      if OpenVMS_On_Target then
6813                         Start_String;
6814                         Store_String_Chars
6815                           ("--for-linker=IDENTIFICATION=");
6816                         String_To_Name_Buffer (Strval (Str));
6817                         Store_String_Chars (Name_Buffer (1 .. Name_Len));
6818
6819                         --  Only the last processed IDENT is saved. The main
6820                         --  purpose is so an IDENT associated with a main
6821                         --  procedure will be used in preference to an IDENT
6822                         --  associated with a with'd package.
6823
6824                         Replace_Linker_Option_String
6825                           (End_String, "--for-linker=IDENTIFICATION=");
6826                      end if;
6827
6828                      Set_Ident_String (Current_Sem_Unit, Str);
6829                   end if;
6830
6831                --  For subunits, we just ignore the Ident, since in GNAT
6832                --  these are not separate object files, and hence not
6833                --  separate units in the unit table.
6834
6835                elsif Nkind (GP) = N_Subunit then
6836                   null;
6837
6838                --  Otherwise we have a misplaced pragma Ident, but we ignore
6839                --  this if we are in an instantiation, since it comes from
6840                --  a generic, and has no relevance to the instantiation.
6841
6842                elsif Prag_Id = Pragma_Ident then
6843                   if Instantiation_Location (Loc) = No_Location then
6844                      Error_Pragma ("pragma% only allowed at outer level");
6845                   end if;
6846                end if;
6847             end;
6848          end Ident;
6849
6850          -----------------------
6851          -- Implicit_Packing --
6852          -----------------------
6853
6854          --  pragma Implicit_Packing;
6855
6856          when Pragma_Implicit_Packing =>
6857             GNAT_Pragma;
6858             Check_Arg_Count (0);
6859             Implicit_Packing := True;
6860
6861          ------------
6862          -- Import --
6863          ------------
6864
6865          --  pragma Import (
6866          --    [   Convention    =>] convention_IDENTIFIER,
6867          --    [   Entity        =>] local_NAME
6868          --    [, [External_Name =>] static_string_EXPRESSION ]
6869          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
6870
6871          when Pragma_Import =>
6872             Check_Ada_83_Warning;
6873             Check_Arg_Order
6874               ((Name_Convention,
6875                 Name_Entity,
6876                 Name_External_Name,
6877                 Name_Link_Name));
6878             Check_At_Least_N_Arguments (2);
6879             Check_At_Most_N_Arguments  (4);
6880             Process_Import_Or_Interface;
6881
6882          ----------------------
6883          -- Import_Exception --
6884          ----------------------
6885
6886          --  pragma Import_Exception (
6887          --        [Internal         =>] LOCAL_NAME,
6888          --     [, [External         =>] EXTERNAL_SYMBOL,]
6889          --     [, [Form     =>] Ada | VMS]
6890          --     [, [Code     =>] static_integer_EXPRESSION]);
6891
6892          when Pragma_Import_Exception => Import_Exception : declare
6893             Args  : Args_List (1 .. 4);
6894             Names : constant Name_List (1 .. 4) := (
6895                       Name_Internal,
6896                       Name_External,
6897                       Name_Form,
6898                       Name_Code);
6899
6900             Internal : Node_Id renames Args (1);
6901             External : Node_Id renames Args (2);
6902             Form     : Node_Id renames Args (3);
6903             Code     : Node_Id renames Args (4);
6904
6905          begin
6906             Gather_Associations (Names, Args);
6907
6908             if Present (External) and then Present (Code) then
6909                Error_Pragma
6910                  ("cannot give both External and Code options for pragma%");
6911             end if;
6912
6913             Process_Extended_Import_Export_Exception_Pragma (
6914               Arg_Internal => Internal,
6915               Arg_External => External,
6916               Arg_Form     => Form,
6917               Arg_Code     => Code);
6918
6919             if not Is_VMS_Exception (Entity (Internal)) then
6920                Set_Imported (Entity (Internal));
6921             end if;
6922          end Import_Exception;
6923
6924          ---------------------
6925          -- Import_Function --
6926          ---------------------
6927
6928          --  pragma Import_Function (
6929          --        [Internal                 =>] LOCAL_NAME,
6930          --     [, [External                 =>] EXTERNAL_SYMBOL]
6931          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
6932          --     [, [Result_Type              =>] SUBTYPE_MARK]
6933          --     [, [Mechanism                =>] MECHANISM]
6934          --     [, [Result_Mechanism         =>] MECHANISM_NAME]
6935          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
6936
6937          --  EXTERNAL_SYMBOL ::=
6938          --    IDENTIFIER
6939          --  | static_string_EXPRESSION
6940
6941          --  PARAMETER_TYPES ::=
6942          --    null
6943          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
6944
6945          --  TYPE_DESIGNATOR ::=
6946          --    subtype_NAME
6947          --  | subtype_Name ' Access
6948
6949          --  MECHANISM ::=
6950          --    MECHANISM_NAME
6951          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
6952
6953          --  MECHANISM_ASSOCIATION ::=
6954          --    [formal_parameter_NAME =>] MECHANISM_NAME
6955
6956          --  MECHANISM_NAME ::=
6957          --    Value
6958          --  | Reference
6959          --  | Descriptor [([Class =>] CLASS_NAME)]
6960
6961          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
6962
6963          when Pragma_Import_Function => Import_Function : declare
6964             Args  : Args_List (1 .. 7);
6965             Names : constant Name_List (1 .. 7) := (
6966                       Name_Internal,
6967                       Name_External,
6968                       Name_Parameter_Types,
6969                       Name_Result_Type,
6970                       Name_Mechanism,
6971                       Name_Result_Mechanism,
6972                       Name_First_Optional_Parameter);
6973
6974             Internal                 : Node_Id renames Args (1);
6975             External                 : Node_Id renames Args (2);
6976             Parameter_Types          : Node_Id renames Args (3);
6977             Result_Type              : Node_Id renames Args (4);
6978             Mechanism                : Node_Id renames Args (5);
6979             Result_Mechanism         : Node_Id renames Args (6);
6980             First_Optional_Parameter : Node_Id renames Args (7);
6981
6982          begin
6983             GNAT_Pragma;
6984             Gather_Associations (Names, Args);
6985             Process_Extended_Import_Export_Subprogram_Pragma (
6986               Arg_Internal                 => Internal,
6987               Arg_External                 => External,
6988               Arg_Parameter_Types          => Parameter_Types,
6989               Arg_Result_Type              => Result_Type,
6990               Arg_Mechanism                => Mechanism,
6991               Arg_Result_Mechanism         => Result_Mechanism,
6992               Arg_First_Optional_Parameter => First_Optional_Parameter);
6993          end Import_Function;
6994
6995          -------------------
6996          -- Import_Object --
6997          -------------------
6998
6999          --  pragma Import_Object (
7000          --        [Internal =>] LOCAL_NAME,
7001          --     [, [External =>] EXTERNAL_SYMBOL]
7002          --     [, [Size     =>] EXTERNAL_SYMBOL]);
7003
7004          --  EXTERNAL_SYMBOL ::=
7005          --    IDENTIFIER
7006          --  | static_string_EXPRESSION
7007
7008          when Pragma_Import_Object => Import_Object : declare
7009             Args  : Args_List (1 .. 3);
7010             Names : constant Name_List (1 .. 3) := (
7011                       Name_Internal,
7012                       Name_External,
7013                       Name_Size);
7014
7015             Internal : Node_Id renames Args (1);
7016             External : Node_Id renames Args (2);
7017             Size     : Node_Id renames Args (3);
7018
7019          begin
7020             GNAT_Pragma;
7021             Gather_Associations (Names, Args);
7022             Process_Extended_Import_Export_Object_Pragma (
7023               Arg_Internal => Internal,
7024               Arg_External => External,
7025               Arg_Size     => Size);
7026          end Import_Object;
7027
7028          ----------------------
7029          -- Import_Procedure --
7030          ----------------------
7031
7032          --  pragma Import_Procedure (
7033          --        [Internal                 =>] LOCAL_NAME,
7034          --     [, [External                 =>] EXTERNAL_SYMBOL]
7035          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
7036          --     [, [Mechanism                =>] MECHANISM]
7037          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
7038
7039          --  EXTERNAL_SYMBOL ::=
7040          --    IDENTIFIER
7041          --  | static_string_EXPRESSION
7042
7043          --  PARAMETER_TYPES ::=
7044          --    null
7045          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
7046
7047          --  TYPE_DESIGNATOR ::=
7048          --    subtype_NAME
7049          --  | subtype_Name ' Access
7050
7051          --  MECHANISM ::=
7052          --    MECHANISM_NAME
7053          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
7054
7055          --  MECHANISM_ASSOCIATION ::=
7056          --    [formal_parameter_NAME =>] MECHANISM_NAME
7057
7058          --  MECHANISM_NAME ::=
7059          --    Value
7060          --  | Reference
7061          --  | Descriptor [([Class =>] CLASS_NAME)]
7062
7063          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
7064
7065          when Pragma_Import_Procedure => Import_Procedure : declare
7066             Args  : Args_List (1 .. 5);
7067             Names : constant Name_List (1 .. 5) := (
7068                       Name_Internal,
7069                       Name_External,
7070                       Name_Parameter_Types,
7071                       Name_Mechanism,
7072                       Name_First_Optional_Parameter);
7073
7074             Internal                 : Node_Id renames Args (1);
7075             External                 : Node_Id renames Args (2);
7076             Parameter_Types          : Node_Id renames Args (3);
7077             Mechanism                : Node_Id renames Args (4);
7078             First_Optional_Parameter : Node_Id renames Args (5);
7079
7080          begin
7081             GNAT_Pragma;
7082             Gather_Associations (Names, Args);
7083             Process_Extended_Import_Export_Subprogram_Pragma (
7084               Arg_Internal                 => Internal,
7085               Arg_External                 => External,
7086               Arg_Parameter_Types          => Parameter_Types,
7087               Arg_Mechanism                => Mechanism,
7088               Arg_First_Optional_Parameter => First_Optional_Parameter);
7089          end Import_Procedure;
7090
7091          -----------------------------
7092          -- Import_Valued_Procedure --
7093          -----------------------------
7094
7095          --  pragma Import_Valued_Procedure (
7096          --        [Internal                 =>] LOCAL_NAME,
7097          --     [, [External                 =>] EXTERNAL_SYMBOL]
7098          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
7099          --     [, [Mechanism                =>] MECHANISM]
7100          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
7101
7102          --  EXTERNAL_SYMBOL ::=
7103          --    IDENTIFIER
7104          --  | static_string_EXPRESSION
7105
7106          --  PARAMETER_TYPES ::=
7107          --    null
7108          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
7109
7110          --  TYPE_DESIGNATOR ::=
7111          --    subtype_NAME
7112          --  | subtype_Name ' Access
7113
7114          --  MECHANISM ::=
7115          --    MECHANISM_NAME
7116          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
7117
7118          --  MECHANISM_ASSOCIATION ::=
7119          --    [formal_parameter_NAME =>] MECHANISM_NAME
7120
7121          --  MECHANISM_NAME ::=
7122          --    Value
7123          --  | Reference
7124          --  | Descriptor [([Class =>] CLASS_NAME)]
7125
7126          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
7127
7128          when Pragma_Import_Valued_Procedure =>
7129          Import_Valued_Procedure : declare
7130             Args  : Args_List (1 .. 5);
7131             Names : constant Name_List (1 .. 5) := (
7132                       Name_Internal,
7133                       Name_External,
7134                       Name_Parameter_Types,
7135                       Name_Mechanism,
7136                       Name_First_Optional_Parameter);
7137
7138             Internal                 : Node_Id renames Args (1);
7139             External                 : Node_Id renames Args (2);
7140             Parameter_Types          : Node_Id renames Args (3);
7141             Mechanism                : Node_Id renames Args (4);
7142             First_Optional_Parameter : Node_Id renames Args (5);
7143
7144          begin
7145             GNAT_Pragma;
7146             Gather_Associations (Names, Args);
7147             Process_Extended_Import_Export_Subprogram_Pragma (
7148               Arg_Internal                 => Internal,
7149               Arg_External                 => External,
7150               Arg_Parameter_Types          => Parameter_Types,
7151               Arg_Mechanism                => Mechanism,
7152               Arg_First_Optional_Parameter => First_Optional_Parameter);
7153          end Import_Valued_Procedure;
7154
7155          ------------------------
7156          -- Initialize_Scalars --
7157          ------------------------
7158
7159          --  pragma Initialize_Scalars;
7160
7161          when Pragma_Initialize_Scalars =>
7162             GNAT_Pragma;
7163             Check_Arg_Count (0);
7164             Check_Valid_Configuration_Pragma;
7165             Check_Restriction (No_Initialize_Scalars, N);
7166
7167             if not Restriction_Active (No_Initialize_Scalars) then
7168                Init_Or_Norm_Scalars := True;
7169                Initialize_Scalars := True;
7170             end if;
7171
7172          ------------
7173          -- Inline --
7174          ------------
7175
7176          --  pragma Inline ( NAME {, NAME} );
7177
7178          when Pragma_Inline =>
7179
7180             --  Pragma is active if inlining option is active
7181
7182             Process_Inline (Inline_Active);
7183
7184          -------------------
7185          -- Inline_Always --
7186          -------------------
7187
7188          --  pragma Inline_Always ( NAME {, NAME} );
7189
7190          when Pragma_Inline_Always =>
7191             Process_Inline (True);
7192
7193          --------------------
7194          -- Inline_Generic --
7195          --------------------
7196
7197          --  pragma Inline_Generic (NAME {, NAME});
7198
7199          when Pragma_Inline_Generic =>
7200             Process_Generic_List;
7201
7202          ----------------------
7203          -- Inspection_Point --
7204          ----------------------
7205
7206          --  pragma Inspection_Point [(object_NAME {, object_NAME})];
7207
7208          when Pragma_Inspection_Point => Inspection_Point : declare
7209             Arg : Node_Id;
7210             Exp : Node_Id;
7211
7212          begin
7213             if Arg_Count > 0 then
7214                Arg := Arg1;
7215                loop
7216                   Exp := Expression (Arg);
7217                   Analyze (Exp);
7218
7219                   if not Is_Entity_Name (Exp)
7220                     or else not Is_Object (Entity (Exp))
7221                   then
7222                      Error_Pragma_Arg ("object name required", Arg);
7223                   end if;
7224
7225                   Next (Arg);
7226                   exit when No (Arg);
7227                end loop;
7228             end if;
7229          end Inspection_Point;
7230
7231          ---------------
7232          -- Interface --
7233          ---------------
7234
7235          --  pragma Interface (
7236          --    [   Convention    =>] convention_IDENTIFIER,
7237          --    [   Entity        =>] local_NAME
7238          --    [, [External_Name =>] static_string_EXPRESSION ]
7239          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
7240
7241          when Pragma_Interface =>
7242             GNAT_Pragma;
7243             Check_Arg_Order
7244               ((Name_Convention,
7245                 Name_Entity,
7246                 Name_External_Name,
7247                 Name_Link_Name));
7248             Check_At_Least_N_Arguments (2);
7249             Check_At_Most_N_Arguments  (4);
7250             Process_Import_Or_Interface;
7251
7252          --------------------
7253          -- Interface_Name --
7254          --------------------
7255
7256          --  pragma Interface_Name (
7257          --    [  Entity        =>] local_NAME
7258          --    [,[External_Name =>] static_string_EXPRESSION ]
7259          --    [,[Link_Name     =>] static_string_EXPRESSION ]);
7260
7261          when Pragma_Interface_Name => Interface_Name : declare
7262             Id     : Node_Id;
7263             Def_Id : Entity_Id;
7264             Hom_Id : Entity_Id;
7265             Found  : Boolean;
7266
7267          begin
7268             GNAT_Pragma;
7269             Check_Arg_Order
7270               ((Name_Entity, Name_External_Name, Name_Link_Name));
7271             Check_At_Least_N_Arguments (2);
7272             Check_At_Most_N_Arguments  (3);
7273             Id := Expression (Arg1);
7274             Analyze (Id);
7275
7276             if not Is_Entity_Name (Id) then
7277                Error_Pragma_Arg
7278                  ("first argument for pragma% must be entity name", Arg1);
7279             elsif Etype (Id) = Any_Type then
7280                return;
7281             else
7282                Def_Id := Entity (Id);
7283             end if;
7284
7285             --  Special DEC-compatible processing for the object case,
7286             --  forces object to be imported.
7287
7288             if Ekind (Def_Id) = E_Variable then
7289                Kill_Size_Check_Code (Def_Id);
7290                Note_Possible_Modification (Id);
7291
7292                --  Initialization is not allowed for imported variable
7293
7294                if Present (Expression (Parent (Def_Id)))
7295                  and then Comes_From_Source (Expression (Parent (Def_Id)))
7296                then
7297                   Error_Msg_Sloc := Sloc (Def_Id);
7298                   Error_Pragma_Arg
7299                     ("no initialization allowed for declaration of& #",
7300                      Arg2);
7301
7302                else
7303                   --  For compatibility, support VADS usage of providing both
7304                   --  pragmas Interface and Interface_Name to obtain the effect
7305                   --  of a single Import pragma.
7306
7307                   if Is_Imported (Def_Id)
7308                     and then Present (First_Rep_Item (Def_Id))
7309                     and then Nkind (First_Rep_Item (Def_Id)) = N_Pragma
7310                     and then Chars (First_Rep_Item (Def_Id)) = Name_Interface
7311                   then
7312                      null;
7313                   else
7314                      Set_Imported (Def_Id);
7315                   end if;
7316
7317                   Set_Is_Public (Def_Id);
7318                   Process_Interface_Name (Def_Id, Arg2, Arg3);
7319                end if;
7320
7321             --  Otherwise must be subprogram
7322
7323             elsif not Is_Subprogram (Def_Id) then
7324                Error_Pragma_Arg
7325                  ("argument of pragma% is not subprogram", Arg1);
7326
7327             else
7328                Check_At_Most_N_Arguments (3);
7329                Hom_Id := Def_Id;
7330                Found := False;
7331
7332                --  Loop through homonyms
7333
7334                loop
7335                   Def_Id := Get_Base_Subprogram (Hom_Id);
7336
7337                   if Is_Imported (Def_Id) then
7338                      Process_Interface_Name (Def_Id, Arg2, Arg3);
7339                      Found := True;
7340                   end if;
7341
7342                   Hom_Id := Homonym (Hom_Id);
7343
7344                   exit when No (Hom_Id)
7345                     or else Scope (Hom_Id) /= Current_Scope;
7346                end loop;
7347
7348                if not Found then
7349                   Error_Pragma_Arg
7350                     ("argument of pragma% is not imported subprogram",
7351                      Arg1);
7352                end if;
7353             end if;
7354          end Interface_Name;
7355
7356          -----------------------
7357          -- Interrupt_Handler --
7358          -----------------------
7359
7360          --  pragma Interrupt_Handler (handler_NAME);
7361
7362          when Pragma_Interrupt_Handler =>
7363             Check_Ada_83_Warning;
7364             Check_Arg_Count (1);
7365             Check_No_Identifiers;
7366
7367             if No_Run_Time_Mode then
7368                Error_Msg_CRT ("Interrupt_Handler pragma", N);
7369             else
7370                Check_Interrupt_Or_Attach_Handler;
7371                Process_Interrupt_Or_Attach_Handler;
7372             end if;
7373
7374          ------------------------
7375          -- Interrupt_Priority --
7376          ------------------------
7377
7378          --  pragma Interrupt_Priority [(EXPRESSION)];
7379
7380          when Pragma_Interrupt_Priority => Interrupt_Priority : declare
7381             P   : constant Node_Id := Parent (N);
7382             Arg : Node_Id;
7383
7384          begin
7385             Check_Ada_83_Warning;
7386
7387             if Arg_Count /= 0 then
7388                Arg := Expression (Arg1);
7389                Check_Arg_Count (1);
7390                Check_No_Identifiers;
7391
7392                --  The expression must be analyzed in the special manner
7393                --  described in "Handling of Default and Per-Object
7394                --  Expressions" in sem.ads.
7395
7396                Analyze_Per_Use_Expression (Arg, RTE (RE_Interrupt_Priority));
7397             end if;
7398
7399             if Nkind (P) /= N_Task_Definition
7400               and then Nkind (P) /= N_Protected_Definition
7401             then
7402                Pragma_Misplaced;
7403                return;
7404
7405             elsif Has_Priority_Pragma (P) then
7406                Error_Pragma ("duplicate pragma% not allowed");
7407
7408             else
7409                Set_Has_Priority_Pragma (P, True);
7410                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
7411             end if;
7412          end Interrupt_Priority;
7413
7414          ---------------------
7415          -- Interrupt_State --
7416          ---------------------
7417
7418          --  pragma Interrupt_State (
7419          --    [Name  =>] INTERRUPT_ID,
7420          --    [State =>] INTERRUPT_STATE);
7421
7422          --  INTERRUPT_ID => IDENTIFIER | static_integer_EXPRESSION
7423          --  INTERRUPT_STATE => System | Runtime | User
7424
7425          --  Note: if the interrupt id is given as an identifier, then
7426          --  it must be one of the identifiers in Ada.Interrupts.Names.
7427          --  Otherwise it is given as a static integer expression which
7428          --  must be in the range of Ada.Interrupts.Interrupt_ID.
7429
7430          when Pragma_Interrupt_State => Interrupt_State : declare
7431
7432             Int_Id : constant Entity_Id := RTE (RE_Interrupt_ID);
7433             --  This is the entity Ada.Interrupts.Interrupt_ID;
7434
7435             State_Type : Character;
7436             --  Set to 's'/'r'/'u' for System/Runtime/User
7437
7438             IST_Num : Pos;
7439             --  Index to entry in Interrupt_States table
7440
7441             Int_Val : Uint;
7442             --  Value of interrupt
7443
7444             Arg1X : constant Node_Id := Get_Pragma_Arg (Arg1);
7445             --  The first argument to the pragma
7446
7447             Int_Ent : Entity_Id;
7448             --  Interrupt entity in Ada.Interrupts.Names
7449
7450          begin
7451             GNAT_Pragma;
7452             Check_Arg_Order ((Name_Name, Name_State));
7453             Check_Arg_Count (2);
7454
7455             Check_Optional_Identifier (Arg1, Name_Name);
7456             Check_Optional_Identifier (Arg2, Name_State);
7457             Check_Arg_Is_Identifier (Arg2);
7458
7459             --  First argument is identifier
7460
7461             if Nkind (Arg1X) = N_Identifier then
7462
7463                --  Search list of names in Ada.Interrupts.Names
7464
7465                Int_Ent := First_Entity (RTE (RE_Names));
7466                loop
7467                   if No (Int_Ent) then
7468                      Error_Pragma_Arg ("invalid interrupt name", Arg1);
7469
7470                   elsif Chars (Int_Ent) = Chars (Arg1X) then
7471                      Int_Val := Expr_Value (Constant_Value (Int_Ent));
7472                      exit;
7473                   end if;
7474
7475                   Next_Entity (Int_Ent);
7476                end loop;
7477
7478             --  First argument is not an identifier, so it must be a
7479             --  static expression of type Ada.Interrupts.Interrupt_ID.
7480
7481             else
7482                Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
7483                Int_Val := Expr_Value (Arg1X);
7484
7485                if Int_Val < Expr_Value (Type_Low_Bound (Int_Id))
7486                     or else
7487                   Int_Val > Expr_Value (Type_High_Bound (Int_Id))
7488                then
7489                   Error_Pragma_Arg
7490                     ("value not in range of type " &
7491                      """Ada.Interrupts.Interrupt_'I'D""", Arg1);
7492                end if;
7493             end if;
7494
7495             --  Check OK state
7496
7497             case Chars (Get_Pragma_Arg (Arg2)) is
7498                when Name_Runtime => State_Type := 'r';
7499                when Name_System  => State_Type := 's';
7500                when Name_User    => State_Type := 'u';
7501
7502                when others =>
7503                   Error_Pragma_Arg ("invalid interrupt state", Arg2);
7504             end case;
7505
7506             --  Check if entry is already stored
7507
7508             IST_Num := Interrupt_States.First;
7509             loop
7510                --  If entry not found, add it
7511
7512                if IST_Num > Interrupt_States.Last then
7513                   Interrupt_States.Append
7514                     ((Interrupt_Number => UI_To_Int (Int_Val),
7515                       Interrupt_State  => State_Type,
7516                       Pragma_Loc       => Loc));
7517                   exit;
7518
7519                --  Case of entry for the same entry
7520
7521                elsif Int_Val = Interrupt_States.Table (IST_Num).
7522                                                            Interrupt_Number
7523                then
7524                   --  If state matches, done, no need to make redundant entry
7525
7526                   exit when
7527                     State_Type = Interrupt_States.Table (IST_Num).
7528                                                            Interrupt_State;
7529
7530                   --  Otherwise if state does not match, error
7531
7532                   Error_Msg_Sloc :=
7533                     Interrupt_States.Table (IST_Num).Pragma_Loc;
7534                   Error_Pragma_Arg
7535                     ("state conflicts with that given #", Arg2);
7536                   exit;
7537                end if;
7538
7539                IST_Num := IST_Num + 1;
7540             end loop;
7541          end Interrupt_State;
7542
7543          ----------------------
7544          -- Java_Constructor --
7545          ----------------------
7546
7547          --  pragma Java_Constructor ([Entity =>] LOCAL_NAME);
7548
7549          --  Also handles pragma CIL_Constructor
7550
7551          when Pragma_CIL_Constructor | Pragma_Java_Constructor =>
7552          Java_Constructor : declare
7553             Id         : Entity_Id;
7554             Def_Id     : Entity_Id;
7555             Hom_Id     : Entity_Id;
7556             Convention : Convention_Id;
7557
7558          begin
7559             GNAT_Pragma;
7560             Check_Arg_Count (1);
7561             Check_Optional_Identifier (Arg1, Name_Entity);
7562             Check_Arg_Is_Local_Name (Arg1);
7563
7564             Id := Expression (Arg1);
7565             Find_Program_Unit_Name (Id);
7566
7567             --  If we did not find the name, we are done
7568
7569             if Etype (Id) = Any_Type then
7570                return;
7571             end if;
7572
7573             case Prag_Id is
7574                when Pragma_CIL_Constructor  => Convention := Convention_CIL;
7575                when Pragma_Java_Constructor => Convention := Convention_Java;
7576                when others                  => null;
7577             end case;
7578
7579             Hom_Id := Entity (Id);
7580
7581             --  Loop through homonyms
7582
7583             loop
7584                Def_Id := Get_Base_Subprogram (Hom_Id);
7585
7586                --  The constructor is required to be a function returning an
7587                --  access type whose designated type has convention Java/CIL.
7588
7589                if Ekind (Def_Id) = E_Function
7590                  and then
7591                    (Is_Value_Type (Etype (Def_Id))
7592                      or else
7593                        (Ekind (Etype (Def_Id)) in Access_Kind
7594                          and then
7595                           (Atree.Convention
7596                              (Designated_Type (Etype (Def_Id))) = Convention
7597                             or else
7598                               Atree.Convention
7599                                (Root_Type (Designated_Type (Etype (Def_Id)))) =
7600                                                                  Convention)))
7601                then
7602                   Set_Is_Constructor (Def_Id);
7603                   Set_Convention     (Def_Id, Convention);
7604                   Set_Is_Imported    (Def_Id);
7605
7606                else
7607                   if Convention = Convention_Java then
7608                      Error_Pragma_Arg
7609                        ("pragma% requires function returning a " &
7610                         "'Java access type", Arg1);
7611                   else
7612                      pragma Assert (Convention = Convention_CIL);
7613                      Error_Pragma_Arg
7614                        ("pragma% requires function returning a " &
7615                         "'CIL access type", Arg1);
7616                   end if;
7617                end if;
7618
7619                Hom_Id := Homonym (Hom_Id);
7620
7621                exit when No (Hom_Id) or else Scope (Hom_Id) /= Current_Scope;
7622             end loop;
7623          end Java_Constructor;
7624
7625          ----------------------
7626          -- Java_Interface --
7627          ----------------------
7628
7629          --  pragma Java_Interface ([Entity =>] LOCAL_NAME);
7630
7631          when Pragma_Java_Interface => Java_Interface : declare
7632             Arg : Node_Id;
7633             Typ : Entity_Id;
7634
7635          begin
7636             GNAT_Pragma;
7637             Check_Arg_Count (1);
7638             Check_Optional_Identifier (Arg1, Name_Entity);
7639             Check_Arg_Is_Local_Name (Arg1);
7640
7641             Arg := Expression (Arg1);
7642             Analyze (Arg);
7643
7644             if Etype (Arg) = Any_Type then
7645                return;
7646             end if;
7647
7648             if not Is_Entity_Name (Arg)
7649               or else not Is_Type (Entity (Arg))
7650             then
7651                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
7652             end if;
7653
7654             Typ := Underlying_Type (Entity (Arg));
7655
7656             --  For now we simply check some of the semantic constraints
7657             --  on the type. This currently leaves out some restrictions
7658             --  on interface types, namely that the parent type must be
7659             --  java.lang.Object.Typ and that all primitives of the type
7660             --  should be declared abstract. ???
7661
7662             if not Is_Tagged_Type (Typ) or else not Is_Abstract_Type (Typ) then
7663                Error_Pragma_Arg ("pragma% requires an abstract "
7664                  & "tagged type", Arg1);
7665
7666             elsif not Has_Discriminants (Typ)
7667               or else Ekind (Etype (First_Discriminant (Typ)))
7668                         /= E_Anonymous_Access_Type
7669               or else
7670                 not Is_Class_Wide_Type
7671                       (Designated_Type (Etype (First_Discriminant (Typ))))
7672             then
7673                Error_Pragma_Arg
7674                  ("type must have a class-wide access discriminant", Arg1);
7675             end if;
7676          end Java_Interface;
7677
7678          ----------------
7679          -- Keep_Names --
7680          ----------------
7681
7682          --  pragma Keep_Names ([On => ] local_NAME);
7683
7684          when Pragma_Keep_Names => Keep_Names : declare
7685             Arg : Node_Id;
7686
7687          begin
7688             GNAT_Pragma;
7689             Check_Arg_Count (1);
7690             Check_Optional_Identifier (Arg1, Name_On);
7691             Check_Arg_Is_Local_Name (Arg1);
7692
7693             Arg := Expression (Arg1);
7694             Analyze (Arg);
7695
7696             if Etype (Arg) = Any_Type then
7697                return;
7698             end if;
7699
7700             if not Is_Entity_Name (Arg)
7701               or else Ekind (Entity (Arg)) /= E_Enumeration_Type
7702             then
7703                Error_Pragma_Arg
7704                  ("pragma% requires a local enumeration type", Arg1);
7705             end if;
7706
7707             Set_Discard_Names (Entity (Arg), False);
7708          end Keep_Names;
7709
7710          -------------
7711          -- License --
7712          -------------
7713
7714          --  pragma License (RESTRICTED | UNRESTRICTED | GPL | MODIFIED_GPL);
7715
7716          when Pragma_License =>
7717             GNAT_Pragma;
7718             Check_Arg_Count (1);
7719             Check_No_Identifiers;
7720             Check_Valid_Configuration_Pragma;
7721             Check_Arg_Is_Identifier (Arg1);
7722
7723             declare
7724                Sind : constant Source_File_Index :=
7725                         Source_Index (Current_Sem_Unit);
7726
7727             begin
7728                case Chars (Get_Pragma_Arg (Arg1)) is
7729                   when Name_GPL =>
7730                      Set_License (Sind, GPL);
7731
7732                   when Name_Modified_GPL =>
7733                      Set_License (Sind, Modified_GPL);
7734
7735                   when Name_Restricted =>
7736                      Set_License (Sind, Restricted);
7737
7738                   when Name_Unrestricted =>
7739                      Set_License (Sind, Unrestricted);
7740
7741                   when others =>
7742                      Error_Pragma_Arg ("invalid license name", Arg1);
7743                end case;
7744             end;
7745
7746          ---------------
7747          -- Link_With --
7748          ---------------
7749
7750          --  pragma Link_With (string_EXPRESSION {, string_EXPRESSION});
7751
7752          when Pragma_Link_With => Link_With : declare
7753             Arg : Node_Id;
7754
7755          begin
7756             GNAT_Pragma;
7757
7758             if Operating_Mode = Generate_Code
7759               and then In_Extended_Main_Source_Unit (N)
7760             then
7761                Check_At_Least_N_Arguments (1);
7762                Check_No_Identifiers;
7763                Check_Is_In_Decl_Part_Or_Package_Spec;
7764                Check_Arg_Is_Static_Expression (Arg1, Standard_String);
7765                Start_String;
7766
7767                Arg := Arg1;
7768                while Present (Arg) loop
7769                   Check_Arg_Is_Static_Expression (Arg, Standard_String);
7770
7771                   --  Store argument, converting sequences of spaces
7772                   --  to a single null character (this is one of the
7773                   --  differences in processing between Link_With
7774                   --  and Linker_Options).
7775
7776                   Arg_Store : declare
7777                      C : constant Char_Code := Get_Char_Code (' ');
7778                      S : constant String_Id :=
7779                            Strval (Expr_Value_S (Expression (Arg)));
7780                      L : constant Nat := String_Length (S);
7781                      F : Nat := 1;
7782
7783                      procedure Skip_Spaces;
7784                      --  Advance F past any spaces
7785
7786                      -----------------
7787                      -- Skip_Spaces --
7788                      -----------------
7789
7790                      procedure Skip_Spaces is
7791                      begin
7792                         while F <= L and then Get_String_Char (S, F) = C loop
7793                            F := F + 1;
7794                         end loop;
7795                      end Skip_Spaces;
7796
7797                   --  Start of processing for Arg_Store
7798
7799                   begin
7800                      Skip_Spaces; -- skip leading spaces
7801
7802                      --  Loop through characters, changing any embedded
7803                      --  sequence of spaces to a single null character
7804                      --  (this is how Link_With/Linker_Options differ)
7805
7806                      while F <= L loop
7807                         if Get_String_Char (S, F) = C then
7808                            Skip_Spaces;
7809                            exit when F > L;
7810                            Store_String_Char (ASCII.NUL);
7811
7812                         else
7813                            Store_String_Char (Get_String_Char (S, F));
7814                            F := F + 1;
7815                         end if;
7816                      end loop;
7817                   end Arg_Store;
7818
7819                   Arg := Next (Arg);
7820
7821                   if Present (Arg) then
7822                      Store_String_Char (ASCII.NUL);
7823                   end if;
7824                end loop;
7825
7826                Store_Linker_Option_String (End_String);
7827             end if;
7828          end Link_With;
7829
7830          ------------------
7831          -- Linker_Alias --
7832          ------------------
7833
7834          --  pragma Linker_Alias (
7835          --      [Entity =>]  LOCAL_NAME
7836          --      [Target =>]  static_string_EXPRESSION);
7837
7838          when Pragma_Linker_Alias =>
7839             GNAT_Pragma;
7840             Check_Arg_Order ((Name_Entity, Name_Target));
7841             Check_Arg_Count (2);
7842             Check_Optional_Identifier (Arg1, Name_Entity);
7843             Check_Optional_Identifier (Arg2, Name_Target);
7844             Check_Arg_Is_Library_Level_Local_Name (Arg1);
7845             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
7846
7847             --  The only processing required is to link this item on to the
7848             --  list of rep items for the given entity. This is accomplished
7849             --  by the call to Rep_Item_Too_Late (when no error is detected
7850             --  and False is returned).
7851
7852             if Rep_Item_Too_Late (Entity (Expression (Arg1)), N) then
7853                return;
7854             else
7855                Set_Has_Gigi_Rep_Item (Entity (Expression (Arg1)));
7856             end if;
7857
7858          ------------------------
7859          -- Linker_Constructor --
7860          ------------------------
7861
7862          --  pragma Linker_Constructor (procedure_LOCAL_NAME);
7863
7864          --  Code is shared with Linker_Destructor
7865
7866          -----------------------
7867          -- Linker_Destructor --
7868          -----------------------
7869
7870          --  pragma Linker_Destructor (procedure_LOCAL_NAME);
7871
7872          when Pragma_Linker_Constructor |
7873               Pragma_Linker_Destructor =>
7874          Linker_Constructor : declare
7875             Arg1_X : Node_Id;
7876             Proc   : Entity_Id;
7877
7878          begin
7879             GNAT_Pragma;
7880             Check_Arg_Count (1);
7881             Check_No_Identifiers;
7882             Check_Arg_Is_Local_Name (Arg1);
7883             Arg1_X := Expression (Arg1);
7884             Analyze (Arg1_X);
7885             Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
7886
7887             if not Is_Library_Level_Entity (Proc) then
7888                Error_Pragma_Arg
7889                 ("argument for pragma% must be library level entity", Arg1);
7890             end if;
7891
7892             --  The only processing required is to link this item on to the
7893             --  list of rep items for the given entity. This is accomplished
7894             --  by the call to Rep_Item_Too_Late (when no error is detected
7895             --  and False is returned).
7896
7897             if Rep_Item_Too_Late (Proc, N) then
7898                return;
7899             else
7900                Set_Has_Gigi_Rep_Item (Proc);
7901             end if;
7902          end Linker_Constructor;
7903
7904          --------------------
7905          -- Linker_Options --
7906          --------------------
7907
7908          --  pragma Linker_Options (string_EXPRESSION {, string_EXPRESSION});
7909
7910          when Pragma_Linker_Options => Linker_Options : declare
7911             Arg : Node_Id;
7912
7913          begin
7914             Check_Ada_83_Warning;
7915             Check_No_Identifiers;
7916             Check_Arg_Count (1);
7917             Check_Is_In_Decl_Part_Or_Package_Spec;
7918
7919             if Operating_Mode = Generate_Code
7920               and then In_Extended_Main_Source_Unit (N)
7921             then
7922                Check_Arg_Is_Static_Expression (Arg1, Standard_String);
7923                Start_String (Strval (Expr_Value_S (Expression (Arg1))));
7924
7925                Arg := Arg2;
7926                while Present (Arg) loop
7927                   Check_Arg_Is_Static_Expression (Arg, Standard_String);
7928                   Store_String_Char (ASCII.NUL);
7929                   Store_String_Chars
7930                     (Strval (Expr_Value_S (Expression (Arg))));
7931                   Arg := Next (Arg);
7932                end loop;
7933
7934                Store_Linker_Option_String (End_String);
7935             end if;
7936          end Linker_Options;
7937
7938          --------------------
7939          -- Linker_Section --
7940          --------------------
7941
7942          --  pragma Linker_Section (
7943          --      [Entity  =>]  LOCAL_NAME
7944          --      [Section =>]  static_string_EXPRESSION);
7945
7946          when Pragma_Linker_Section =>
7947             GNAT_Pragma;
7948             Check_Arg_Order ((Name_Entity, Name_Section));
7949             Check_Arg_Count (2);
7950             Check_Optional_Identifier (Arg1, Name_Entity);
7951             Check_Optional_Identifier (Arg2, Name_Section);
7952             Check_Arg_Is_Library_Level_Local_Name (Arg1);
7953             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
7954
7955             --  The only processing required is to link this item on to the
7956             --  list of rep items for the given entity. This is accomplished
7957             --  by the call to Rep_Item_Too_Late (when no error is detected
7958             --  and False is returned).
7959
7960             if Rep_Item_Too_Late (Entity (Expression (Arg1)), N) then
7961                return;
7962             else
7963                Set_Has_Gigi_Rep_Item (Entity (Expression (Arg1)));
7964             end if;
7965
7966          ----------
7967          -- List --
7968          ----------
7969
7970          --  pragma List (On | Off)
7971
7972          --  There is nothing to do here, since we did all the processing
7973          --  for this pragma in Par.Prag (so that it works properly even in
7974          --  syntax only mode)
7975
7976          when Pragma_List =>
7977             null;
7978
7979          --------------------
7980          -- Locking_Policy --
7981          --------------------
7982
7983          --  pragma Locking_Policy (policy_IDENTIFIER);
7984
7985          when Pragma_Locking_Policy => declare
7986             LP : Character;
7987
7988          begin
7989             Check_Ada_83_Warning;
7990             Check_Arg_Count (1);
7991             Check_No_Identifiers;
7992             Check_Arg_Is_Locking_Policy (Arg1);
7993             Check_Valid_Configuration_Pragma;
7994             Get_Name_String (Chars (Expression (Arg1)));
7995             LP := Fold_Upper (Name_Buffer (1));
7996
7997             if Locking_Policy /= ' '
7998               and then Locking_Policy /= LP
7999             then
8000                Error_Msg_Sloc := Locking_Policy_Sloc;
8001                Error_Pragma ("locking policy incompatible with policy#");
8002
8003             --  Set new policy, but always preserve System_Location since
8004             --  we like the error message with the run time name.
8005
8006             else
8007                Locking_Policy := LP;
8008
8009                if Locking_Policy_Sloc /= System_Location then
8010                   Locking_Policy_Sloc := Loc;
8011                end if;
8012             end if;
8013          end;
8014
8015          ----------------
8016          -- Long_Float --
8017          ----------------
8018
8019          --  pragma Long_Float (D_Float | G_Float);
8020
8021          when Pragma_Long_Float =>
8022             GNAT_Pragma;
8023             Check_Valid_Configuration_Pragma;
8024             Check_Arg_Count (1);
8025             Check_No_Identifier (Arg1);
8026             Check_Arg_Is_One_Of (Arg1, Name_D_Float, Name_G_Float);
8027
8028             if not OpenVMS_On_Target then
8029                Error_Pragma ("?pragma% ignored (applies only to Open'V'M'S)");
8030             end if;
8031
8032             --  D_Float case
8033
8034             if Chars (Expression (Arg1)) = Name_D_Float then
8035                if Opt.Float_Format_Long = 'G' then
8036                   Error_Pragma ("G_Float previously specified");
8037                end if;
8038
8039                Opt.Float_Format_Long := 'D';
8040
8041             --  G_Float case (this is the default, does not need overriding)
8042
8043             else
8044                if Opt.Float_Format_Long = 'D' then
8045                   Error_Pragma ("D_Float previously specified");
8046                end if;
8047
8048                Opt.Float_Format_Long := 'G';
8049             end if;
8050
8051             Set_Standard_Fpt_Formats;
8052
8053          -----------------------
8054          -- Machine_Attribute --
8055          -----------------------
8056
8057          --  pragma Machine_Attribute (
8058          --    [Entity         =>] LOCAL_NAME,
8059          --    [Attribute_Name =>] static_string_EXPRESSION
8060          --  [,[Info           =>] static_string_EXPRESSION] );
8061
8062          when Pragma_Machine_Attribute => Machine_Attribute : declare
8063             Def_Id : Entity_Id;
8064
8065          begin
8066             GNAT_Pragma;
8067             Check_Arg_Order ((Name_Entity, Name_Attribute_Name, Name_Info));
8068
8069             if Arg_Count = 3 then
8070                Check_Optional_Identifier (Arg3, Name_Info);
8071                Check_Arg_Is_Static_Expression (Arg3, Standard_String);
8072             else
8073                Check_Arg_Count (2);
8074             end if;
8075
8076             Check_Optional_Identifier (Arg1, Name_Entity);
8077             Check_Optional_Identifier (Arg2, Name_Attribute_Name);
8078             Check_Arg_Is_Local_Name (Arg1);
8079             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
8080             Def_Id := Entity (Expression (Arg1));
8081
8082             if Is_Access_Type (Def_Id) then
8083                Def_Id := Designated_Type (Def_Id);
8084             end if;
8085
8086             if Rep_Item_Too_Early (Def_Id, N) then
8087                return;
8088             end if;
8089
8090             Def_Id := Underlying_Type (Def_Id);
8091
8092             --  The only processing required is to link this item on to the
8093             --  list of rep items for the given entity. This is accomplished
8094             --  by the call to Rep_Item_Too_Late (when no error is detected
8095             --  and False is returned).
8096
8097             if Rep_Item_Too_Late (Def_Id, N) then
8098                return;
8099             else
8100                Set_Has_Gigi_Rep_Item (Entity (Expression (Arg1)));
8101             end if;
8102          end Machine_Attribute;
8103
8104          ----------
8105          -- Main --
8106          ----------
8107
8108          --  pragma Main
8109          --   (MAIN_OPTION [, MAIN_OPTION]);
8110
8111          --  MAIN_OPTION ::=
8112          --    [STACK_SIZE              =>] static_integer_EXPRESSION
8113          --  | [TASK_STACK_SIZE_DEFAULT =>] static_integer_EXPRESSION
8114          --  | [TIME_SLICING_ENABLED    =>] static_boolean_EXPRESSION
8115
8116          when Pragma_Main => Main : declare
8117             Args  : Args_List (1 .. 3);
8118             Names : constant Name_List (1 .. 3) := (
8119                       Name_Stack_Size,
8120                       Name_Task_Stack_Size_Default,
8121                       Name_Time_Slicing_Enabled);
8122
8123             Nod : Node_Id;
8124
8125          begin
8126             GNAT_Pragma;
8127             Gather_Associations (Names, Args);
8128
8129             for J in 1 .. 2 loop
8130                if Present (Args (J)) then
8131                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
8132                end if;
8133             end loop;
8134
8135             if Present (Args (3)) then
8136                Check_Arg_Is_Static_Expression (Args (3), Standard_Boolean);
8137             end if;
8138
8139             Nod := Next (N);
8140             while Present (Nod) loop
8141                if Nkind (Nod) = N_Pragma
8142                  and then Chars (Nod) = Name_Main
8143                then
8144                   Error_Msg_Name_1 := Chars (N);
8145                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
8146                end if;
8147
8148                Next (Nod);
8149             end loop;
8150          end Main;
8151
8152          ------------------
8153          -- Main_Storage --
8154          ------------------
8155
8156          --  pragma Main_Storage
8157          --   (MAIN_STORAGE_OPTION [, MAIN_STORAGE_OPTION]);
8158
8159          --  MAIN_STORAGE_OPTION ::=
8160          --    [WORKING_STORAGE =>] static_SIMPLE_EXPRESSION
8161          --  | [TOP_GUARD =>] static_SIMPLE_EXPRESSION
8162
8163          when Pragma_Main_Storage => Main_Storage : declare
8164             Args  : Args_List (1 .. 2);
8165             Names : constant Name_List (1 .. 2) := (
8166                       Name_Working_Storage,
8167                       Name_Top_Guard);
8168
8169             Nod : Node_Id;
8170
8171          begin
8172             GNAT_Pragma;
8173             Gather_Associations (Names, Args);
8174
8175             for J in 1 .. 2 loop
8176                if Present (Args (J)) then
8177                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
8178                end if;
8179             end loop;
8180
8181             Check_In_Main_Program;
8182
8183             Nod := Next (N);
8184             while Present (Nod) loop
8185                if Nkind (Nod) = N_Pragma
8186                  and then Chars (Nod) = Name_Main_Storage
8187                then
8188                   Error_Msg_Name_1 := Chars (N);
8189                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
8190                end if;
8191
8192                Next (Nod);
8193             end loop;
8194          end Main_Storage;
8195
8196          -----------------
8197          -- Memory_Size --
8198          -----------------
8199
8200          --  pragma Memory_Size (NUMERIC_LITERAL)
8201
8202          when Pragma_Memory_Size =>
8203             GNAT_Pragma;
8204
8205             --  Memory size is simply ignored
8206
8207             Check_No_Identifiers;
8208             Check_Arg_Count (1);
8209             Check_Arg_Is_Integer_Literal (Arg1);
8210
8211          -------------
8212          -- No_Body --
8213          -------------
8214
8215          --  pragma No_Body;
8216
8217          --  The only correct use of this pragma is on its own in a file, in
8218          --  which case it is specially processed (see Gnat1drv.Check_Bad_Body
8219          --  and Frontend, which use Sinput.L.Source_File_Is_Pragma_No_Body to
8220          --  check for a file containing nothing but a No_Body pragma). If we
8221          --  attempt to process it during normal semantics processing, it means
8222          --  it was misplaced.
8223
8224          when Pragma_No_Body =>
8225             Error_Pragma ("misplaced pragma %");
8226
8227          ---------------
8228          -- No_Return --
8229          ---------------
8230
8231          --  pragma No_Return (procedure_LOCAL_NAME {, procedure_Local_Name});
8232
8233          when Pragma_No_Return => No_Return : declare
8234             Id    : Node_Id;
8235             E     : Entity_Id;
8236             Found : Boolean;
8237             Arg   : Node_Id;
8238
8239          begin
8240             GNAT_Pragma;
8241             Check_At_Least_N_Arguments (1);
8242
8243             --  Loop through arguments of pragma
8244
8245             Arg := Arg1;
8246             while Present (Arg) loop
8247                Check_Arg_Is_Local_Name (Arg);
8248                Id := Expression (Arg);
8249                Analyze (Id);
8250
8251                if not Is_Entity_Name (Id) then
8252                   Error_Pragma_Arg ("entity name required", Arg);
8253                end if;
8254
8255                if Etype (Id) = Any_Type then
8256                   raise Pragma_Exit;
8257                end if;
8258
8259                --  Loop to find matching procedures
8260
8261                E := Entity (Id);
8262                Found := False;
8263                while Present (E)
8264                  and then Scope (E) = Current_Scope
8265                loop
8266                   if Ekind (E) = E_Procedure
8267                     or else Ekind (E) = E_Generic_Procedure
8268                   then
8269                      Set_No_Return (E);
8270                      Found := True;
8271                   end if;
8272
8273                   E := Homonym (E);
8274                end loop;
8275
8276                if not Found then
8277                   Error_Pragma_Arg ("no procedure & found for pragma%", Arg);
8278                end if;
8279
8280                Next (Arg);
8281             end loop;
8282          end No_Return;
8283
8284          ------------------------
8285          -- No_Strict_Aliasing --
8286          ------------------------
8287
8288          --  pragma No_Strict_Aliasing [([Entity =>] type_LOCAL_NAME)];
8289
8290          when Pragma_No_Strict_Aliasing => No_Strict_Alias : declare
8291             E_Id : Entity_Id;
8292
8293          begin
8294             GNAT_Pragma;
8295             Check_At_Most_N_Arguments (1);
8296
8297             if Arg_Count = 0 then
8298                Check_Valid_Configuration_Pragma;
8299                Opt.No_Strict_Aliasing := True;
8300
8301             else
8302                Check_Optional_Identifier (Arg2, Name_Entity);
8303                Check_Arg_Is_Local_Name (Arg1);
8304                E_Id := Entity (Expression (Arg1));
8305
8306                if E_Id = Any_Type then
8307                   return;
8308                elsif No (E_Id) or else not Is_Access_Type (E_Id) then
8309                   Error_Pragma_Arg ("pragma% requires access type", Arg1);
8310                end if;
8311
8312                Set_No_Strict_Aliasing (Implementation_Base_Type (E_Id));
8313             end if;
8314          end No_Strict_Alias;
8315
8316          -----------------
8317          -- Obsolescent --
8318          -----------------
8319
8320          --  pragma Obsolescent [(
8321          --    [Entity => NAME,]
8322          --    [(static_string_EXPRESSION [, Ada_05])];
8323
8324          when Pragma_Obsolescent => Obsolescent : declare
8325             Ename : Node_Id;
8326             Decl  : Node_Id;
8327
8328             procedure Set_Obsolescent (E : Entity_Id);
8329             --  Given an entity Ent, mark it as obsolescent if appropriate
8330
8331             ---------------------
8332             -- Set_Obsolescent --
8333             ---------------------
8334
8335             procedure Set_Obsolescent (E : Entity_Id) is
8336                Active : Boolean;
8337                Ent    : Entity_Id;
8338                S      : String_Id;
8339
8340             begin
8341                Active := True;
8342                Ent    := E;
8343
8344                --  Entity name was given
8345
8346                if Present (Ename) then
8347
8348                   --  If entity name matches, we are fine
8349
8350                   if Chars (Ename) = Chars (Ent) then
8351                      null;
8352
8353                   --  If entity name does not match, only possibility is an
8354                   --  enumeration literal from an enumeration type declaration.
8355
8356                   elsif Ekind (Ent) /= E_Enumeration_Type then
8357                      Error_Pragma
8358                        ("pragma % entity name does not match declaration");
8359
8360                   else
8361                      Ent := First_Literal (E);
8362                      loop
8363                         if No (Ent) then
8364                            Error_Pragma
8365                              ("pragma % entity name does not match any " &
8366                               "enumeration literal");
8367
8368                         elsif Chars (Ent) = Chars (Ename) then
8369                            exit;
8370
8371                         else
8372                            Ent := Next_Literal (Ent);
8373                         end if;
8374                      end loop;
8375                   end if;
8376                end if;
8377
8378                --  Ent points to entity to be marked
8379
8380                if Arg_Count >= 1 then
8381
8382                   --  Deal with static string argument
8383
8384                   Check_Arg_Is_Static_Expression (Arg1, Standard_String);
8385                   S := Strval (Expression (Arg1));
8386
8387                   for J in 1 .. String_Length (S) loop
8388                      if not In_Character_Range (Get_String_Char (S, J)) then
8389                         Error_Pragma_Arg
8390                           ("pragma% argument does not allow wide characters",
8391                            Arg1);
8392                      end if;
8393                   end loop;
8394
8395                   Set_Obsolescent_Warning (Ent, Expression (Arg1));
8396
8397                   --  Check for Ada_05 parameter
8398
8399                   if Arg_Count /= 1 then
8400                      Check_Arg_Count (2);
8401
8402                      declare
8403                         Argx : constant Node_Id := Get_Pragma_Arg (Arg2);
8404
8405                      begin
8406                         Check_Arg_Is_Identifier (Argx);
8407
8408                         if Chars (Argx) /= Name_Ada_05 then
8409                            Error_Msg_Name_2 := Name_Ada_05;
8410                            Error_Pragma_Arg
8411                              ("only allowed argument for pragma% is %", Argx);
8412                         end if;
8413
8414                         if Ada_Version_Explicit < Ada_05
8415                           or else not Warn_On_Ada_2005_Compatibility
8416                         then
8417                            Active := False;
8418                         end if;
8419                      end;
8420                   end if;
8421                end if;
8422
8423                --  Set flag if pragma active
8424
8425                if Active then
8426                   Set_Is_Obsolescent (Ent);
8427                end if;
8428
8429                return;
8430             end Set_Obsolescent;
8431
8432          --  Start of processing for pragma Obsolescent
8433
8434          begin
8435             GNAT_Pragma;
8436
8437             Check_At_Most_N_Arguments (3);
8438
8439             --  See if first argument specifies an entity name
8440
8441             if Arg_Count >= 1
8442               and then Chars (Arg1) = Name_Entity
8443             then
8444                Ename := Get_Pragma_Arg (Arg1);
8445
8446                if Nkind (Ename) /= N_Character_Literal
8447                     and then
8448                   Nkind (Ename) /= N_Identifier
8449                     and then
8450                   Nkind (Ename) /= N_Operator_Symbol
8451                then
8452                   Error_Pragma_Arg ("entity name expected for pragma%", Arg1);
8453                end if;
8454
8455                --  Eliminate first argument, so we can share processing
8456
8457                Arg1 := Arg2;
8458                Arg2 := Arg3;
8459                Arg_Count := Arg_Count - 1;
8460
8461             --  No Entity name argument given
8462
8463             else
8464                Ename := Empty;
8465             end if;
8466
8467             Check_No_Identifiers;
8468
8469             --  Get immediately preceding declaration
8470
8471             Decl := Prev (N);
8472             while Present (Decl) and then Nkind (Decl) = N_Pragma loop
8473                Prev (Decl);
8474             end loop;
8475
8476             --  Cases where we do not follow anything other than another pragma
8477
8478             if No (Decl) then
8479
8480                --  First case: library level compilation unit declaration with
8481                --  the pragma immediately following the declaration.
8482
8483                if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
8484                   Set_Obsolescent
8485                     (Defining_Entity (Unit (Parent (Parent (N)))));
8486                   return;
8487
8488                --  Case 2: library unit placement for package
8489
8490                else
8491                   declare
8492                      Ent : constant Entity_Id := Find_Lib_Unit_Name;
8493                   begin
8494                      if Ekind (Ent) = E_Package
8495                        or else Ekind (Ent) = E_Generic_Package
8496                      then
8497                         Set_Obsolescent (Ent);
8498                         return;
8499                      end if;
8500                   end;
8501                end if;
8502
8503             --  Cases where we must follow a declaration
8504
8505             else
8506                if Nkind (Decl) not in N_Declaration
8507                  and then Nkind (Decl) not in N_Later_Decl_Item
8508                  and then Nkind (Decl) not in N_Generic_Declaration
8509                then
8510                   Error_Pragma
8511                     ("pragma% misplaced, " &
8512                      "must immediately follow a declaration");
8513
8514                else
8515                   Set_Obsolescent (Defining_Entity (Decl));
8516                   return;
8517                end if;
8518             end if;
8519          end Obsolescent;
8520
8521          -----------------
8522          -- No_Run_Time --
8523          -----------------
8524
8525          --  pragma No_Run_Time
8526
8527          --  Note: this pragma is retained for backwards compatibiltiy.
8528          --  See body of Rtsfind for full details on its handling.
8529
8530          when Pragma_No_Run_Time =>
8531             GNAT_Pragma;
8532             Check_Valid_Configuration_Pragma;
8533             Check_Arg_Count (0);
8534
8535             No_Run_Time_Mode           := True;
8536             Configurable_Run_Time_Mode := True;
8537
8538             declare
8539                Word32 : constant Boolean := Ttypes.System_Word_Size = 32;
8540             begin
8541                if Word32 then
8542                   Duration_32_Bits_On_Target := True;
8543                end if;
8544             end;
8545
8546             Set_Restriction (No_Finalization, N);
8547             Set_Restriction (No_Exception_Handlers, N);
8548             Set_Restriction (Max_Tasks, N, 0);
8549             Set_Restriction (No_Tasking, N);
8550
8551          -----------------------
8552          -- Normalize_Scalars --
8553          -----------------------
8554
8555          --  pragma Normalize_Scalars;
8556
8557          when Pragma_Normalize_Scalars =>
8558             Check_Ada_83_Warning;
8559             Check_Arg_Count (0);
8560             Check_Valid_Configuration_Pragma;
8561             Normalize_Scalars := True;
8562             Init_Or_Norm_Scalars := True;
8563
8564          --------------
8565          -- Optimize --
8566          --------------
8567
8568          --  pragma Optimize (Time | Space);
8569
8570          --  The actual check for optimize is done in Gigi. Note that this
8571          --  pragma does not actually change the optimization setting, it
8572          --  simply checks that it is consistent with the pragma.
8573
8574          when Pragma_Optimize =>
8575             Check_No_Identifiers;
8576             Check_Arg_Count (1);
8577             Check_Arg_Is_One_Of (Arg1, Name_Time, Name_Space, Name_Off);
8578
8579          ----------
8580          -- Pack --
8581          ----------
8582
8583          --  pragma Pack (first_subtype_LOCAL_NAME);
8584
8585          when Pragma_Pack => Pack : declare
8586             Assoc   : constant Node_Id := Arg1;
8587             Type_Id : Node_Id;
8588             Typ     : Entity_Id;
8589
8590          begin
8591             Check_No_Identifiers;
8592             Check_Arg_Count (1);
8593             Check_Arg_Is_Local_Name (Arg1);
8594
8595             Type_Id := Expression (Assoc);
8596             Find_Type (Type_Id);
8597             Typ := Entity (Type_Id);
8598
8599             if Typ = Any_Type
8600               or else Rep_Item_Too_Early (Typ, N)
8601             then
8602                return;
8603             else
8604                Typ := Underlying_Type (Typ);
8605             end if;
8606
8607             if not Is_Array_Type (Typ) and then not Is_Record_Type (Typ) then
8608                Error_Pragma ("pragma% must specify array or record type");
8609             end if;
8610
8611             Check_First_Subtype (Arg1);
8612
8613             if Has_Pragma_Pack (Typ) then
8614                Error_Pragma ("duplicate pragma%, only one allowed");
8615
8616             --  Array type
8617
8618             elsif Is_Array_Type (Typ) then
8619
8620                --  Pack not allowed for aliased or atomic components
8621
8622                if Has_Aliased_Components (Base_Type (Typ)) then
8623                   Error_Pragma
8624                     ("pragma% ignored, cannot pack aliased components?");
8625
8626                elsif Has_Atomic_Components (Typ)
8627                  or else Is_Atomic (Component_Type (Typ))
8628                then
8629                   Error_Pragma
8630                     ("?pragma% ignored, cannot pack atomic components");
8631                end if;
8632
8633                --  If we had an explicit component size given, then we do not
8634                --  let Pack override this given size. We also give a warning
8635                --  that Pack is being ignored unless we can tell for sure that
8636                --  the Pack would not have had any effect anyway.
8637
8638                if Has_Component_Size_Clause (Typ) then
8639                   if Known_Static_RM_Size (Component_Type (Typ))
8640                     and then
8641                       RM_Size (Component_Type (Typ)) = Component_Size (Typ)
8642                   then
8643                      null;
8644                   else
8645                      Error_Pragma
8646                        ("?pragma% ignored, explicit component size given");
8647                   end if;
8648
8649                --  If no prior array component size given, Pack is effective
8650
8651                else
8652                   if not Rep_Item_Too_Late (Typ, N) then
8653                      if VM_Target = No_VM then
8654                         Set_Is_Packed (Base_Type (Typ));
8655                      elsif not GNAT_Mode then
8656                         Error_Pragma
8657                           ("?pragma% ignored in this configuration");
8658                      end if;
8659
8660                      Set_Has_Pragma_Pack      (Base_Type (Typ));
8661                      Set_Has_Non_Standard_Rep (Base_Type (Typ));
8662                   end if;
8663                end if;
8664
8665             --  For record types, the pack is always effective
8666
8667             else pragma Assert (Is_Record_Type (Typ));
8668                if not Rep_Item_Too_Late (Typ, N) then
8669                   if VM_Target = No_VM then
8670                      Set_Is_Packed (Base_Type (Typ));
8671                   elsif not GNAT_Mode then
8672                      Error_Pragma ("?pragma% ignored in this configuration");
8673                   end if;
8674
8675                   Set_Has_Pragma_Pack      (Base_Type (Typ));
8676                   Set_Has_Non_Standard_Rep (Base_Type (Typ));
8677                end if;
8678             end if;
8679          end Pack;
8680
8681          ----------
8682          -- Page --
8683          ----------
8684
8685          --  pragma Page;
8686
8687          --  There is nothing to do here, since we did all the processing
8688          --  for this pragma in Par.Prag (so that it works properly even in
8689          --  syntax only mode)
8690
8691          when Pragma_Page =>
8692             null;
8693
8694          -------------
8695          -- Passive --
8696          -------------
8697
8698          --  pragma Passive [(PASSIVE_FORM)];
8699
8700          --   PASSIVE_FORM ::= Semaphore | No
8701
8702          when Pragma_Passive =>
8703             GNAT_Pragma;
8704
8705             if Nkind (Parent (N)) /= N_Task_Definition then
8706                Error_Pragma ("pragma% must be within task definition");
8707             end if;
8708
8709             if Arg_Count /= 0 then
8710                Check_Arg_Count (1);
8711                Check_Arg_Is_One_Of (Arg1, Name_Semaphore, Name_No);
8712             end if;
8713
8714          ----------------------------------
8715          -- Preelaborable_Initialization --
8716          ----------------------------------
8717
8718          --  pragma Preelaborable_Initialization (DIRECT_NAME);
8719
8720          when Pragma_Preelaborable_Initialization => Preelab_Init : declare
8721             Ent : Entity_Id;
8722
8723          begin
8724             Ada_2005_Pragma;
8725             Check_Arg_Count (1);
8726             Check_No_Identifiers;
8727             Check_Arg_Is_Identifier (Arg1);
8728             Check_Arg_Is_Local_Name (Arg1);
8729             Check_First_Subtype (Arg1);
8730             Ent := Entity (Expression (Arg1));
8731
8732             if not Is_Private_Type (Ent) then
8733                Error_Pragma_Arg
8734                  ("pragma % can only be applied to private type", Arg1);
8735             end if;
8736
8737             Set_Known_To_Have_Preelab_Init (Ent);
8738
8739             if Has_Pragma_Preelab_Init (Ent)
8740               and then Warn_On_Redundant_Constructs
8741             then
8742                Error_Pragma ("?duplicate pragma%!");
8743             else
8744                Set_Has_Pragma_Preelab_Init (Ent);
8745             end if;
8746          end Preelab_Init;
8747
8748          -------------
8749          -- Polling --
8750          -------------
8751
8752          --  pragma Polling (ON | OFF);
8753
8754          when Pragma_Polling =>
8755             GNAT_Pragma;
8756             Check_Arg_Count (1);
8757             Check_No_Identifiers;
8758             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
8759             Polling_Required := (Chars (Expression (Arg1)) = Name_On);
8760
8761          --------------------
8762          -- Persistent_BSS --
8763          --------------------
8764
8765          when Pragma_Persistent_BSS => Persistent_BSS :  declare
8766             Decl : Node_Id;
8767             Ent  : Entity_Id;
8768             Prag : Node_Id;
8769
8770          begin
8771             GNAT_Pragma;
8772             Check_At_Most_N_Arguments (1);
8773
8774             --  Case of application to specific object (one argument)
8775
8776             if Arg_Count = 1 then
8777                Check_Arg_Is_Library_Level_Local_Name (Arg1);
8778
8779                if not Is_Entity_Name (Expression (Arg1))
8780                  or else
8781                   (Ekind (Entity (Expression (Arg1))) /= E_Variable
8782                     and then Ekind (Entity (Expression (Arg1))) /= E_Constant)
8783                then
8784                   Error_Pragma_Arg ("pragma% only applies to objects", Arg1);
8785                end if;
8786
8787                Ent := Entity (Expression (Arg1));
8788                Decl := Parent (Ent);
8789
8790                if Rep_Item_Too_Late (Ent, N) then
8791                   return;
8792                end if;
8793
8794                if Present (Expression (Decl)) then
8795                   Error_Pragma_Arg
8796                     ("object for pragma% cannot have initialization", Arg1);
8797                end if;
8798
8799                if not Is_Potentially_Persistent_Type (Etype (Ent)) then
8800                   Error_Pragma_Arg
8801                     ("object type for pragma% is not potentially persistent",
8802                      Arg1);
8803                end if;
8804
8805                Prag :=
8806                  Make_Linker_Section_Pragma
8807                    (Ent, Sloc (N), ".persistent.bss");
8808                Insert_After (N, Prag);
8809                Analyze (Prag);
8810
8811             --  Case of use as configuration pragma with no arguments
8812
8813             else
8814                Check_Valid_Configuration_Pragma;
8815                Persistent_BSS_Mode := True;
8816             end if;
8817          end Persistent_BSS;
8818
8819          ------------------
8820          -- Preelaborate --
8821          ------------------
8822
8823          --  pragma Preelaborate [(library_unit_NAME)];
8824
8825          --  Set the flag Is_Preelaborated of program unit name entity
8826
8827          when Pragma_Preelaborate => Preelaborate : declare
8828             Pa  : constant Node_Id   := Parent (N);
8829             Pk  : constant Node_Kind := Nkind (Pa);
8830             Ent : Entity_Id;
8831
8832          begin
8833             Check_Ada_83_Warning;
8834             Check_Valid_Library_Unit_Pragma;
8835
8836             if Nkind (N) = N_Null_Statement then
8837                return;
8838             end if;
8839
8840             Ent := Find_Lib_Unit_Name;
8841
8842             --  This filters out pragmas inside generic parent then
8843             --  show up inside instantiation
8844
8845             if Present (Ent)
8846               and then not (Pk = N_Package_Specification
8847                               and then Present (Generic_Parent (Pa)))
8848             then
8849                if not Debug_Flag_U then
8850                   Set_Is_Preelaborated (Ent);
8851                   Set_Suppress_Elaboration_Warnings (Ent);
8852                end if;
8853             end if;
8854          end Preelaborate;
8855
8856          ---------------------
8857          -- Preelaborate_05 --
8858          ---------------------
8859
8860          --  pragma Preelaborate_05 [(library_unit_NAME)];
8861
8862          --  This pragma is useable only in GNAT_Mode, where it is used like
8863          --  pragma Preelaborate but it is only effective in Ada 2005 mode
8864          --  (otherwise it is ignored). This is used to implement AI-362 which
8865          --  recategorizes some run-time packages in Ada 2005 mode.
8866
8867          when Pragma_Preelaborate_05 => Preelaborate_05 : declare
8868             Ent : Entity_Id;
8869
8870          begin
8871             GNAT_Pragma;
8872             Check_Valid_Library_Unit_Pragma;
8873
8874             if not GNAT_Mode then
8875                Error_Pragma ("pragma% only available in GNAT mode");
8876             end if;
8877
8878             if Nkind (N) = N_Null_Statement then
8879                return;
8880             end if;
8881
8882             --  This is one of the few cases where we need to test the value of
8883             --  Ada_Version_Explicit rather than Ada_Version (which is always
8884             --  set to Ada_05 in a predefined unit), we need to know the
8885             --  explicit version set to know if this pragma is active.
8886
8887             if Ada_Version_Explicit >= Ada_05 then
8888                Ent := Find_Lib_Unit_Name;
8889                Set_Is_Preelaborated (Ent);
8890                Set_Suppress_Elaboration_Warnings (Ent);
8891             end if;
8892          end Preelaborate_05;
8893
8894          --------------
8895          -- Priority --
8896          --------------
8897
8898          --  pragma Priority (EXPRESSION);
8899
8900          when Pragma_Priority => Priority : declare
8901             P   : constant Node_Id := Parent (N);
8902             Arg : Node_Id;
8903
8904          begin
8905             Check_No_Identifiers;
8906             Check_Arg_Count (1);
8907
8908             --  Subprogram case
8909
8910             if Nkind (P) = N_Subprogram_Body then
8911                Check_In_Main_Program;
8912
8913                Arg := Expression (Arg1);
8914                Analyze_And_Resolve (Arg, Standard_Integer);
8915
8916                --  Must be static
8917
8918                if not Is_Static_Expression (Arg) then
8919                   Flag_Non_Static_Expr
8920                     ("main subprogram priority is not static!", Arg);
8921                   raise Pragma_Exit;
8922
8923                --  If constraint error, then we already signalled an error
8924
8925                elsif Raises_Constraint_Error (Arg) then
8926                   null;
8927
8928                --  Otherwise check in range
8929
8930                else
8931                   declare
8932                      Val : constant Uint := Expr_Value (Arg);
8933
8934                   begin
8935                      if Val < 0
8936                        or else Val > Expr_Value (Expression
8937                                        (Parent (RTE (RE_Max_Priority))))
8938                      then
8939                         Error_Pragma_Arg
8940                           ("main subprogram priority is out of range", Arg1);
8941                      end if;
8942                   end;
8943                end if;
8944
8945                Set_Main_Priority
8946                     (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
8947
8948                --  Load an arbitrary entity from System.Tasking to make sure
8949                --  this package is implicitly with'ed, since we need to have
8950                --  the tasking run-time active for the pragma Priority to have
8951                --  any effect.
8952
8953                declare
8954                   Discard : Entity_Id;
8955                   pragma Warnings (Off, Discard);
8956                begin
8957                   Discard := RTE (RE_Task_List);
8958                end;
8959
8960             --  Task or Protected, must be of type Integer
8961
8962             elsif Nkind (P) = N_Protected_Definition
8963                     or else
8964                   Nkind (P) = N_Task_Definition
8965             then
8966                Arg := Expression (Arg1);
8967
8968                --  The expression must be analyzed in the special manner
8969                --  described in "Handling of Default and Per-Object
8970                --  Expressions" in sem.ads.
8971
8972                Analyze_Per_Use_Expression (Arg, Standard_Integer);
8973
8974                if not Is_Static_Expression (Arg) then
8975                   Check_Restriction (Static_Priorities, Arg);
8976                end if;
8977
8978             --  Anything else is incorrect
8979
8980             else
8981                Pragma_Misplaced;
8982             end if;
8983
8984             if Has_Priority_Pragma (P) then
8985                Error_Pragma ("duplicate pragma% not allowed");
8986             else
8987                Set_Has_Priority_Pragma (P, True);
8988
8989                if Nkind (P) = N_Protected_Definition
8990                     or else
8991                   Nkind (P) = N_Task_Definition
8992                then
8993                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
8994                   --  exp_ch9 should use this ???
8995                end if;
8996             end if;
8997          end Priority;
8998
8999          -----------------------------------
9000          -- Priority_Specific_Dispatching --
9001          -----------------------------------
9002
9003          --  pragma Priority_Specific_Dispatching (
9004          --    policy_IDENTIFIER,
9005          --    first_priority_EXPRESSION,
9006          --    last_priority_EXPRESSION);
9007
9008          when Pragma_Priority_Specific_Dispatching =>
9009          Priority_Specific_Dispatching : declare
9010             Prio_Id : constant Entity_Id := RTE (RE_Any_Priority);
9011             --  This is the entity System.Any_Priority;
9012
9013             DP          : Character;
9014             Lower_Bound : Node_Id;
9015             Upper_Bound : Node_Id;
9016             Lower_Val   : Uint;
9017             Upper_Val   : Uint;
9018
9019          begin
9020             Ada_2005_Pragma;
9021             Check_Arg_Count (3);
9022             Check_No_Identifiers;
9023             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
9024             Check_Valid_Configuration_Pragma;
9025             Get_Name_String (Chars (Expression (Arg1)));
9026             DP := Fold_Upper (Name_Buffer (1));
9027
9028             Lower_Bound := Expression (Arg2);
9029             Check_Arg_Is_Static_Expression (Lower_Bound, Standard_Integer);
9030             Lower_Val := Expr_Value (Lower_Bound);
9031
9032             Upper_Bound := Expression (Arg3);
9033             Check_Arg_Is_Static_Expression (Upper_Bound, Standard_Integer);
9034             Upper_Val := Expr_Value (Upper_Bound);
9035
9036             --  It is not allowed to use Task_Dispatching_Policy and
9037             --  Priority_Specific_Dispatching in the same partition.
9038
9039             if Task_Dispatching_Policy /= ' ' then
9040                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
9041                Error_Pragma
9042                  ("pragma% incompatible with Task_Dispatching_Policy#");
9043
9044             --  Check lower bound in range
9045
9046             elsif Lower_Val < Expr_Value (Type_Low_Bound (Prio_Id))
9047                     or else
9048                   Lower_Val > Expr_Value (Type_High_Bound (Prio_Id))
9049             then
9050                Error_Pragma_Arg
9051                  ("first_priority is out of range", Arg2);
9052
9053             --  Check upper bound in range
9054
9055             elsif Upper_Val < Expr_Value (Type_Low_Bound (Prio_Id))
9056                     or else
9057                   Upper_Val > Expr_Value (Type_High_Bound (Prio_Id))
9058             then
9059                Error_Pragma_Arg
9060                  ("last_priority is out of range", Arg3);
9061
9062             --  Check that the priority range is valid
9063
9064             elsif Lower_Val > Upper_Val then
9065                Error_Pragma
9066                  ("last_priority_expression must be greater than" &
9067                   " or equal to first_priority_expression");
9068
9069             --  Store the new policy, but always preserve System_Location since
9070             --  we like the error message with the run-time name.
9071
9072             else
9073                --  Check overlapping in the priority ranges specified in other
9074                --  Priority_Specific_Dispatching pragmas within the same
9075                --  partition. We can only check those we know about!
9076
9077                for J in
9078                   Specific_Dispatching.First .. Specific_Dispatching.Last
9079                loop
9080                   if Specific_Dispatching.Table (J).First_Priority in
9081                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
9082                   or else Specific_Dispatching.Table (J).Last_Priority in
9083                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
9084                   then
9085                      Error_Msg_Sloc :=
9086                        Specific_Dispatching.Table (J).Pragma_Loc;
9087                         Error_Pragma
9088                           ("priority range overlaps with "
9089                            & "Priority_Specific_Dispatching#");
9090                   end if;
9091                end loop;
9092
9093                --  The use of Priority_Specific_Dispatching is incompatible
9094                --  with Task_Dispatching_Policy.
9095
9096                if Task_Dispatching_Policy /= ' ' then
9097                   Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
9098                      Error_Pragma
9099                        ("Priority_Specific_Dispatching incompatible "
9100                         & "with Task_Dispatching_Policy#");
9101                end if;
9102
9103                --  The use of Priority_Specific_Dispatching forces ceiling
9104                --  locking policy.
9105
9106                if Locking_Policy /= ' ' and then Locking_Policy /= 'C' then
9107                   Error_Msg_Sloc := Locking_Policy_Sloc;
9108                      Error_Pragma
9109                        ("Priority_Specific_Dispatching incompatible "
9110                         & "with Locking_Policy#");
9111
9112                --  Set the Ceiling_Locking policy, but preserve System_Location
9113                --  since we like the error message with the run time name.
9114
9115                else
9116                   Locking_Policy := 'C';
9117
9118                   if Locking_Policy_Sloc /= System_Location then
9119                      Locking_Policy_Sloc := Loc;
9120                   end if;
9121                end if;
9122
9123                --  Add entry in the table
9124
9125                Specific_Dispatching.Append
9126                     ((Dispatching_Policy => DP,
9127                       First_Priority     => UI_To_Int (Lower_Val),
9128                       Last_Priority      => UI_To_Int (Upper_Val),
9129                       Pragma_Loc         => Loc));
9130             end if;
9131          end Priority_Specific_Dispatching;
9132
9133          -------------
9134          -- Profile --
9135          -------------
9136
9137          --  pragma Profile (profile_IDENTIFIER);
9138
9139          --  profile_IDENTIFIER => Protected | Ravenscar
9140
9141          when Pragma_Profile =>
9142             Ada_2005_Pragma;
9143             Check_Arg_Count (1);
9144             Check_Valid_Configuration_Pragma;
9145             Check_No_Identifiers;
9146
9147             declare
9148                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
9149             begin
9150                if Chars (Argx) = Name_Ravenscar then
9151                   Set_Ravenscar_Profile (N);
9152                elsif Chars (Argx) = Name_Restricted then
9153                   Set_Profile_Restrictions (Restricted, N, Warn => False);
9154                else
9155                   Error_Pragma_Arg ("& is not a valid profile", Argx);
9156                end if;
9157             end;
9158
9159          ----------------------
9160          -- Profile_Warnings --
9161          ----------------------
9162
9163          --  pragma Profile_Warnings (profile_IDENTIFIER);
9164
9165          --  profile_IDENTIFIER => Protected | Ravenscar
9166
9167          when Pragma_Profile_Warnings =>
9168             GNAT_Pragma;
9169             Check_Arg_Count (1);
9170             Check_Valid_Configuration_Pragma;
9171             Check_No_Identifiers;
9172
9173             declare
9174                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
9175             begin
9176                if Chars (Argx) = Name_Ravenscar then
9177                   Set_Profile_Restrictions (Ravenscar, N, Warn => True);
9178                elsif Chars (Argx) = Name_Restricted then
9179                   Set_Profile_Restrictions (Restricted, N, Warn => True);
9180                else
9181                   Error_Pragma_Arg ("& is not a valid profile", Argx);
9182                end if;
9183             end;
9184
9185          --------------------------
9186          -- Propagate_Exceptions --
9187          --------------------------
9188
9189          --  pragma Propagate_Exceptions;
9190
9191          --  Note: this pragma is obsolete and has no effect
9192
9193          when Pragma_Propagate_Exceptions =>
9194             GNAT_Pragma;
9195             Check_Arg_Count (0);
9196
9197             if In_Extended_Main_Source_Unit (N) then
9198                Propagate_Exceptions := True;
9199             end if;
9200
9201          ------------------
9202          -- Psect_Object --
9203          ------------------
9204
9205          --  pragma Psect_Object (
9206          --        [Internal =>] LOCAL_NAME,
9207          --     [, [External =>] EXTERNAL_SYMBOL]
9208          --     [, [Size     =>] EXTERNAL_SYMBOL]);
9209
9210          when Pragma_Psect_Object | Pragma_Common_Object =>
9211          Psect_Object : declare
9212             Args  : Args_List (1 .. 3);
9213             Names : constant Name_List (1 .. 3) := (
9214                       Name_Internal,
9215                       Name_External,
9216                       Name_Size);
9217
9218             Internal : Node_Id renames Args (1);
9219             External : Node_Id renames Args (2);
9220             Size     : Node_Id renames Args (3);
9221
9222             Def_Id : Entity_Id;
9223
9224             procedure Check_Too_Long (Arg : Node_Id);
9225             --  Posts message if the argument is an identifier with more
9226             --  than 31 characters, or a string literal with more than
9227             --  31 characters, and we are operating under VMS
9228
9229             --------------------
9230             -- Check_Too_Long --
9231             --------------------
9232
9233             procedure Check_Too_Long (Arg : Node_Id) is
9234                X : constant Node_Id := Original_Node (Arg);
9235
9236             begin
9237                if Nkind (X) /= N_String_Literal
9238                     and then
9239                   Nkind (X) /= N_Identifier
9240                then
9241                   Error_Pragma_Arg
9242                     ("inappropriate argument for pragma %", Arg);
9243                end if;
9244
9245                if OpenVMS_On_Target then
9246                   if (Nkind (X) = N_String_Literal
9247                        and then String_Length (Strval (X)) > 31)
9248                     or else
9249                      (Nkind (X) = N_Identifier
9250                        and then Length_Of_Name (Chars (X)) > 31)
9251                   then
9252                      Error_Pragma_Arg
9253                        ("argument for pragma % is longer than 31 characters",
9254                         Arg);
9255                   end if;
9256                end if;
9257             end Check_Too_Long;
9258
9259          --  Start of processing for Common_Object/Psect_Object
9260
9261          begin
9262             GNAT_Pragma;
9263             Gather_Associations (Names, Args);
9264             Process_Extended_Import_Export_Internal_Arg (Internal);
9265
9266             Def_Id := Entity (Internal);
9267
9268             if Ekind (Def_Id) /= E_Constant
9269               and then Ekind (Def_Id) /= E_Variable
9270             then
9271                Error_Pragma_Arg
9272                  ("pragma% must designate an object", Internal);
9273             end if;
9274
9275             Check_Too_Long (Internal);
9276
9277             if Is_Imported (Def_Id) or else Is_Exported (Def_Id) then
9278                Error_Pragma_Arg
9279                  ("cannot use pragma% for imported/exported object",
9280                   Internal);
9281             end if;
9282
9283             if Is_Concurrent_Type (Etype (Internal)) then
9284                Error_Pragma_Arg
9285                  ("cannot specify pragma % for task/protected object",
9286                   Internal);
9287             end if;
9288
9289             if Has_Rep_Pragma (Def_Id, Name_Common_Object)
9290                  or else
9291                Has_Rep_Pragma (Def_Id, Name_Psect_Object)
9292             then
9293                Error_Msg_N ("?duplicate Common/Psect_Object pragma", N);
9294             end if;
9295
9296             if Ekind (Def_Id) = E_Constant then
9297                Error_Pragma_Arg
9298                  ("cannot specify pragma % for a constant", Internal);
9299             end if;
9300
9301             if Is_Record_Type (Etype (Internal)) then
9302                declare
9303                   Ent  : Entity_Id;
9304                   Decl : Entity_Id;
9305
9306                begin
9307                   Ent := First_Entity (Etype (Internal));
9308                   while Present (Ent) loop
9309                      Decl := Declaration_Node (Ent);
9310
9311                      if Ekind (Ent) = E_Component
9312                        and then Nkind (Decl) = N_Component_Declaration
9313                        and then Present (Expression (Decl))
9314                        and then Warn_On_Export_Import
9315                      then
9316                         Error_Msg_N
9317                           ("?object for pragma % has defaults", Internal);
9318                         exit;
9319
9320                      else
9321                         Next_Entity (Ent);
9322                      end if;
9323                   end loop;
9324                end;
9325             end if;
9326
9327             if Present (Size) then
9328                Check_Too_Long (Size);
9329             end if;
9330
9331             if Present (External) then
9332                Check_Arg_Is_External_Name (External);
9333                Check_Too_Long (External);
9334             end if;
9335
9336             --  If all error tests pass, link pragma on to the rep item chain
9337
9338             Record_Rep_Item (Def_Id, N);
9339          end Psect_Object;
9340
9341          ----------
9342          -- Pure --
9343          ----------
9344
9345          --  pragma Pure [(library_unit_NAME)];
9346
9347          when Pragma_Pure => Pure : declare
9348             Ent : Entity_Id;
9349
9350          begin
9351             Check_Ada_83_Warning;
9352             Check_Valid_Library_Unit_Pragma;
9353
9354             if Nkind (N) = N_Null_Statement then
9355                return;
9356             end if;
9357
9358             Ent := Find_Lib_Unit_Name;
9359             Set_Is_Pure (Ent);
9360             Set_Has_Pragma_Pure (Ent);
9361             Set_Suppress_Elaboration_Warnings (Ent);
9362          end Pure;
9363
9364          -------------
9365          -- Pure_05 --
9366          -------------
9367
9368          --  pragma Pure_05 [(library_unit_NAME)];
9369
9370          --  This pragma is useable only in GNAT_Mode, where it is used like
9371          --  pragma Pure but it is only effective in Ada 2005 mode (otherwise
9372          --  it is ignored). It may be used after a pragma Preelaborate, in
9373          --  which case it overrides the effect of the pragma Preelaborate.
9374          --  This is used to implement AI-362 which recategorizes some run-time
9375          --  packages in Ada 2005 mode.
9376
9377          when Pragma_Pure_05 => Pure_05 : declare
9378             Ent : Entity_Id;
9379
9380          begin
9381             GNAT_Pragma;
9382             Check_Valid_Library_Unit_Pragma;
9383
9384             if not GNAT_Mode then
9385                Error_Pragma ("pragma% only available in GNAT mode");
9386             end if;
9387             if Nkind (N) = N_Null_Statement then
9388                return;
9389             end if;
9390
9391             --  This is one of the few cases where we need to test the value of
9392             --  Ada_Version_Explicit rather than Ada_Version (which is always
9393             --  set to Ada_05 in a predefined unit), we need to know the
9394             --  explicit version set to know if this pragma is active.
9395
9396             if Ada_Version_Explicit >= Ada_05 then
9397                Ent := Find_Lib_Unit_Name;
9398                Set_Is_Preelaborated (Ent, False);
9399                Set_Is_Pure (Ent);
9400                Set_Suppress_Elaboration_Warnings (Ent);
9401             end if;
9402          end Pure_05;
9403
9404          -------------------
9405          -- Pure_Function --
9406          -------------------
9407
9408          --  pragma Pure_Function ([Entity =>] function_LOCAL_NAME);
9409
9410          when Pragma_Pure_Function => Pure_Function : declare
9411             E_Id      : Node_Id;
9412             E         : Entity_Id;
9413             Def_Id    : Entity_Id;
9414             Effective : Boolean := False;
9415
9416          begin
9417             GNAT_Pragma;
9418             Check_Arg_Count (1);
9419             Check_Optional_Identifier (Arg1, Name_Entity);
9420             Check_Arg_Is_Local_Name (Arg1);
9421             E_Id := Expression (Arg1);
9422
9423             if Error_Posted (E_Id) then
9424                return;
9425             end if;
9426
9427             --  Loop through homonyms (overloadings) of referenced entity
9428
9429             E := Entity (E_Id);
9430
9431             if Present (E) then
9432                loop
9433                   Def_Id := Get_Base_Subprogram (E);
9434
9435                   if Ekind (Def_Id) /= E_Function
9436                     and then Ekind (Def_Id) /= E_Generic_Function
9437                     and then Ekind (Def_Id) /= E_Operator
9438                   then
9439                      Error_Pragma_Arg
9440                        ("pragma% requires a function name", Arg1);
9441                   end if;
9442
9443                   Set_Is_Pure (Def_Id);
9444
9445                   if not Has_Pragma_Pure_Function (Def_Id) then
9446                      Set_Has_Pragma_Pure_Function (Def_Id);
9447                      Effective := True;
9448                   end if;
9449
9450                   E := Homonym (E);
9451                   exit when No (E) or else Scope (E) /= Current_Scope;
9452                end loop;
9453
9454                if not Effective
9455                  and then Warn_On_Redundant_Constructs
9456                then
9457                   Error_Msg_NE ("pragma Pure_Function on& is redundant?",
9458                     N, Entity (E_Id));
9459                end if;
9460             end if;
9461          end Pure_Function;
9462
9463          --------------------
9464          -- Queuing_Policy --
9465          --------------------
9466
9467          --  pragma Queuing_Policy (policy_IDENTIFIER);
9468
9469          when Pragma_Queuing_Policy => declare
9470             QP : Character;
9471
9472          begin
9473             Check_Ada_83_Warning;
9474             Check_Arg_Count (1);
9475             Check_No_Identifiers;
9476             Check_Arg_Is_Queuing_Policy (Arg1);
9477             Check_Valid_Configuration_Pragma;
9478             Get_Name_String (Chars (Expression (Arg1)));
9479             QP := Fold_Upper (Name_Buffer (1));
9480
9481             if Queuing_Policy /= ' '
9482               and then Queuing_Policy /= QP
9483             then
9484                Error_Msg_Sloc := Queuing_Policy_Sloc;
9485                Error_Pragma ("queuing policy incompatible with policy#");
9486
9487             --  Set new policy, but always preserve System_Location since
9488             --  we like the error message with the run time name.
9489
9490             else
9491                Queuing_Policy := QP;
9492
9493                if Queuing_Policy_Sloc /= System_Location then
9494                   Queuing_Policy_Sloc := Loc;
9495                end if;
9496             end if;
9497          end;
9498
9499          ---------------------------
9500          -- Remote_Call_Interface --
9501          ---------------------------
9502
9503          --  pragma Remote_Call_Interface [(library_unit_NAME)];
9504
9505          when Pragma_Remote_Call_Interface => Remote_Call_Interface : declare
9506             Cunit_Node : Node_Id;
9507             Cunit_Ent  : Entity_Id;
9508             K          : Node_Kind;
9509
9510          begin
9511             Check_Ada_83_Warning;
9512             Check_Valid_Library_Unit_Pragma;
9513
9514             if Nkind (N) = N_Null_Statement then
9515                return;
9516             end if;
9517
9518             Cunit_Node := Cunit (Current_Sem_Unit);
9519             K          := Nkind (Unit (Cunit_Node));
9520             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
9521
9522             if K = N_Package_Declaration
9523               or else K = N_Generic_Package_Declaration
9524               or else K = N_Subprogram_Declaration
9525               or else K = N_Generic_Subprogram_Declaration
9526               or else (K = N_Subprogram_Body
9527                          and then Acts_As_Spec (Unit (Cunit_Node)))
9528             then
9529                null;
9530             else
9531                Error_Pragma (
9532                  "pragma% must apply to package or subprogram declaration");
9533             end if;
9534
9535             Set_Is_Remote_Call_Interface (Cunit_Ent);
9536          end Remote_Call_Interface;
9537
9538          ------------------
9539          -- Remote_Types --
9540          ------------------
9541
9542          --  pragma Remote_Types [(library_unit_NAME)];
9543
9544          when Pragma_Remote_Types => Remote_Types : declare
9545             Cunit_Node : Node_Id;
9546             Cunit_Ent  : Entity_Id;
9547
9548          begin
9549             Check_Ada_83_Warning;
9550             Check_Valid_Library_Unit_Pragma;
9551
9552             if Nkind (N) = N_Null_Statement then
9553                return;
9554             end if;
9555
9556             Cunit_Node := Cunit (Current_Sem_Unit);
9557             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
9558
9559             if Nkind (Unit (Cunit_Node)) /= N_Package_Declaration
9560               and then
9561               Nkind (Unit (Cunit_Node)) /= N_Generic_Package_Declaration
9562             then
9563                Error_Pragma (
9564                  "pragma% can only apply to a package declaration");
9565             end if;
9566
9567             Set_Is_Remote_Types (Cunit_Ent);
9568          end Remote_Types;
9569
9570          ---------------
9571          -- Ravenscar --
9572          ---------------
9573
9574          --  pragma Ravenscar;
9575
9576          when Pragma_Ravenscar =>
9577             GNAT_Pragma;
9578             Check_Arg_Count (0);
9579             Check_Valid_Configuration_Pragma;
9580             Set_Ravenscar_Profile (N);
9581
9582             if Warn_On_Obsolescent_Feature then
9583                Error_Msg_N
9584                  ("pragma Ravenscar is an obsolescent feature?", N);
9585                Error_Msg_N
9586                  ("|use pragma Profile (Ravenscar) instead", N);
9587             end if;
9588
9589          -------------------------
9590          -- Restricted_Run_Time --
9591          -------------------------
9592
9593          --  pragma Restricted_Run_Time;
9594
9595          when Pragma_Restricted_Run_Time =>
9596             GNAT_Pragma;
9597             Check_Arg_Count (0);
9598             Check_Valid_Configuration_Pragma;
9599             Set_Profile_Restrictions (Restricted, N, Warn => False);
9600
9601             if Warn_On_Obsolescent_Feature then
9602                Error_Msg_N
9603                  ("pragma Restricted_Run_Time is an obsolescent feature?", N);
9604                Error_Msg_N
9605                  ("|use pragma Profile (Restricted) instead", N);
9606             end if;
9607
9608          ------------------
9609          -- Restrictions --
9610          ------------------
9611
9612          --  pragma Restrictions (RESTRICTION {, RESTRICTION});
9613
9614          --  RESTRICTION ::=
9615          --    restriction_IDENTIFIER
9616          --  | restriction_parameter_IDENTIFIER => EXPRESSION
9617
9618          when Pragma_Restrictions =>
9619             Process_Restrictions_Or_Restriction_Warnings (Warn => False);
9620
9621          --------------------------
9622          -- Restriction_Warnings --
9623          --------------------------
9624
9625          --  pragma Restriction_Warnings (RESTRICTION {, RESTRICTION});
9626
9627          --  RESTRICTION ::=
9628          --    restriction_IDENTIFIER
9629          --  | restriction_parameter_IDENTIFIER => EXPRESSION
9630
9631          when Pragma_Restriction_Warnings =>
9632             Process_Restrictions_Or_Restriction_Warnings (Warn => True);
9633
9634          ----------------
9635          -- Reviewable --
9636          ----------------
9637
9638          --  pragma Reviewable;
9639
9640          when Pragma_Reviewable =>
9641             Check_Ada_83_Warning;
9642             Check_Arg_Count (0);
9643             rv;
9644
9645          -------------------
9646          -- Share_Generic --
9647          -------------------
9648
9649          --  pragma Share_Generic (NAME {, NAME});
9650
9651          when Pragma_Share_Generic =>
9652             GNAT_Pragma;
9653             Process_Generic_List;
9654
9655          ------------
9656          -- Shared --
9657          ------------
9658
9659          --  pragma Shared (LOCAL_NAME);
9660
9661          when Pragma_Shared =>
9662             GNAT_Pragma;
9663             Process_Atomic_Shared_Volatile;
9664
9665          --------------------
9666          -- Shared_Passive --
9667          --------------------
9668
9669          --  pragma Shared_Passive [(library_unit_NAME)];
9670
9671          --  Set the flag Is_Shared_Passive of program unit name entity
9672
9673          when Pragma_Shared_Passive => Shared_Passive : declare
9674             Cunit_Node : Node_Id;
9675             Cunit_Ent  : Entity_Id;
9676
9677          begin
9678             Check_Ada_83_Warning;
9679             Check_Valid_Library_Unit_Pragma;
9680
9681             if Nkind (N) = N_Null_Statement then
9682                return;
9683             end if;
9684
9685             Cunit_Node := Cunit (Current_Sem_Unit);
9686             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
9687
9688             if Nkind (Unit (Cunit_Node)) /= N_Package_Declaration
9689               and then
9690               Nkind (Unit (Cunit_Node)) /= N_Generic_Package_Declaration
9691             then
9692                Error_Pragma (
9693                  "pragma% can only apply to a package declaration");
9694             end if;
9695
9696             Set_Is_Shared_Passive (Cunit_Ent);
9697          end Shared_Passive;
9698
9699          ----------------------
9700          -- Source_File_Name --
9701          ----------------------
9702
9703          --  There are five forms for this pragma:
9704
9705          --  pragma Source_File_Name (
9706          --    [UNIT_NAME      =>] unit_NAME,
9707          --     BODY_FILE_NAME =>  STRING_LITERAL
9708          --    [, [INDEX =>] INTEGER_LITERAL]);
9709
9710          --  pragma Source_File_Name (
9711          --    [UNIT_NAME      =>] unit_NAME,
9712          --     SPEC_FILE_NAME =>  STRING_LITERAL
9713          --    [, [INDEX =>] INTEGER_LITERAL]);
9714
9715          --  pragma Source_File_Name (
9716          --     BODY_FILE_NAME  => STRING_LITERAL
9717          --  [, DOT_REPLACEMENT => STRING_LITERAL]
9718          --  [, CASING          => CASING_SPEC]);
9719
9720          --  pragma Source_File_Name (
9721          --     SPEC_FILE_NAME  => STRING_LITERAL
9722          --  [, DOT_REPLACEMENT => STRING_LITERAL]
9723          --  [, CASING          => CASING_SPEC]);
9724
9725          --  pragma Source_File_Name (
9726          --     SUBUNIT_FILE_NAME  => STRING_LITERAL
9727          --  [, DOT_REPLACEMENT    => STRING_LITERAL]
9728          --  [, CASING             => CASING_SPEC]);
9729
9730          --  CASING_SPEC ::= Uppercase | Lowercase | Mixedcase
9731
9732          --  Pragma Source_File_Name_Project (SFNP) is equivalent to pragma
9733          --  Source_File_Name (SFN), however their usage is exclusive:
9734          --  SFN can only be used when no project file is used, while
9735          --  SFNP can only be used when a project file is used.
9736
9737          --  No processing here. Processing was completed during parsing,
9738          --  since we need to have file names set as early as possible.
9739          --  Units are loaded well before semantic processing starts.
9740
9741          --  The only processing we defer to this point is the check
9742          --  for correct placement.
9743
9744          when Pragma_Source_File_Name =>
9745             GNAT_Pragma;
9746             Check_Valid_Configuration_Pragma;
9747
9748          ------------------------------
9749          -- Source_File_Name_Project --
9750          ------------------------------
9751
9752          --  See Source_File_Name for syntax
9753
9754          --  No processing here. Processing was completed during parsing,
9755          --  since we need to have file names set as early as possible.
9756          --  Units are loaded well before semantic processing starts.
9757
9758          --  The only processing we defer to this point is the check
9759          --  for correct placement.
9760
9761          when Pragma_Source_File_Name_Project =>
9762             GNAT_Pragma;
9763             Check_Valid_Configuration_Pragma;
9764
9765             --  Check that a pragma Source_File_Name_Project is used only
9766             --  in a configuration pragmas file.
9767
9768             --  Pragmas Source_File_Name_Project should only be generated
9769             --  by the Project Manager in configuration pragmas files.
9770
9771             --  This is really an ugly test. It seems to depend on some
9772             --  accidental and undocumented property. At the very least
9773             --  it needs to be documented, but it would be better to have
9774             --  a clean way of testing if we are in a configuration file???
9775
9776             if Present (Parent (N)) then
9777                Error_Pragma
9778                  ("pragma% can only appear in a configuration pragmas file");
9779             end if;
9780
9781          ----------------------
9782          -- Source_Reference --
9783          ----------------------
9784
9785          --  pragma Source_Reference (INTEGER_LITERAL [, STRING_LITERAL]);
9786
9787          --  Nothing to do, all processing completed in Par.Prag, since we
9788          --  need the information for possible parser messages that are output
9789
9790          when Pragma_Source_Reference =>
9791             GNAT_Pragma;
9792
9793          --------------------------------
9794          -- Static_Elaboration_Desired --
9795          --------------------------------
9796
9797          --  pragma Static_Elaboration_Desired (DIRECT_NAME);
9798
9799          when Pragma_Static_Elaboration_Desired =>
9800             GNAT_Pragma;
9801             Check_At_Most_N_Arguments (1);
9802
9803             if Is_Compilation_Unit (Current_Scope)
9804               and then Ekind (Current_Scope) = E_Package
9805             then
9806                Set_Static_Elaboration_Desired (Current_Scope, True);
9807             else
9808                Error_Pragma ("pragma% must apply to a library-level package");
9809             end if;
9810
9811          ------------------
9812          -- Storage_Size --
9813          ------------------
9814
9815          --  pragma Storage_Size (EXPRESSION);
9816
9817          when Pragma_Storage_Size => Storage_Size : declare
9818             P   : constant Node_Id := Parent (N);
9819             Arg : Node_Id;
9820
9821          begin
9822             Check_No_Identifiers;
9823             Check_Arg_Count (1);
9824
9825             --  The expression must be analyzed in the special manner
9826             --  described in "Handling of Default Expressions" in sem.ads.
9827
9828             --  Set In_Default_Expression for per-object case ???
9829
9830             Arg := Expression (Arg1);
9831             Analyze_Per_Use_Expression (Arg, Any_Integer);
9832
9833             if not Is_Static_Expression (Arg) then
9834                Check_Restriction (Static_Storage_Size, Arg);
9835             end if;
9836
9837             if Nkind (P) /= N_Task_Definition then
9838                Pragma_Misplaced;
9839                return;
9840
9841             else
9842                if Has_Storage_Size_Pragma (P) then
9843                   Error_Pragma ("duplicate pragma% not allowed");
9844                else
9845                   Set_Has_Storage_Size_Pragma (P, True);
9846                end if;
9847
9848                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
9849                --  ???  exp_ch9 should use this!
9850             end if;
9851          end Storage_Size;
9852
9853          ------------------
9854          -- Storage_Unit --
9855          ------------------
9856
9857          --  pragma Storage_Unit (NUMERIC_LITERAL);
9858
9859          --  Only permitted argument is System'Storage_Unit value
9860
9861          when Pragma_Storage_Unit =>
9862             Check_No_Identifiers;
9863             Check_Arg_Count (1);
9864             Check_Arg_Is_Integer_Literal (Arg1);
9865
9866             if Intval (Expression (Arg1)) /=
9867               UI_From_Int (Ttypes.System_Storage_Unit)
9868             then
9869                Error_Msg_Uint_1 := UI_From_Int (Ttypes.System_Storage_Unit);
9870                Error_Pragma_Arg
9871                  ("the only allowed argument for pragma% is ^", Arg1);
9872             end if;
9873
9874          --------------------
9875          -- Stream_Convert --
9876          --------------------
9877
9878          --  pragma Stream_Convert (
9879          --    [Entity =>] type_LOCAL_NAME,
9880          --    [Read   =>] function_NAME,
9881          --    [Write  =>] function NAME);
9882
9883          when Pragma_Stream_Convert => Stream_Convert : declare
9884
9885             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id);
9886             --  Check that the given argument is the name of a local
9887             --  function of one argument that is not overloaded earlier
9888             --  in the current local scope. A check is also made that the
9889             --  argument is a function with one parameter.
9890
9891             --------------------------------------
9892             -- Check_OK_Stream_Convert_Function --
9893             --------------------------------------
9894
9895             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id) is
9896                Ent : Entity_Id;
9897
9898             begin
9899                Check_Arg_Is_Local_Name (Arg);
9900                Ent := Entity (Expression (Arg));
9901
9902                if Has_Homonym (Ent) then
9903                   Error_Pragma_Arg
9904                     ("argument for pragma% may not be overloaded", Arg);
9905                end if;
9906
9907                if Ekind (Ent) /= E_Function
9908                  or else No (First_Formal (Ent))
9909                  or else Present (Next_Formal (First_Formal (Ent)))
9910                then
9911                   Error_Pragma_Arg
9912                     ("argument for pragma% must be" &
9913                      " function of one argument", Arg);
9914                end if;
9915             end Check_OK_Stream_Convert_Function;
9916
9917          --  Start of procecessing for Stream_Convert
9918
9919          begin
9920             GNAT_Pragma;
9921             Check_Arg_Order ((Name_Entity, Name_Read, Name_Write));
9922             Check_Arg_Count (3);
9923             Check_Optional_Identifier (Arg1, Name_Entity);
9924             Check_Optional_Identifier (Arg2, Name_Read);
9925             Check_Optional_Identifier (Arg3, Name_Write);
9926             Check_Arg_Is_Local_Name (Arg1);
9927             Check_OK_Stream_Convert_Function (Arg2);
9928             Check_OK_Stream_Convert_Function (Arg3);
9929
9930             declare
9931                Typ   : constant Entity_Id :=
9932                          Underlying_Type (Entity (Expression (Arg1)));
9933                Read  : constant Entity_Id := Entity (Expression (Arg2));
9934                Write : constant Entity_Id := Entity (Expression (Arg3));
9935
9936             begin
9937                if Etype (Typ) = Any_Type
9938                     or else
9939                   Etype (Read) = Any_Type
9940                     or else
9941                   Etype (Write) = Any_Type
9942                then
9943                   return;
9944                end if;
9945
9946                Check_First_Subtype (Arg1);
9947
9948                if Rep_Item_Too_Early (Typ, N)
9949                     or else
9950                   Rep_Item_Too_Late (Typ, N)
9951                then
9952                   return;
9953                end if;
9954
9955                if Underlying_Type (Etype (Read)) /= Typ then
9956                   Error_Pragma_Arg
9957                     ("incorrect return type for function&", Arg2);
9958                end if;
9959
9960                if Underlying_Type (Etype (First_Formal (Write))) /= Typ then
9961                   Error_Pragma_Arg
9962                     ("incorrect parameter type for function&", Arg3);
9963                end if;
9964
9965                if Underlying_Type (Etype (First_Formal (Read))) /=
9966                   Underlying_Type (Etype (Write))
9967                then
9968                   Error_Pragma_Arg
9969                     ("result type of & does not match Read parameter type",
9970                      Arg3);
9971                end if;
9972             end;
9973          end Stream_Convert;
9974
9975          -------------------------
9976          -- Style_Checks (GNAT) --
9977          -------------------------
9978
9979          --  pragma Style_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
9980
9981          --  This is processed by the parser since some of the style
9982          --  checks take place during source scanning and parsing. This
9983          --  means that we don't need to issue error messages here.
9984
9985          when Pragma_Style_Checks => Style_Checks : declare
9986             A  : constant Node_Id   := Expression (Arg1);
9987             S  : String_Id;
9988             C  : Char_Code;
9989
9990          begin
9991             GNAT_Pragma;
9992             Check_No_Identifiers;
9993
9994             --  Two argument form
9995
9996             if Arg_Count = 2 then
9997                Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
9998
9999                declare
10000                   E_Id : Node_Id;
10001                   E    : Entity_Id;
10002
10003                begin
10004                   E_Id := Expression (Arg2);
10005                   Analyze (E_Id);
10006
10007                   if not Is_Entity_Name (E_Id) then
10008                      Error_Pragma_Arg
10009                        ("second argument of pragma% must be entity name",
10010                         Arg2);
10011                   end if;
10012
10013                   E := Entity (E_Id);
10014
10015                   if E = Any_Id then
10016                      return;
10017                   else
10018                      loop
10019                         Set_Suppress_Style_Checks (E,
10020                           (Chars (Expression (Arg1)) = Name_Off));
10021                         exit when No (Homonym (E));
10022                         E := Homonym (E);
10023                      end loop;
10024                   end if;
10025                end;
10026
10027             --  One argument form
10028
10029             else
10030                Check_Arg_Count (1);
10031
10032                if Nkind (A) = N_String_Literal then
10033                   S   := Strval (A);
10034
10035                   declare
10036                      Slen    : constant Natural := Natural (String_Length (S));
10037                      Options : String (1 .. Slen);
10038                      J       : Natural;
10039
10040                   begin
10041                      J := 1;
10042                      loop
10043                         C := Get_String_Char (S, Int (J));
10044                         exit when not In_Character_Range (C);
10045                         Options (J) := Get_Character (C);
10046
10047                         --  If at end of string, set options. As per discussion
10048                         --  above, no need to check for errors, since we issued
10049                         --  them in the parser.
10050
10051                         if J = Slen then
10052                            Set_Style_Check_Options (Options);
10053                            exit;
10054                         end if;
10055
10056                         J := J + 1;
10057                      end loop;
10058                   end;
10059
10060                elsif Nkind (A) = N_Identifier then
10061                   if Chars (A) = Name_All_Checks then
10062                      Set_Default_Style_Check_Options;
10063
10064                   elsif Chars (A) = Name_On then
10065                      Style_Check := True;
10066
10067                   elsif Chars (A) = Name_Off then
10068                      Style_Check := False;
10069                   end if;
10070                end if;
10071             end if;
10072          end Style_Checks;
10073
10074          --------------
10075          -- Subtitle --
10076          --------------
10077
10078          --  pragma Subtitle ([Subtitle =>] STRING_LITERAL);
10079
10080          when Pragma_Subtitle =>
10081             GNAT_Pragma;
10082             Check_Arg_Count (1);
10083             Check_Optional_Identifier (Arg1, Name_Subtitle);
10084             Check_Arg_Is_String_Literal (Arg1);
10085
10086          --------------
10087          -- Suppress --
10088          --------------
10089
10090          --  pragma Suppress (IDENTIFIER [, [On =>] NAME]);
10091
10092          when Pragma_Suppress =>
10093             Process_Suppress_Unsuppress (True);
10094
10095          ------------------
10096          -- Suppress_All --
10097          ------------------
10098
10099          --  pragma Suppress_All;
10100
10101          --  The only check made here is that the pragma appears in the
10102          --  proper place, i.e. following a compilation unit. If indeed
10103          --  it appears in this context, then the parser has already
10104          --  inserted an equivalent pragma Suppress (All_Checks) to get
10105          --  the required effect.
10106
10107          when Pragma_Suppress_All =>
10108             GNAT_Pragma;
10109             Check_Arg_Count (0);
10110
10111             if Nkind (Parent (N)) /= N_Compilation_Unit_Aux
10112               or else not Is_List_Member (N)
10113               or else List_Containing (N) /= Pragmas_After (Parent (N))
10114             then
10115                Error_Pragma
10116                  ("misplaced pragma%, must follow compilation unit");
10117             end if;
10118
10119          -------------------------
10120          -- Suppress_Debug_Info --
10121          -------------------------
10122
10123          --  pragma Suppress_Debug_Info ([Entity =>] LOCAL_NAME);
10124
10125          when Pragma_Suppress_Debug_Info =>
10126             GNAT_Pragma;
10127             Check_Arg_Count (1);
10128             Check_Optional_Identifier (Arg1, Name_Entity);
10129             Check_Arg_Is_Local_Name (Arg1);
10130             Set_Debug_Info_Off (Entity (Get_Pragma_Arg (Arg1)));
10131
10132          ----------------------------------
10133          -- Suppress_Exception_Locations --
10134          ----------------------------------
10135
10136          --  pragma Suppress_Exception_Locations;
10137
10138          when Pragma_Suppress_Exception_Locations =>
10139             GNAT_Pragma;
10140             Check_Arg_Count (0);
10141             Check_Valid_Configuration_Pragma;
10142             Exception_Locations_Suppressed := True;
10143
10144          -----------------------------
10145          -- Suppress_Initialization --
10146          -----------------------------
10147
10148          --  pragma Suppress_Initialization ([Entity =>] type_Name);
10149
10150          when Pragma_Suppress_Initialization => Suppress_Init : declare
10151             E_Id : Node_Id;
10152             E    : Entity_Id;
10153
10154          begin
10155             GNAT_Pragma;
10156             Check_Arg_Count (1);
10157             Check_Optional_Identifier (Arg1, Name_Entity);
10158             Check_Arg_Is_Local_Name (Arg1);
10159
10160             E_Id := Expression (Arg1);
10161
10162             if Etype (E_Id) = Any_Type then
10163                return;
10164             end if;
10165
10166             E := Entity (E_Id);
10167
10168             if Is_Type (E) then
10169                if Is_Incomplete_Or_Private_Type (E) then
10170                   if No (Full_View (Base_Type (E))) then
10171                      Error_Pragma_Arg
10172                        ("argument of pragma% cannot be an incomplete type",
10173                          Arg1);
10174                   else
10175                      Set_Suppress_Init_Proc (Full_View (Base_Type (E)));
10176                   end if;
10177                else
10178                   Set_Suppress_Init_Proc (Base_Type (E));
10179                end if;
10180
10181             else
10182                Error_Pragma_Arg
10183                  ("pragma% requires argument that is a type name", Arg1);
10184             end if;
10185          end Suppress_Init;
10186
10187          -----------------
10188          -- System_Name --
10189          -----------------
10190
10191          --  pragma System_Name (DIRECT_NAME);
10192
10193          --  Syntax check: one argument, which must be the identifier GNAT
10194          --  or the identifier GCC, no other identifiers are acceptable.
10195
10196          when Pragma_System_Name =>
10197             Check_No_Identifiers;
10198             Check_Arg_Count (1);
10199             Check_Arg_Is_One_Of (Arg1, Name_Gcc, Name_Gnat);
10200
10201          -----------------------------
10202          -- Task_Dispatching_Policy --
10203          -----------------------------
10204
10205          --  pragma Task_Dispatching_Policy (policy_IDENTIFIER);
10206
10207          when Pragma_Task_Dispatching_Policy => declare
10208             DP : Character;
10209
10210          begin
10211             Check_Ada_83_Warning;
10212             Check_Arg_Count (1);
10213             Check_No_Identifiers;
10214             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
10215             Check_Valid_Configuration_Pragma;
10216             Get_Name_String (Chars (Expression (Arg1)));
10217             DP := Fold_Upper (Name_Buffer (1));
10218
10219             if Task_Dispatching_Policy /= ' '
10220               and then Task_Dispatching_Policy /= DP
10221             then
10222                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
10223                Error_Pragma
10224                  ("task dispatching policy incompatible with policy#");
10225
10226             --  Set new policy, but always preserve System_Location since
10227             --  we like the error message with the run time name.
10228
10229             else
10230                Task_Dispatching_Policy := DP;
10231
10232                if Task_Dispatching_Policy_Sloc /= System_Location then
10233                   Task_Dispatching_Policy_Sloc := Loc;
10234                end if;
10235             end if;
10236          end;
10237
10238          --------------
10239          -- Task_Info --
10240          --------------
10241
10242          --  pragma Task_Info (EXPRESSION);
10243
10244          when Pragma_Task_Info => Task_Info : declare
10245             P : constant Node_Id := Parent (N);
10246
10247          begin
10248             GNAT_Pragma;
10249
10250             if Nkind (P) /= N_Task_Definition then
10251                Error_Pragma ("pragma% must appear in task definition");
10252             end if;
10253
10254             Check_No_Identifiers;
10255             Check_Arg_Count (1);
10256
10257             Analyze_And_Resolve (Expression (Arg1), RTE (RE_Task_Info_Type));
10258
10259             if Etype (Expression (Arg1)) = Any_Type then
10260                return;
10261             end if;
10262
10263             if Has_Task_Info_Pragma (P) then
10264                Error_Pragma ("duplicate pragma% not allowed");
10265             else
10266                Set_Has_Task_Info_Pragma (P, True);
10267             end if;
10268          end Task_Info;
10269
10270          ---------------
10271          -- Task_Name --
10272          ---------------
10273
10274          --  pragma Task_Name (string_EXPRESSION);
10275
10276          when Pragma_Task_Name => Task_Name : declare
10277          --  pragma Priority (EXPRESSION);
10278
10279             P   : constant Node_Id := Parent (N);
10280             Arg : Node_Id;
10281
10282          begin
10283             Check_No_Identifiers;
10284             Check_Arg_Count (1);
10285
10286             Arg := Expression (Arg1);
10287             Analyze_And_Resolve (Arg, Standard_String);
10288
10289             if Nkind (P) /= N_Task_Definition then
10290                Pragma_Misplaced;
10291             end if;
10292
10293             if Has_Task_Name_Pragma (P) then
10294                Error_Pragma ("duplicate pragma% not allowed");
10295             else
10296                Set_Has_Task_Name_Pragma (P, True);
10297                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
10298             end if;
10299          end Task_Name;
10300
10301          ------------------
10302          -- Task_Storage --
10303          ------------------
10304
10305          --  pragma Task_Storage (
10306          --     [Task_Type =>] LOCAL_NAME,
10307          --     [Top_Guard =>] static_integer_EXPRESSION);
10308
10309          when Pragma_Task_Storage => Task_Storage : declare
10310             Args  : Args_List (1 .. 2);
10311             Names : constant Name_List (1 .. 2) := (
10312                       Name_Task_Type,
10313                       Name_Top_Guard);
10314
10315             Task_Type : Node_Id renames Args (1);
10316             Top_Guard : Node_Id renames Args (2);
10317
10318             Ent : Entity_Id;
10319
10320          begin
10321             GNAT_Pragma;
10322             Gather_Associations (Names, Args);
10323
10324             if No (Task_Type) then
10325                Error_Pragma
10326                  ("missing task_type argument for pragma%");
10327             end if;
10328
10329             Check_Arg_Is_Local_Name (Task_Type);
10330
10331             Ent := Entity (Task_Type);
10332
10333             if not Is_Task_Type (Ent) then
10334                Error_Pragma_Arg
10335                  ("argument for pragma% must be task type", Task_Type);
10336             end if;
10337
10338             if No (Top_Guard) then
10339                Error_Pragma_Arg
10340                  ("pragma% takes two arguments", Task_Type);
10341             else
10342                Check_Arg_Is_Static_Expression (Top_Guard, Any_Integer);
10343             end if;
10344
10345             Check_First_Subtype (Task_Type);
10346
10347             if Rep_Item_Too_Late (Ent, N) then
10348                raise Pragma_Exit;
10349             end if;
10350          end Task_Storage;
10351
10352          ----------------
10353          -- Time_Slice --
10354          ----------------
10355
10356          --  pragma Time_Slice (static_duration_EXPRESSION);
10357
10358          when Pragma_Time_Slice => Time_Slice : declare
10359             Val : Ureal;
10360             Nod : Node_Id;
10361
10362          begin
10363             GNAT_Pragma;
10364             Check_Arg_Count (1);
10365             Check_No_Identifiers;
10366             Check_In_Main_Program;
10367             Check_Arg_Is_Static_Expression (Arg1, Standard_Duration);
10368
10369             if not Error_Posted (Arg1) then
10370                Nod := Next (N);
10371                while Present (Nod) loop
10372                   if Nkind (Nod) = N_Pragma
10373                     and then Chars (Nod) = Name_Time_Slice
10374                   then
10375                      Error_Msg_Name_1 := Chars (N);
10376                      Error_Msg_N ("duplicate pragma% not permitted", Nod);
10377                   end if;
10378
10379                   Next (Nod);
10380                end loop;
10381             end if;
10382
10383             --  Process only if in main unit
10384
10385             if Get_Source_Unit (Loc) = Main_Unit then
10386                Opt.Time_Slice_Set := True;
10387                Val := Expr_Value_R (Expression (Arg1));
10388
10389                if Val <= Ureal_0 then
10390                   Opt.Time_Slice_Value := 0;
10391
10392                elsif Val > UR_From_Uint (UI_From_Int (1000)) then
10393                   Opt.Time_Slice_Value := 1_000_000_000;
10394
10395                else
10396                   Opt.Time_Slice_Value :=
10397                     UI_To_Int (UR_To_Uint (Val * UI_From_Int (1_000_000)));
10398                end if;
10399             end if;
10400          end Time_Slice;
10401
10402          -----------
10403          -- Title --
10404          -----------
10405
10406          --  pragma Title (TITLING_OPTION [, TITLING OPTION]);
10407
10408          --   TITLING_OPTION ::=
10409          --     [Title =>] STRING_LITERAL
10410          --   | [Subtitle =>] STRING_LITERAL
10411
10412          when Pragma_Title => Title : declare
10413             Args  : Args_List (1 .. 2);
10414             Names : constant Name_List (1 .. 2) := (
10415                       Name_Title,
10416                       Name_Subtitle);
10417
10418          begin
10419             GNAT_Pragma;
10420             Gather_Associations (Names, Args);
10421
10422             for J in 1 .. 2 loop
10423                if Present (Args (J)) then
10424                   Check_Arg_Is_String_Literal (Args (J));
10425                end if;
10426             end loop;
10427          end Title;
10428
10429          ---------------------
10430          -- Unchecked_Union --
10431          ---------------------
10432
10433          --  pragma Unchecked_Union (first_subtype_LOCAL_NAME)
10434
10435          when Pragma_Unchecked_Union => Unchecked_Union : declare
10436             Assoc   : constant Node_Id := Arg1;
10437             Type_Id : constant Node_Id := Expression (Assoc);
10438             Typ     : Entity_Id;
10439             Discr   : Entity_Id;
10440             Tdef    : Node_Id;
10441             Clist   : Node_Id;
10442             Vpart   : Node_Id;
10443             Comp    : Node_Id;
10444             Variant : Node_Id;
10445
10446          begin
10447             GNAT_Pragma;
10448             Check_No_Identifiers;
10449             Check_Arg_Count (1);
10450             Check_Arg_Is_Local_Name (Arg1);
10451
10452             Find_Type (Type_Id);
10453             Typ := Entity (Type_Id);
10454
10455             if Typ = Any_Type
10456               or else Rep_Item_Too_Early (Typ, N)
10457             then
10458                return;
10459             else
10460                Typ := Underlying_Type (Typ);
10461             end if;
10462
10463             if Rep_Item_Too_Late (Typ, N) then
10464                return;
10465             end if;
10466
10467             Check_First_Subtype (Arg1);
10468
10469             --  Note remaining cases are references to a type in the current
10470             --  declarative part. If we find an error, we post the error on
10471             --  the relevant type declaration at an appropriate point.
10472
10473             if not Is_Record_Type (Typ) then
10474                Error_Msg_N ("Unchecked_Union must be record type", Typ);
10475                return;
10476
10477             elsif Is_Tagged_Type (Typ) then
10478                Error_Msg_N ("Unchecked_Union must not be tagged", Typ);
10479                return;
10480
10481             elsif Is_Limited_Type (Typ) then
10482                Error_Msg_N
10483                  ("Unchecked_Union must not be limited record type", Typ);
10484                Explain_Limited_Type (Typ, Typ);
10485                return;
10486
10487             else
10488                if not Has_Discriminants (Typ) then
10489                   Error_Msg_N
10490                     ("Unchecked_Union must have one discriminant", Typ);
10491                   return;
10492                end if;
10493
10494                Discr := First_Discriminant (Typ);
10495                while Present (Discr) loop
10496                   if No (Discriminant_Default_Value (Discr)) then
10497                      Error_Msg_N
10498                        ("Unchecked_Union discriminant must have default value",
10499                         Discr);
10500                   end if;
10501                   Next_Discriminant (Discr);
10502                end loop;
10503
10504                Tdef  := Type_Definition (Declaration_Node (Typ));
10505                Clist := Component_List (Tdef);
10506
10507                Comp := First (Component_Items (Clist));
10508                while Present (Comp) loop
10509                   Check_Component (Comp);
10510                   Next (Comp);
10511                end loop;
10512
10513                if No (Clist) or else No (Variant_Part (Clist)) then
10514                   Error_Msg_N
10515                     ("Unchecked_Union must have variant part",
10516                      Tdef);
10517                   return;
10518                end if;
10519
10520                Vpart := Variant_Part (Clist);
10521
10522                Variant := First (Variants (Vpart));
10523                while Present (Variant) loop
10524                   Check_Variant (Variant);
10525                   Next (Variant);
10526                end loop;
10527             end if;
10528
10529             Set_Is_Unchecked_Union  (Typ, True);
10530             Set_Convention          (Typ, Convention_C);
10531
10532             Set_Has_Unchecked_Union (Base_Type (Typ), True);
10533             Set_Is_Unchecked_Union  (Base_Type (Typ), True);
10534          end Unchecked_Union;
10535
10536          ------------------------
10537          -- Unimplemented_Unit --
10538          ------------------------
10539
10540          --  pragma Unimplemented_Unit;
10541
10542          --  Note: this only gives an error if we are generating code,
10543          --  or if we are in a generic library unit (where the pragma
10544          --  appears in the body, not in the spec).
10545
10546          when Pragma_Unimplemented_Unit => Unimplemented_Unit : declare
10547             Cunitent : constant Entity_Id :=
10548                          Cunit_Entity (Get_Source_Unit (Loc));
10549             Ent_Kind : constant Entity_Kind :=
10550                          Ekind (Cunitent);
10551
10552          begin
10553             GNAT_Pragma;
10554             Check_Arg_Count (0);
10555
10556             if Operating_Mode = Generate_Code
10557               or else Ent_Kind = E_Generic_Function
10558               or else Ent_Kind = E_Generic_Procedure
10559               or else Ent_Kind = E_Generic_Package
10560             then
10561                Get_Name_String (Chars (Cunitent));
10562                Set_Casing (Mixed_Case);
10563                Write_Str (Name_Buffer (1 .. Name_Len));
10564                Write_Str (" is not supported in this configuration");
10565                Write_Eol;
10566                raise Unrecoverable_Error;
10567             end if;
10568          end Unimplemented_Unit;
10569
10570          ------------------------
10571          -- Universal_Aliasing --
10572          ------------------------
10573
10574          --  pragma Universal_Aliasing [([Entity =>] type_LOCAL_NAME)];
10575
10576          when Pragma_Universal_Aliasing => Universal_Alias : declare
10577             E_Id : Entity_Id;
10578
10579          begin
10580             GNAT_Pragma;
10581             Check_Arg_Count (1);
10582             Check_Optional_Identifier (Arg2, Name_Entity);
10583             Check_Arg_Is_Local_Name (Arg1);
10584             E_Id := Entity (Expression (Arg1));
10585
10586             if E_Id = Any_Type then
10587                return;
10588             elsif No (E_Id) or else not Is_Type (E_Id) then
10589                Error_Pragma_Arg ("pragma% requires type", Arg1);
10590             end if;
10591
10592             Set_Universal_Aliasing (Implementation_Base_Type (E_Id));
10593          end Universal_Alias;
10594
10595          --------------------
10596          -- Universal_Data --
10597          --------------------
10598
10599          --  pragma Universal_Data [(library_unit_NAME)];
10600
10601          when Pragma_Universal_Data =>
10602             GNAT_Pragma;
10603
10604             --  If this is a configuration pragma, then set the universal
10605             --  addressing option, otherwise confirm that the pragma
10606             --  satisfies the requirements of library unit pragma placement
10607             --  and leave it to the GNAAMP back end to detect the pragma
10608             --  (avoids transitive setting of the option due to withed units).
10609
10610             if Is_Configuration_Pragma then
10611                Universal_Addressing_On_AAMP := True;
10612             else
10613                Check_Valid_Library_Unit_Pragma;
10614             end if;
10615
10616             if not AAMP_On_Target then
10617                Error_Pragma ("?pragma% ignored (applies only to AAMP)");
10618             end if;
10619
10620          ------------------
10621          -- Unreferenced --
10622          ------------------
10623
10624          --  pragma Unreferenced (local_Name {, local_Name});
10625
10626          --    or when used in a context clause:
10627
10628          --  pragma Unreferenced (library_unit_NAME {, library_unit_NAME}
10629
10630          when Pragma_Unreferenced => Unreferenced : declare
10631             Arg_Node : Node_Id;
10632             Arg_Expr : Node_Id;
10633             Arg_Ent  : Entity_Id;
10634             Citem    : Node_Id;
10635
10636          begin
10637             GNAT_Pragma;
10638             Check_At_Least_N_Arguments (1);
10639
10640             --  Check case of appearing within context clause
10641
10642             if Is_In_Context_Clause then
10643
10644                --  The arguments must all be units mentioned in a with clause
10645                --  in the same context clause. Note we already checked (in
10646                --  Par.Prag) that the arguments are either identifiers or
10647                --  selected components.
10648
10649                Arg_Node := Arg1;
10650                while Present (Arg_Node) loop
10651                   Citem := First (List_Containing (N));
10652                   while Citem /= N loop
10653                      if Nkind (Citem) = N_With_Clause
10654                        and then Same_Name (Name (Citem), Expression (Arg_Node))
10655                      then
10656                         Set_Has_Pragma_Unreferenced
10657                           (Cunit_Entity
10658                              (Get_Source_Unit
10659                                 (Library_Unit (Citem))));
10660                         Set_Unit_Name (Expression (Arg_Node), Name (Citem));
10661                         exit;
10662                      end if;
10663
10664                      Next (Citem);
10665                   end loop;
10666
10667                   if Citem = N then
10668                      Error_Pragma_Arg
10669                        ("argument of pragma% is not with'ed unit", Arg_Node);
10670                   end if;
10671
10672                   Next (Arg_Node);
10673                end loop;
10674
10675             --  Case of not in list of context items
10676
10677             else
10678                Arg_Node := Arg1;
10679                while Present (Arg_Node) loop
10680                   Check_No_Identifier (Arg_Node);
10681
10682                   --  Note: the analyze call done by Check_Arg_Is_Local_Name
10683                   --  will in fact generate reference, so that the entity will
10684                   --  have a reference, which will inhibit any warnings about
10685                   --  it not being referenced, and also properly show up in the
10686                   --  ali file as a reference. But this reference is recorded
10687                   --  before the Has_Pragma_Unreferenced flag is set, so that
10688                   --  no warning is generated for this reference.
10689
10690                   Check_Arg_Is_Local_Name (Arg_Node);
10691                   Arg_Expr := Get_Pragma_Arg (Arg_Node);
10692
10693                   if Is_Entity_Name (Arg_Expr) then
10694                      Arg_Ent := Entity (Arg_Expr);
10695
10696                      --  If the entity is overloaded, the pragma applies to the
10697                      --  most recent overloading, as documented. In this case,
10698                      --  name resolution does not generate a reference, so it
10699                      --  must be done here explicitly.
10700
10701                      if Is_Overloaded (Arg_Expr) then
10702                         Generate_Reference (Arg_Ent, N);
10703                      end if;
10704
10705                      Set_Has_Pragma_Unreferenced (Arg_Ent);
10706                   end if;
10707
10708                   Next (Arg_Node);
10709                end loop;
10710             end if;
10711          end Unreferenced;
10712
10713          --------------------------
10714          -- Unreferenced_Objects --
10715          --------------------------
10716
10717          --  pragma Unreferenced_Objects (local_Name {, local_Name});
10718
10719          when Pragma_Unreferenced_Objects => Unreferenced_Objects : declare
10720             Arg_Node : Node_Id;
10721             Arg_Expr : Node_Id;
10722
10723          begin
10724             GNAT_Pragma;
10725             Check_At_Least_N_Arguments (1);
10726
10727             Arg_Node := Arg1;
10728             while Present (Arg_Node) loop
10729                Check_No_Identifier (Arg_Node);
10730                Check_Arg_Is_Local_Name (Arg_Node);
10731                Arg_Expr := Get_Pragma_Arg (Arg_Node);
10732
10733                if not Is_Entity_Name (Arg_Expr)
10734                  or else not Is_Type (Entity (Arg_Expr))
10735                then
10736                   Error_Pragma_Arg
10737                     ("argument for pragma% must be type or subtype", Arg_Node);
10738                end if;
10739
10740                Set_Has_Pragma_Unreferenced_Objects (Entity (Arg_Expr));
10741                Next (Arg_Node);
10742             end loop;
10743          end Unreferenced_Objects;
10744
10745          ------------------------------
10746          -- Unreserve_All_Interrupts --
10747          ------------------------------
10748
10749          --  pragma Unreserve_All_Interrupts;
10750
10751          when Pragma_Unreserve_All_Interrupts =>
10752             GNAT_Pragma;
10753             Check_Arg_Count (0);
10754
10755             if In_Extended_Main_Code_Unit (Main_Unit_Entity) then
10756                Unreserve_All_Interrupts := True;
10757             end if;
10758
10759          ----------------
10760          -- Unsuppress --
10761          ----------------
10762
10763          --  pragma Unsuppress (IDENTIFIER [, [On =>] NAME]);
10764
10765          when Pragma_Unsuppress =>
10766             GNAT_Pragma;
10767             Process_Suppress_Unsuppress (False);
10768
10769          -------------------
10770          -- Use_VADS_Size --
10771          -------------------
10772
10773          --  pragma Use_VADS_Size;
10774
10775          when Pragma_Use_VADS_Size =>
10776             GNAT_Pragma;
10777             Check_Arg_Count (0);
10778             Check_Valid_Configuration_Pragma;
10779             Use_VADS_Size := True;
10780
10781          ---------------------
10782          -- Validity_Checks --
10783          ---------------------
10784
10785          --  pragma Validity_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
10786
10787          when Pragma_Validity_Checks => Validity_Checks : declare
10788             A  : constant Node_Id   := Expression (Arg1);
10789             S  : String_Id;
10790             C  : Char_Code;
10791
10792          begin
10793             GNAT_Pragma;
10794             Check_Arg_Count (1);
10795             Check_No_Identifiers;
10796
10797             if Nkind (A) = N_String_Literal then
10798                S   := Strval (A);
10799
10800                declare
10801                   Slen    : constant Natural := Natural (String_Length (S));
10802                   Options : String (1 .. Slen);
10803                   J       : Natural;
10804
10805                begin
10806                   J := 1;
10807                   loop
10808                      C := Get_String_Char (S, Int (J));
10809                      exit when not In_Character_Range (C);
10810                      Options (J) := Get_Character (C);
10811
10812                      if J = Slen then
10813                         Set_Validity_Check_Options (Options);
10814                         exit;
10815                      else
10816                         J := J + 1;
10817                      end if;
10818                   end loop;
10819                end;
10820
10821             elsif Nkind (A) = N_Identifier then
10822
10823                if Chars (A) = Name_All_Checks then
10824                   Set_Validity_Check_Options ("a");
10825
10826                elsif Chars (A) = Name_On then
10827                   Validity_Checks_On := True;
10828
10829                elsif Chars (A) = Name_Off then
10830                   Validity_Checks_On := False;
10831
10832                end if;
10833             end if;
10834          end Validity_Checks;
10835
10836          --------------
10837          -- Volatile --
10838          --------------
10839
10840          --  pragma Volatile (LOCAL_NAME);
10841
10842          when Pragma_Volatile =>
10843             Process_Atomic_Shared_Volatile;
10844
10845          -------------------------
10846          -- Volatile_Components --
10847          -------------------------
10848
10849          --  pragma Volatile_Components (array_LOCAL_NAME);
10850
10851          --  Volatile is handled by the same circuit as Atomic_Components
10852
10853          --------------
10854          -- Warnings --
10855          --------------
10856
10857          --  pragma Warnings (On | Off);
10858          --  pragma Warnings (On | Off, LOCAL_NAME);
10859          --  pragma Warnings (static_string_EXPRESSION);
10860          --  pragma Warnings (On | Off, STRING_LITERAL);
10861
10862          when Pragma_Warnings => Warnings : begin
10863             GNAT_Pragma;
10864             Check_At_Least_N_Arguments (1);
10865             Check_No_Identifiers;
10866
10867             declare
10868                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
10869
10870             begin
10871                --  One argument case
10872
10873                if Arg_Count = 1 then
10874
10875                   --  On/Off one argument case was processed by parser
10876
10877                   if Nkind (Argx) = N_Identifier
10878                     and then
10879                       (Chars (Argx) = Name_On
10880                          or else
10881                        Chars (Argx) = Name_Off)
10882                   then
10883                      null;
10884
10885                   --  One argument case must be ON/OFF or static string expr
10886
10887                   elsif not Is_Static_String_Expression (Arg1) then
10888                      Error_Pragma_Arg
10889                        ("argument of pragma% must be On/Off or " &
10890                         "static string expression", Arg2);
10891
10892                   --  One argument string expression case
10893
10894                   else
10895                      declare
10896                         Lit : constant Node_Id   := Expr_Value_S (Argx);
10897                         Str : constant String_Id := Strval (Lit);
10898                         Len : constant Nat       := String_Length (Str);
10899                         C   : Char_Code;
10900                         J   : Nat;
10901                         OK  : Boolean;
10902                         Chr : Character;
10903
10904                      begin
10905                         J := 1;
10906                         while J <= Len loop
10907                            C := Get_String_Char (Str, J);
10908                            OK := In_Character_Range (C);
10909
10910                            if OK then
10911                               Chr := Get_Character (C);
10912
10913                               --  Dot case
10914
10915                               if J < Len and then Chr = '.' then
10916                                  J := J + 1;
10917                                  C := Get_String_Char (Str, J);
10918                                  Chr := Get_Character (C);
10919
10920                                  if not Set_Dot_Warning_Switch (Chr) then
10921                                     Error_Pragma_Arg
10922                                       ("invalid warning switch character " &
10923                                        '.' & Chr, Arg1);
10924                                  end if;
10925
10926                               --  Non-Dot case
10927
10928                               else
10929                                  OK := Set_Warning_Switch (Chr);
10930                               end if;
10931                            end if;
10932
10933                            if not OK then
10934                               Error_Pragma_Arg
10935                                 ("invalid warning switch character " & Chr,
10936                                  Arg1);
10937                            end if;
10938
10939                            J := J + 1;
10940                         end loop;
10941                      end;
10942                   end if;
10943
10944                   --  Two or more arguments (must be two)
10945
10946                else
10947                   Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
10948                   Check_At_Most_N_Arguments (2);
10949
10950                   declare
10951                      E_Id : Node_Id;
10952                      E    : Entity_Id;
10953                      Err  : Boolean;
10954
10955                   begin
10956                      E_Id := Expression (Arg2);
10957                      Analyze (E_Id);
10958
10959                      --  In the expansion of an inlined body, a reference to
10960                      --  the formal may be wrapped in a conversion if the
10961                      --  actual is a conversion. Retrieve the real entity name.
10962
10963                      if (In_Instance_Body
10964                          or else In_Inlined_Body)
10965                        and then Nkind (E_Id) = N_Unchecked_Type_Conversion
10966                      then
10967                         E_Id := Expression (E_Id);
10968                      end if;
10969
10970                      --  Entity name case
10971
10972                      if Is_Entity_Name (E_Id) then
10973                         E := Entity (E_Id);
10974
10975                         if E = Any_Id then
10976                            return;
10977                         else
10978                            loop
10979                               Set_Warnings_Off
10980                                 (E, (Chars (Expression (Arg1)) = Name_Off));
10981
10982                               if Is_Enumeration_Type (E) then
10983                                  declare
10984                                     Lit : Entity_Id;
10985                                  begin
10986                                     Lit := First_Literal (E);
10987                                     while Present (Lit) loop
10988                                        Set_Warnings_Off (Lit);
10989                                        Next_Literal (Lit);
10990                                     end loop;
10991                                  end;
10992                               end if;
10993
10994                               exit when No (Homonym (E));
10995                               E := Homonym (E);
10996                            end loop;
10997                         end if;
10998
10999                      --  Error if not entity or static string literal case
11000
11001                      elsif not Is_Static_String_Expression (Arg2) then
11002                         Error_Pragma_Arg
11003                           ("second argument of pragma% must be entity " &
11004                            "name or static string expression", Arg2);
11005
11006                      --  String literal case
11007
11008                      else
11009                         String_To_Name_Buffer
11010                           (Strval (Expr_Value_S (Expression (Arg2))));
11011
11012                         --  Note on configuration pragma case: If this is a
11013                         --  configuration pragma, then for an OFF pragma, we
11014                         --  just set Config True in the call, which is all
11015                         --  that needs to be done. For the case of ON, this
11016                         --  is normally an error, unless it is canceling the
11017                         --  effect of a previous OFF pragma in the same file.
11018                         --  In any other case, an error will be signalled (ON
11019                         --  with no matching OFF).
11020
11021                         if Chars (Argx) = Name_Off then
11022                            Set_Specific_Warning_Off
11023                              (Loc, Name_Buffer (1 .. Name_Len),
11024                               Config => Is_Configuration_Pragma);
11025
11026                         elsif Chars (Argx) = Name_On then
11027                            Set_Specific_Warning_On
11028                              (Loc, Name_Buffer (1 .. Name_Len), Err);
11029
11030                            if Err then
11031                               Error_Msg
11032                                 ("?pragma Warnings On with no " &
11033                                  "matching Warnings Off",
11034                                  Loc);
11035                            end if;
11036                         end if;
11037                      end if;
11038                   end;
11039                end if;
11040             end;
11041          end Warnings;
11042
11043          -------------------
11044          -- Weak_External --
11045          -------------------
11046
11047          --  pragma Weak_External ([Entity =>] LOCAL_NAME);
11048
11049          when Pragma_Weak_External => Weak_External : declare
11050             Ent : Entity_Id;
11051
11052          begin
11053             GNAT_Pragma;
11054             Check_Arg_Count (1);
11055             Check_Optional_Identifier (Arg1, Name_Entity);
11056             Check_Arg_Is_Library_Level_Local_Name (Arg1);
11057             Ent := Entity (Expression (Arg1));
11058
11059             if Rep_Item_Too_Early (Ent, N) then
11060                return;
11061             else
11062                Ent := Underlying_Type (Ent);
11063             end if;
11064
11065             --  The only processing required is to link this item on to the
11066             --  list of rep items for the given entity. This is accomplished
11067             --  by the call to Rep_Item_Too_Late (when no error is detected
11068             --  and False is returned).
11069
11070             if Rep_Item_Too_Late (Ent, N) then
11071                return;
11072             else
11073                Set_Has_Gigi_Rep_Item (Ent);
11074             end if;
11075          end Weak_External;
11076
11077          -----------------------------
11078          -- Wide_Character_Encoding --
11079          -----------------------------
11080
11081          --  pragma Wide_Character_Encoding (IDENTIFIER);
11082
11083          when Pragma_Wide_Character_Encoding =>
11084
11085             --  Nothing to do, handled in parser. Note that we do not enforce
11086             --  configuration pragma placement, this pragma can appear at any
11087             --  place in the source, allowing mixed encodings within a single
11088             --  source program.
11089
11090             null;
11091
11092          --------------------
11093          -- Unknown_Pragma --
11094          --------------------
11095
11096          --  Should be impossible, since the case of an unknown pragma is
11097          --  separately processed before the case statement is entered.
11098
11099          when Unknown_Pragma =>
11100             raise Program_Error;
11101       end case;
11102
11103    exception
11104       when Pragma_Exit => null;
11105    end Analyze_Pragma;
11106
11107    ---------------------------------
11108    -- Delay_Config_Pragma_Analyze --
11109    ---------------------------------
11110
11111    function Delay_Config_Pragma_Analyze (N : Node_Id) return Boolean is
11112    begin
11113       return Chars (N) = Name_Interrupt_State
11114                or else
11115              Chars (N) = Name_Priority_Specific_Dispatching;
11116    end Delay_Config_Pragma_Analyze;
11117
11118    -------------------------
11119    -- Get_Base_Subprogram --
11120    -------------------------
11121
11122    function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id is
11123       Result : Entity_Id;
11124
11125    begin
11126       --  Follow subprogram renaming chain
11127
11128       Result := Def_Id;
11129       while Is_Subprogram (Result)
11130         and then
11131           (Is_Generic_Instance (Result)
11132             or else Nkind (Parent (Declaration_Node (Result))) =
11133                     N_Subprogram_Renaming_Declaration)
11134         and then Present (Alias (Result))
11135       loop
11136          Result := Alias (Result);
11137       end loop;
11138
11139       return Result;
11140    end Get_Base_Subprogram;
11141
11142    -----------------------------
11143    -- Is_Config_Static_String --
11144    -----------------------------
11145
11146    function Is_Config_Static_String (Arg : Node_Id) return Boolean is
11147
11148       function Add_Config_Static_String (Arg : Node_Id) return Boolean;
11149       --  This is an internal recursive function that is just like the
11150       --  outer function except that it adds the string to the name buffer
11151       --  rather than placing the string in the name buffer.
11152
11153       ------------------------------
11154       -- Add_Config_Static_String --
11155       ------------------------------
11156
11157       function Add_Config_Static_String (Arg : Node_Id) return Boolean is
11158          N : Node_Id;
11159          C : Char_Code;
11160
11161       begin
11162          N := Arg;
11163
11164          if Nkind (N) = N_Op_Concat then
11165             if Add_Config_Static_String (Left_Opnd (N)) then
11166                N := Right_Opnd (N);
11167             else
11168                return False;
11169             end if;
11170          end if;
11171
11172          if Nkind (N) /= N_String_Literal then
11173             Error_Msg_N ("string literal expected for pragma argument", N);
11174             return False;
11175
11176          else
11177             for J in 1 .. String_Length (Strval (N)) loop
11178                C := Get_String_Char (Strval (N), J);
11179
11180                if not In_Character_Range (C) then
11181                   Error_Msg
11182                     ("string literal contains invalid wide character",
11183                      Sloc (N) + 1 + Source_Ptr (J));
11184                   return False;
11185                end if;
11186
11187                Add_Char_To_Name_Buffer (Get_Character (C));
11188             end loop;
11189          end if;
11190
11191          return True;
11192       end Add_Config_Static_String;
11193
11194    --  Start of prorcessing for Is_Config_Static_String
11195
11196    begin
11197
11198       Name_Len := 0;
11199       return Add_Config_Static_String (Arg);
11200    end Is_Config_Static_String;
11201
11202    -----------------------------------------
11203    -- Is_Non_Significant_Pragma_Reference --
11204    -----------------------------------------
11205
11206    --  This function makes use of the following static table which indicates
11207    --  whether a given pragma is significant. A value of -1 in this table
11208    --  indicates that the reference is significant. A value of zero indicates
11209    --  than appearence as any argument is insignificant, a positive value
11210    --  indicates that appearence in that parameter position is significant.
11211
11212    Sig_Flags : constant array (Pragma_Id) of Int :=
11213
11214      (Pragma_AST_Entry                     => -1,
11215       Pragma_Abort_Defer                   => -1,
11216       Pragma_Ada_83                        => -1,
11217       Pragma_Ada_95                        => -1,
11218       Pragma_Ada_05                        => -1,
11219       Pragma_Ada_2005                      => -1,
11220       Pragma_All_Calls_Remote              => -1,
11221       Pragma_Annotate                      => -1,
11222       Pragma_Assert                        => -1,
11223       Pragma_Assertion_Policy              =>  0,
11224       Pragma_Asynchronous                  => -1,
11225       Pragma_Atomic                        =>  0,
11226       Pragma_Atomic_Components             =>  0,
11227       Pragma_Attach_Handler                => -1,
11228       Pragma_Check_Name                    =>  0,
11229       Pragma_CIL_Constructor               => -1,
11230       Pragma_CPP_Class                     =>  0,
11231       Pragma_CPP_Constructor               =>  0,
11232       Pragma_CPP_Virtual                   =>  0,
11233       Pragma_CPP_Vtable                    =>  0,
11234       Pragma_C_Pass_By_Copy                =>  0,
11235       Pragma_Comment                       =>  0,
11236       Pragma_Common_Object                 => -1,
11237       Pragma_Compile_Time_Error            => -1,
11238       Pragma_Compile_Time_Warning          => -1,
11239       Pragma_Complete_Representation       =>  0,
11240       Pragma_Complex_Representation        =>  0,
11241       Pragma_Component_Alignment           => -1,
11242       Pragma_Controlled                    =>  0,
11243       Pragma_Convention                    =>  0,
11244       Pragma_Convention_Identifier         =>  0,
11245       Pragma_Debug                         => -1,
11246       Pragma_Debug_Policy                  =>  0,
11247       Pragma_Detect_Blocking               => -1,
11248       Pragma_Discard_Names                 =>  0,
11249       Pragma_Elaborate                     => -1,
11250       Pragma_Elaborate_All                 => -1,
11251       Pragma_Elaborate_Body                => -1,
11252       Pragma_Elaboration_Checks            => -1,
11253       Pragma_Eliminate                     => -1,
11254       Pragma_Export                        => -1,
11255       Pragma_Export_Exception              => -1,
11256       Pragma_Export_Function               => -1,
11257       Pragma_Export_Object                 => -1,
11258       Pragma_Export_Procedure              => -1,
11259       Pragma_Export_Value                  => -1,
11260       Pragma_Export_Valued_Procedure       => -1,
11261       Pragma_Extend_System                 => -1,
11262       Pragma_Extensions_Allowed            => -1,
11263       Pragma_External                      => -1,
11264       Pragma_External_Name_Casing          => -1,
11265       Pragma_Finalize_Storage_Only         =>  0,
11266       Pragma_Float_Representation          =>  0,
11267       Pragma_Ident                         => -1,
11268       Pragma_Implicit_Packing              =>  0,
11269       Pragma_Import                        => +2,
11270       Pragma_Import_Exception              =>  0,
11271       Pragma_Import_Function               =>  0,
11272       Pragma_Import_Object                 =>  0,
11273       Pragma_Import_Procedure              =>  0,
11274       Pragma_Import_Valued_Procedure       =>  0,
11275       Pragma_Initialize_Scalars            => -1,
11276       Pragma_Inline                        =>  0,
11277       Pragma_Inline_Always                 =>  0,
11278       Pragma_Inline_Generic                =>  0,
11279       Pragma_Inspection_Point              => -1,
11280       Pragma_Interface                     => +2,
11281       Pragma_Interface_Name                => +2,
11282       Pragma_Interrupt_Handler             => -1,
11283       Pragma_Interrupt_Priority            => -1,
11284       Pragma_Interrupt_State               => -1,
11285       Pragma_Java_Constructor              => -1,
11286       Pragma_Java_Interface                => -1,
11287       Pragma_Keep_Names                    =>  0,
11288       Pragma_License                       => -1,
11289       Pragma_Link_With                     => -1,
11290       Pragma_Linker_Alias                  => -1,
11291       Pragma_Linker_Constructor            => -1,
11292       Pragma_Linker_Destructor             => -1,
11293       Pragma_Linker_Options                => -1,
11294       Pragma_Linker_Section                => -1,
11295       Pragma_List                          => -1,
11296       Pragma_Locking_Policy                => -1,
11297       Pragma_Long_Float                    => -1,
11298       Pragma_Machine_Attribute             => -1,
11299       Pragma_Main                          => -1,
11300       Pragma_Main_Storage                  => -1,
11301       Pragma_Memory_Size                   => -1,
11302       Pragma_No_Return                     =>  0,
11303       Pragma_No_Body                       =>  0,
11304       Pragma_No_Run_Time                   => -1,
11305       Pragma_No_Strict_Aliasing            => -1,
11306       Pragma_Normalize_Scalars             => -1,
11307       Pragma_Obsolescent                   =>  0,
11308       Pragma_Optimize                      => -1,
11309       Pragma_Pack                          =>  0,
11310       Pragma_Page                          => -1,
11311       Pragma_Passive                       => -1,
11312       Pragma_Preelaborable_Initialization  => -1,
11313       Pragma_Polling                       => -1,
11314       Pragma_Persistent_BSS                =>  0,
11315       Pragma_Preelaborate                  => -1,
11316       Pragma_Preelaborate_05               => -1,
11317       Pragma_Priority                      => -1,
11318       Pragma_Priority_Specific_Dispatching => -1,
11319       Pragma_Profile                       =>  0,
11320       Pragma_Profile_Warnings              =>  0,
11321       Pragma_Propagate_Exceptions          => -1,
11322       Pragma_Psect_Object                  => -1,
11323       Pragma_Pure                          => -1,
11324       Pragma_Pure_05                       => -1,
11325       Pragma_Pure_Function                 => -1,
11326       Pragma_Queuing_Policy                => -1,
11327       Pragma_Ravenscar                     => -1,
11328       Pragma_Remote_Call_Interface         => -1,
11329       Pragma_Remote_Types                  => -1,
11330       Pragma_Restricted_Run_Time           => -1,
11331       Pragma_Restriction_Warnings          => -1,
11332       Pragma_Restrictions                  => -1,
11333       Pragma_Reviewable                    => -1,
11334       Pragma_Share_Generic                 => -1,
11335       Pragma_Shared                        => -1,
11336       Pragma_Shared_Passive                => -1,
11337       Pragma_Source_File_Name              => -1,
11338       Pragma_Source_File_Name_Project      => -1,
11339       Pragma_Source_Reference              => -1,
11340       Pragma_Storage_Size                  => -1,
11341       Pragma_Storage_Unit                  => -1,
11342       Pragma_Static_Elaboration_Desired    => -1,
11343       Pragma_Stream_Convert                => -1,
11344       Pragma_Style_Checks                  => -1,
11345       Pragma_Subtitle                      => -1,
11346       Pragma_Suppress                      =>  0,
11347       Pragma_Suppress_Exception_Locations  =>  0,
11348       Pragma_Suppress_All                  => -1,
11349       Pragma_Suppress_Debug_Info           =>  0,
11350       Pragma_Suppress_Initialization       =>  0,
11351       Pragma_System_Name                   => -1,
11352       Pragma_Task_Dispatching_Policy       => -1,
11353       Pragma_Task_Info                     => -1,
11354       Pragma_Task_Name                     => -1,
11355       Pragma_Task_Storage                  =>  0,
11356       Pragma_Time_Slice                    => -1,
11357       Pragma_Title                         => -1,
11358       Pragma_Unchecked_Union               =>  0,
11359       Pragma_Unimplemented_Unit            => -1,
11360       Pragma_Universal_Aliasing            => -1,
11361       Pragma_Universal_Data                => -1,
11362       Pragma_Unreferenced                  => -1,
11363       Pragma_Unreferenced_Objects          => -1,
11364       Pragma_Unreserve_All_Interrupts      => -1,
11365       Pragma_Unsuppress                    =>  0,
11366       Pragma_Use_VADS_Size                 => -1,
11367       Pragma_Validity_Checks               => -1,
11368       Pragma_Volatile                      =>  0,
11369       Pragma_Volatile_Components           =>  0,
11370       Pragma_Warnings                      => -1,
11371       Pragma_Weak_External                 => -1,
11372       Pragma_Wide_Character_Encoding       =>  0,
11373       Unknown_Pragma                       =>  0);
11374
11375    function Is_Non_Significant_Pragma_Reference (N : Node_Id) return Boolean is
11376       P : Node_Id;
11377       C : Int;
11378       A : Node_Id;
11379
11380    begin
11381       P := Parent (N);
11382
11383       if Nkind (P) /= N_Pragma_Argument_Association then
11384          return False;
11385
11386       else
11387          C := Sig_Flags (Get_Pragma_Id (Chars (Parent (P))));
11388
11389          case C is
11390             when -1 =>
11391                return False;
11392
11393             when 0 =>
11394                return True;
11395
11396             when others =>
11397                A := First (Pragma_Argument_Associations (Parent (P)));
11398                for J in 1 .. C - 1 loop
11399                   if No (A) then
11400                      return False;
11401                   end if;
11402
11403                   Next (A);
11404                end loop;
11405
11406                return A = P;
11407          end case;
11408       end if;
11409    end Is_Non_Significant_Pragma_Reference;
11410
11411    ------------------------------
11412    -- Is_Pragma_String_Literal --
11413    ------------------------------
11414
11415    --  This function returns true if the corresponding pragma argument is
11416    --  a static string expression. These are the only cases in which string
11417    --  literals can appear as pragma arguments. We also allow a string
11418    --  literal as the first argument to pragma Assert (although it will
11419    --  of course always generate a type error).
11420
11421    function Is_Pragma_String_Literal (Par : Node_Id) return Boolean is
11422       Pragn : constant Node_Id := Parent (Par);
11423       Assoc : constant List_Id := Pragma_Argument_Associations (Pragn);
11424       Pname : constant Name_Id := Chars (Pragn);
11425       Argn  : Natural;
11426       N     : Node_Id;
11427
11428    begin
11429       Argn := 1;
11430       N := First (Assoc);
11431       loop
11432          exit when N = Par;
11433          Argn := Argn + 1;
11434          Next (N);
11435       end loop;
11436
11437       if Pname = Name_Assert then
11438          return True;
11439
11440       elsif Pname = Name_Export then
11441          return Argn > 2;
11442
11443       elsif Pname = Name_Ident then
11444          return Argn = 1;
11445
11446       elsif Pname = Name_Import then
11447          return Argn > 2;
11448
11449       elsif Pname = Name_Interface_Name then
11450          return Argn > 1;
11451
11452       elsif Pname = Name_Linker_Alias then
11453          return Argn = 2;
11454
11455       elsif Pname = Name_Linker_Section then
11456          return Argn = 2;
11457
11458       elsif Pname = Name_Machine_Attribute then
11459          return Argn = 2;
11460
11461       elsif Pname = Name_Source_File_Name then
11462          return True;
11463
11464       elsif Pname = Name_Source_Reference then
11465          return Argn = 2;
11466
11467       elsif Pname = Name_Title then
11468          return True;
11469
11470       elsif Pname = Name_Subtitle then
11471          return True;
11472
11473       else
11474          return False;
11475       end if;
11476    end Is_Pragma_String_Literal;
11477
11478    --------------------------------------
11479    -- Process_Compilation_Unit_Pragmas --
11480    --------------------------------------
11481
11482    procedure Process_Compilation_Unit_Pragmas (N : Node_Id) is
11483    begin
11484       --  A special check for pragma Suppress_All. This is a strange DEC
11485       --  pragma, strange because it comes at the end of the unit. If we
11486       --  have a pragma Suppress_All in the Pragmas_After of the current
11487       --  unit, then we insert a pragma Suppress (All_Checks) at the start
11488       --  of the context clause to ensure the correct processing.
11489
11490       declare
11491          PA : constant List_Id := Pragmas_After (Aux_Decls_Node (N));
11492          P  : Node_Id;
11493
11494       begin
11495          if Present (PA) then
11496             P := First (PA);
11497             while Present (P) loop
11498                if Chars (P) = Name_Suppress_All then
11499                   Prepend_To (Context_Items (N),
11500                     Make_Pragma (Sloc (P),
11501                       Chars => Name_Suppress,
11502                       Pragma_Argument_Associations => New_List (
11503                         Make_Pragma_Argument_Association (Sloc (P),
11504                           Expression =>
11505                             Make_Identifier (Sloc (P),
11506                               Chars => Name_All_Checks)))));
11507                   exit;
11508                end if;
11509
11510                Next (P);
11511             end loop;
11512          end if;
11513       end;
11514    end Process_Compilation_Unit_Pragmas;
11515
11516    --------
11517    -- rv --
11518    --------
11519
11520    procedure rv is
11521    begin
11522       null;
11523    end rv;
11524
11525    --------------------------------
11526    -- Set_Encoded_Interface_Name --
11527    --------------------------------
11528
11529    procedure Set_Encoded_Interface_Name (E : Entity_Id; S : Node_Id) is
11530       Str : constant String_Id := Strval (S);
11531       Len : constant Int       := String_Length (Str);
11532       CC  : Char_Code;
11533       C   : Character;
11534       J   : Int;
11535
11536       Hex : constant array (0 .. 15) of Character := "0123456789abcdef";
11537
11538       procedure Encode;
11539       --  Stores encoded value of character code CC. The encoding we
11540       --  use an underscore followed by four lower case hex digits.
11541
11542       ------------
11543       -- Encode --
11544       ------------
11545
11546       procedure Encode is
11547       begin
11548          Store_String_Char (Get_Char_Code ('_'));
11549          Store_String_Char
11550            (Get_Char_Code (Hex (Integer (CC / 2 ** 12))));
11551          Store_String_Char
11552            (Get_Char_Code (Hex (Integer (CC / 2 ** 8 and 16#0F#))));
11553          Store_String_Char
11554            (Get_Char_Code (Hex (Integer (CC / 2 ** 4 and 16#0F#))));
11555          Store_String_Char
11556            (Get_Char_Code (Hex (Integer (CC and 16#0F#))));
11557       end Encode;
11558
11559    --  Start of processing for Set_Encoded_Interface_Name
11560
11561    begin
11562       --  If first character is asterisk, this is a link name, and we
11563       --  leave it completely unmodified. We also ignore null strings
11564       --  (the latter case happens only in error cases) and no encoding
11565       --  should occur for Java or AAMP interface names.
11566
11567       if Len = 0
11568         or else Get_String_Char (Str, 1) = Get_Char_Code ('*')
11569         or else VM_Target /= No_VM
11570         or else AAMP_On_Target
11571       then
11572          Set_Interface_Name (E, S);
11573
11574       else
11575          J := 1;
11576          loop
11577             CC := Get_String_Char (Str, J);
11578
11579             exit when not In_Character_Range (CC);
11580
11581             C := Get_Character (CC);
11582
11583             exit when C /= '_' and then C /= '$'
11584               and then C not in '0' .. '9'
11585               and then C not in 'a' .. 'z'
11586               and then C not in 'A' .. 'Z';
11587
11588             if J = Len then
11589                Set_Interface_Name (E, S);
11590                return;
11591
11592             else
11593                J := J + 1;
11594             end if;
11595          end loop;
11596
11597          --  Here we need to encode. The encoding we use as follows:
11598          --     three underscores  + four hex digits (lower case)
11599
11600          Start_String;
11601
11602          for J in 1 .. String_Length (Str) loop
11603             CC := Get_String_Char (Str, J);
11604
11605             if not In_Character_Range (CC) then
11606                Encode;
11607             else
11608                C := Get_Character (CC);
11609
11610                if C = '_' or else C = '$'
11611                  or else C in '0' .. '9'
11612                  or else C in 'a' .. 'z'
11613                  or else C in 'A' .. 'Z'
11614                then
11615                   Store_String_Char (CC);
11616                else
11617                   Encode;
11618                end if;
11619             end if;
11620          end loop;
11621
11622          Set_Interface_Name (E,
11623            Make_String_Literal (Sloc (S),
11624              Strval => End_String));
11625       end if;
11626    end Set_Encoded_Interface_Name;
11627
11628    -------------------
11629    -- Set_Unit_Name --
11630    -------------------
11631
11632    procedure Set_Unit_Name (N : Node_Id; With_Item : Node_Id) is
11633       Pref : Node_Id;
11634       Scop : Entity_Id;
11635
11636    begin
11637       if Nkind (N) = N_Identifier
11638         and then Nkind (With_Item) = N_Identifier
11639       then
11640          Set_Entity (N, Entity (With_Item));
11641
11642       elsif Nkind (N) = N_Selected_Component then
11643          Change_Selected_Component_To_Expanded_Name (N);
11644          Set_Entity (N, Entity (With_Item));
11645          Set_Entity (Selector_Name (N), Entity (N));
11646
11647          Pref := Prefix (N);
11648          Scop := Scope (Entity (N));
11649          while Nkind (Pref) = N_Selected_Component loop
11650             Change_Selected_Component_To_Expanded_Name (Pref);
11651             Set_Entity (Selector_Name (Pref), Scop);
11652             Set_Entity (Pref, Scop);
11653             Pref := Prefix (Pref);
11654             Scop := Scope (Scop);
11655          end loop;
11656
11657          Set_Entity (Pref, Scop);
11658       end if;
11659    end Set_Unit_Name;
11660 end Sem_Prag;