OSDN Git Service

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