OSDN Git Service

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