OSDN Git Service

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