OSDN Git Service

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