OSDN Git Service

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