OSDN Git Service

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