OSDN Git Service

2011-08-04 Robert Dewar <dewar@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_prag.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                             S E M _ P R A G                              --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2011, 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 Elists;   use Elists;
39 with Errout;   use Errout;
40 with Exp_Dist; use Exp_Dist;
41 with Exp_Util; use Exp_Util;
42 with Lib;      use Lib;
43 with Lib.Writ; use Lib.Writ;
44 with Lib.Xref; use Lib.Xref;
45 with Namet.Sp; use Namet.Sp;
46 with Nlists;   use Nlists;
47 with Nmake;    use Nmake;
48 with Opt;      use Opt;
49 with Output;   use Output;
50 with Par_SCO;  use Par_SCO;
51 with Restrict; use Restrict;
52 with Rident;   use Rident;
53 with Rtsfind;  use Rtsfind;
54 with Sem;      use Sem;
55 with Sem_Aux;  use Sem_Aux;
56 with Sem_Ch3;  use Sem_Ch3;
57 with Sem_Ch6;  use Sem_Ch6;
58 with Sem_Ch8;  use Sem_Ch8;
59 with Sem_Ch12; use Sem_Ch12;
60 with Sem_Ch13; use Sem_Ch13;
61 with Sem_Disp; use Sem_Disp;
62 with Sem_Dist; use Sem_Dist;
63 with Sem_Elim; use Sem_Elim;
64 with Sem_Eval; use Sem_Eval;
65 with Sem_Intr; use Sem_Intr;
66 with Sem_Mech; use Sem_Mech;
67 with Sem_Res;  use Sem_Res;
68 with Sem_Type; use Sem_Type;
69 with Sem_Util; use Sem_Util;
70 with Sem_VFpt; use Sem_VFpt;
71 with Sem_Warn; use Sem_Warn;
72 with Stand;    use Stand;
73 with Sinfo;    use Sinfo;
74 with Sinfo.CN; use Sinfo.CN;
75 with Sinput;   use Sinput;
76 with Snames;   use Snames;
77 with Stringt;  use Stringt;
78 with Stylesw;  use Stylesw;
79 with Table;
80 with Targparm; use Targparm;
81 with Tbuild;   use Tbuild;
82 with Ttypes;
83 with Uintp;    use Uintp;
84 with Uname;    use Uname;
85 with Urealp;   use Urealp;
86 with Validsw;  use Validsw;
87 with Warnsw;   use Warnsw;
88
89 package body Sem_Prag is
90
91    ----------------------------------------------
92    -- Common Handling of Import-Export Pragmas --
93    ----------------------------------------------
94
95    --  In the following section, a number of Import_xxx and Export_xxx pragmas
96    --  are defined by GNAT. These are compatible with the DEC pragmas of the
97    --  same name, and all have the following common form and processing:
98
99    --  pragma Export_xxx
100    --        [Internal                 =>] LOCAL_NAME
101    --     [, [External                 =>] EXTERNAL_SYMBOL]
102    --     [, other optional parameters   ]);
103
104    --  pragma Import_xxx
105    --        [Internal                 =>] LOCAL_NAME
106    --     [, [External                 =>] EXTERNAL_SYMBOL]
107    --     [, other optional parameters   ]);
108
109    --   EXTERNAL_SYMBOL ::=
110    --     IDENTIFIER
111    --   | static_string_EXPRESSION
112
113    --  The internal LOCAL_NAME designates the entity that is imported or
114    --  exported, and must refer to an entity in the current declarative
115    --  part (as required by the rules for LOCAL_NAME).
116
117    --  The external linker name is designated by the External parameter if
118    --  given, or the Internal parameter if not (if there is no External
119    --  parameter, the External parameter is a copy of the Internal name).
120
121    --  If the External parameter is given as a string, then this string is
122    --  treated as an external name (exactly as though it had been given as an
123    --  External_Name parameter for a normal Import pragma).
124
125    --  If the External parameter is given as an identifier (or there is no
126    --  External parameter, so that the Internal identifier is used), then
127    --  the external name is the characters of the identifier, translated
128    --  to all upper case letters for OpenVMS versions of GNAT, and to all
129    --  lower case letters for all other versions
130
131    --  Note: the external name specified or implied by any of these special
132    --  Import_xxx or Export_xxx pragmas override an external or link name
133    --  specified in a previous Import or Export pragma.
134
135    --  Note: these and all other DEC-compatible GNAT pragmas allow full use of
136    --  named notation, following the standard rules for subprogram calls, i.e.
137    --  parameters can be given in any order if named notation is used, and
138    --  positional and named notation can be mixed, subject to the rule that all
139    --  positional parameters must appear first.
140
141    --  Note: All these pragmas are implemented exactly following the DEC design
142    --  and implementation and are intended to be fully compatible with the use
143    --  of these pragmas in the DEC Ada compiler.
144
145    --------------------------------------------
146    -- Checking for Duplicated External Names --
147    --------------------------------------------
148
149    --  It is suspicious if two separate Export pragmas use the same external
150    --  name. The following table is used to diagnose this situation so that
151    --  an appropriate warning can be issued.
152
153    --  The Node_Id stored is for the N_String_Literal node created to hold
154    --  the value of the external name. The Sloc of this node is used to
155    --  cross-reference the location of the duplication.
156
157    package Externals is new Table.Table (
158      Table_Component_Type => Node_Id,
159      Table_Index_Type     => Int,
160      Table_Low_Bound      => 0,
161      Table_Initial        => 100,
162      Table_Increment      => 100,
163      Table_Name           => "Name_Externals");
164
165    -------------------------------------
166    -- Local Subprograms and Variables --
167    -------------------------------------
168
169    function Adjust_External_Name_Case (N : Node_Id) return Node_Id;
170    --  This routine is used for possible casing adjustment of an explicit
171    --  external name supplied as a string literal (the node N), according to
172    --  the casing requirement of Opt.External_Name_Casing. If this is set to
173    --  As_Is, then the string literal is returned unchanged, but if it is set
174    --  to Uppercase or Lowercase, then a new string literal with appropriate
175    --  casing is constructed.
176
177    function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id;
178    --  If Def_Id refers to a renamed subprogram, then the base subprogram (the
179    --  original one, following the renaming chain) is returned. Otherwise the
180    --  entity is returned unchanged. Should be in Einfo???
181
182    procedure Preanalyze_TC_Args (Arg_Req, Arg_Ens : Node_Id);
183    --  Preanalyze the boolean expressions in the Requires and Ensures arguments
184    --  of a Test_Case pragma if present (possibly Empty). We treat these as
185    --  spec expressions (i.e. similar to a default expression).
186
187    procedure rv;
188    --  This is a dummy function called by the processing for pragma Reviewable.
189    --  It is there for assisting front end debugging. By placing a Reviewable
190    --  pragma in the source program, a breakpoint on rv catches this place in
191    --  the source, allowing convenient stepping to the point of interest.
192
193    procedure Set_Unit_Name (N : Node_Id; With_Item : Node_Id);
194    --  Place semantic information on the argument of an Elaborate/Elaborate_All
195    --  pragma. Entity name for unit and its parents is taken from item in
196    --  previous with_clause that mentions the unit.
197
198    -------------------------------
199    -- Adjust_External_Name_Case --
200    -------------------------------
201
202    function Adjust_External_Name_Case (N : Node_Id) return Node_Id is
203       CC : Char_Code;
204
205    begin
206       --  Adjust case of literal if required
207
208       if Opt.External_Name_Exp_Casing = As_Is then
209          return N;
210
211       else
212          --  Copy existing string
213
214          Start_String;
215
216          --  Set proper casing
217
218          for J in 1 .. String_Length (Strval (N)) loop
219             CC := Get_String_Char (Strval (N), J);
220
221             if Opt.External_Name_Exp_Casing = Uppercase
222               and then CC >= Get_Char_Code ('a')
223               and then CC <= Get_Char_Code ('z')
224             then
225                Store_String_Char (CC - 32);
226
227             elsif Opt.External_Name_Exp_Casing = Lowercase
228               and then CC >= Get_Char_Code ('A')
229               and then CC <= Get_Char_Code ('Z')
230             then
231                Store_String_Char (CC + 32);
232
233             else
234                Store_String_Char (CC);
235             end if;
236          end loop;
237
238          return
239            Make_String_Literal (Sloc (N),
240              Strval => End_String);
241       end if;
242    end Adjust_External_Name_Case;
243
244    ------------------------------
245    -- Analyze_PPC_In_Decl_Part --
246    ------------------------------
247
248    procedure Analyze_PPC_In_Decl_Part (N : Node_Id; S : Entity_Id) is
249       Arg1 : constant Node_Id := First (Pragma_Argument_Associations (N));
250
251    begin
252       --  Install formals and push subprogram spec onto scope stack so that we
253       --  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 spec expression
259       --  (i.e. similar to a default expression).
260
261       Preanalyze_Spec_Expression
262         (Get_Pragma_Arg (Arg1), Standard_Boolean);
263
264       --  Remove the subprogram from the scope stack now that the pre-analysis
265       --  of the precondition/postcondition is done.
266
267       End_Scope;
268    end Analyze_PPC_In_Decl_Part;
269
270    --------------------
271    -- Analyze_Pragma --
272    --------------------
273
274    procedure Analyze_Pragma (N : Node_Id) is
275       Loc     : constant Source_Ptr := Sloc (N);
276       Pname   : constant Name_Id    := Pragma_Name (N);
277       Prag_Id : Pragma_Id;
278
279       Pragma_Exit : exception;
280       --  This exception is used to exit pragma processing completely. It is
281       --  used when an error is detected, and no further processing is
282       --  required. It is also used if an earlier error has left the tree in
283       --  a state where the pragma should not be processed.
284
285       Arg_Count : Nat;
286       --  Number of pragma argument associations
287
288       Arg1 : Node_Id;
289       Arg2 : Node_Id;
290       Arg3 : Node_Id;
291       Arg4 : Node_Id;
292       --  First four pragma arguments (pragma argument association nodes, or
293       --  Empty if the corresponding argument does not exist).
294
295       type Name_List is array (Natural range <>) of Name_Id;
296       type Args_List is array (Natural range <>) of Node_Id;
297       --  Types used for arguments to Check_Arg_Order and Gather_Associations
298
299       procedure Ada_2005_Pragma;
300       --  Called for pragmas defined in Ada 2005, that are not in Ada 95. In
301       --  Ada 95 mode, these are implementation defined pragmas, so should be
302       --  caught by the No_Implementation_Pragmas restriction.
303
304       procedure Ada_2012_Pragma;
305       --  Called for pragmas defined in Ada 2012, that are not in Ada 95 or 05.
306       --  In Ada 95 or 05 mode, these are implementation defined pragmas, so
307       --  should be caught by the No_Implementation_Pragmas restriction.
308
309       procedure Check_Ada_83_Warning;
310       --  Issues a warning message for the current pragma if operating in Ada
311       --  83 mode (used for language pragmas that are not a standard part of
312       --  Ada 83). This procedure does not raise Error_Pragma. Also notes use
313       --  of 95 pragma.
314
315       procedure Check_Arg_Count (Required : Nat);
316       --  Check argument count for pragma is equal to given parameter. If not,
317       --  then issue an error message and raise Pragma_Exit.
318
319       --  Note: all routines whose name is Check_Arg_Is_xxx take an argument
320       --  Arg which can either be a pragma argument association, in which case
321       --  the check is applied to the expression of the association or an
322       --  expression directly.
323
324       procedure Check_Arg_Is_External_Name (Arg : Node_Id);
325       --  Check that an argument has the right form for an EXTERNAL_NAME
326       --  parameter of an extended import/export pragma. The rule is that the
327       --  name must be an identifier or string literal (in Ada 83 mode) or a
328       --  static string expression (in Ada 95 mode).
329
330       procedure Check_Arg_Is_Identifier (Arg : Node_Id);
331       --  Check the specified argument Arg to make sure that it is an
332       --  identifier. If not give error and raise Pragma_Exit.
333
334       procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id);
335       --  Check the specified argument Arg to make sure that it is an integer
336       --  literal. If not give error and raise Pragma_Exit.
337
338       procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id);
339       --  Check the specified argument Arg to make sure that it has the proper
340       --  syntactic form for a local name and meets the semantic requirements
341       --  for a local name. The local name is analyzed as part of the
342       --  processing for this call. In addition, the local name is required
343       --  to represent an entity at the library level.
344
345       procedure Check_Arg_Is_Local_Name (Arg : Node_Id);
346       --  Check the specified argument Arg to make sure that it has the proper
347       --  syntactic form for a local name and meets the semantic requirements
348       --  for a local name. The local name is analyzed as part of the
349       --  processing for this call.
350
351       procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id);
352       --  Check the specified argument Arg to make sure that it is a valid
353       --  locking policy name. If not give error and raise Pragma_Exit.
354
355       procedure Check_Arg_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id);
356       procedure Check_Arg_Is_One_Of (Arg : Node_Id; N1, N2, N3 : Name_Id);
357       procedure Check_Arg_Is_One_Of (Arg : Node_Id; N1, N2, N3, N4 : Name_Id);
358       --  Check the specified argument Arg to make sure that it is an
359       --  identifier whose name matches either N1 or N2 (or N3 if present).
360       --  If not then give error and raise Pragma_Exit.
361
362       procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id);
363       --  Check the specified argument Arg to make sure that it is a valid
364       --  queuing policy name. If not give error and raise Pragma_Exit.
365
366       procedure Check_Arg_Is_Static_Expression
367         (Arg : Node_Id;
368          Typ : Entity_Id := Empty);
369       --  Check the specified argument Arg to make sure that it is a static
370       --  expression of the given type (i.e. it will be analyzed and resolved
371       --  using this type, which can be any valid argument to Resolve, e.g.
372       --  Any_Integer is OK). If not, given error and raise Pragma_Exit. If
373       --  Typ is left Empty, then any static expression is allowed.
374
375       procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id);
376       --  Check the specified argument Arg to make sure that it is a valid task
377       --  dispatching policy name. If not give error and raise Pragma_Exit.
378
379       procedure Check_Arg_Order (Names : Name_List);
380       --  Checks for an instance of two arguments with identifiers for the
381       --  current pragma which are not in the sequence indicated by Names,
382       --  and if so, generates a fatal message about bad order of arguments.
383
384       procedure Check_At_Least_N_Arguments (N : Nat);
385       --  Check there are at least N arguments present
386
387       procedure Check_At_Most_N_Arguments (N : Nat);
388       --  Check there are no more than N arguments present
389
390       procedure Check_Component
391         (Comp            : Node_Id;
392          UU_Typ          : Entity_Id;
393          In_Variant_Part : Boolean := False);
394       --  Examine an Unchecked_Union component for correct use of per-object
395       --  constrained subtypes, and for restrictions on finalizable components.
396       --  UU_Typ is the related Unchecked_Union type. Flag In_Variant_Part
397       --  should be set when Comp comes from a record variant.
398
399       procedure Check_Duplicate_Pragma (E : Entity_Id);
400       --  Check if a pragma of the same name as the current pragma is already
401       --  chained as a rep pragma to the given entity. If so give a message
402       --  about the duplicate, and then raise Pragma_Exit so does not return.
403       --  Also checks for delayed aspect specification node in the chain.
404
405       procedure Check_Duplicated_Export_Name (Nam : Node_Id);
406       --  Nam is an N_String_Literal node containing the external name set by
407       --  an Import or Export pragma (or extended Import or Export pragma).
408       --  This procedure checks for possible duplications if this is the export
409       --  case, and if found, issues an appropriate error message.
410
411       procedure Check_First_Subtype (Arg : Node_Id);
412       --  Checks that Arg, whose expression is an entity name, references a
413       --  first subtype.
414
415       procedure Check_Identifier (Arg : Node_Id; Id : Name_Id);
416       --  Checks that the given argument has an identifier, and if so, requires
417       --  it to match the given identifier name. If there is no identifier, or
418       --  a non-matching identifier, then an error message is given and
419       --  Pragma_Exit is raised.
420
421       procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id);
422       --  Checks that the given argument has an identifier, and if so, requires
423       --  it to match one of the given identifier names. If there is no
424       --  identifier, or a non-matching identifier, then an error message is
425       --  given and Pragma_Exit is raised.
426
427       procedure Check_In_Main_Program;
428       --  Common checks for pragmas that appear within a main program
429       --  (Priority, Main_Storage, Time_Slice, Relative_Deadline, CPU).
430
431       procedure Check_Interrupt_Or_Attach_Handler;
432       --  Common processing for first argument of pragma Interrupt_Handler or
433       --  pragma Attach_Handler.
434
435       procedure Check_Is_In_Decl_Part_Or_Package_Spec;
436       --  Check that pragma appears in a declarative part, or in a package
437       --  specification, i.e. that it does not occur in a statement sequence
438       --  in a body.
439
440       procedure Check_No_Identifier (Arg : Node_Id);
441       --  Checks that the given argument does not have an identifier. If
442       --  an identifier is present, then an error message is issued, and
443       --  Pragma_Exit is raised.
444
445       procedure Check_No_Identifiers;
446       --  Checks that none of the arguments to the pragma has an identifier.
447       --  If any argument has an identifier, then an error message is issued,
448       --  and Pragma_Exit is raised.
449
450       procedure Check_No_Link_Name;
451       --  Checks that no link name is specified
452
453       procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id);
454       --  Checks if the given argument has an identifier, and if so, requires
455       --  it to match the given identifier name. If there is a non-matching
456       --  identifier, then an error message is given and Pragma_Exit is raised.
457
458       procedure Check_Optional_Identifier (Arg : Node_Id; Id : String);
459       --  Checks if the given argument has an identifier, and if so, requires
460       --  it to match the given identifier name. If there is a non-matching
461       --  identifier, then an error message is given and Pragma_Exit is raised.
462       --  In this version of the procedure, the identifier name is given as
463       --  a string with lower case letters.
464
465       procedure Check_Precondition_Postcondition (In_Body : out Boolean);
466       --  Called to process a precondition or postcondition pragma. There are
467       --  three cases:
468       --
469       --    The pragma appears after a subprogram spec
470       --
471       --      If the corresponding check is not enabled, the pragma is analyzed
472       --      but otherwise ignored and control returns with In_Body set False.
473       --
474       --      If the check is enabled, then the first step is to analyze the
475       --      pragma, but this is skipped if the subprogram spec appears within
476       --      a package specification (because this is the case where we delay
477       --      analysis till the end of the spec). Then (whether or not it was
478       --      analyzed), the pragma is chained to the subprogram in question
479       --      (using Spec_PPC_List and Next_Pragma) and control returns to the
480       --      caller with In_Body set False.
481       --
482       --    The pragma appears at the start of subprogram body declarations
483       --
484       --      In this case an immediate return to the caller is made with
485       --      In_Body set True, and the pragma is NOT analyzed.
486       --
487       --    In all other cases, an error message for bad placement is given
488
489       procedure Check_Static_Constraint (Constr : Node_Id);
490       --  Constr is a constraint from an N_Subtype_Indication node from a
491       --  component constraint in an Unchecked_Union type. This routine checks
492       --  that the constraint is static as required by the restrictions for
493       --  Unchecked_Union.
494
495       procedure Check_Test_Case;
496       --  Called to process a test-case pragma. The treatment is similar to the
497       --  one for pre- and postcondition in Check_Precondition_Postcondition.
498       --  There are three cases:
499       --
500       --    The pragma appears after a subprogram spec
501       --
502       --      The first step is to analyze the pragma, but this is skipped if
503       --      the subprogram spec appears within a package specification
504       --      (because this is the case where we delay analysis till the end of
505       --      the spec). Then (whether or not it was analyzed), the pragma is
506       --      chained to the subprogram in question (using Spec_TC_List and
507       --      Next_Pragma).
508       --
509       --    The pragma appears at the start of subprogram body declarations
510       --
511       --      In this case an immediate return to the caller is made, and the
512       --      pragma is NOT analyzed.
513       --
514       --    In all other cases, an error message for bad placement is given
515
516       procedure Check_Valid_Configuration_Pragma;
517       --  Legality checks for placement of a configuration pragma
518
519       procedure Check_Valid_Library_Unit_Pragma;
520       --  Legality checks for library unit pragmas. A special case arises for
521       --  pragmas in generic instances that come from copies of the original
522       --  library unit pragmas in the generic templates. In the case of other
523       --  than library level instantiations these can appear in contexts which
524       --  would normally be invalid (they only apply to the original template
525       --  and to library level instantiations), and they are simply ignored,
526       --  which is implemented by rewriting them as null statements.
527
528       procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id);
529       --  Check an Unchecked_Union variant for lack of nested variants and
530       --  presence of at least one component. UU_Typ is the related Unchecked_
531       --  Union type.
532
533       procedure Error_Pragma (Msg : String);
534       pragma No_Return (Error_Pragma);
535       --  Outputs error message for current pragma. The message contains a %
536       --  that will be replaced with the pragma name, and the flag is placed
537       --  on the pragma itself. Pragma_Exit is then raised.
538
539       procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id);
540       pragma No_Return (Error_Pragma_Arg);
541       --  Outputs error message for current pragma. The message may contain
542       --  a % that will be replaced with the pragma name. The parameter Arg
543       --  may either be a pragma argument association, in which case the flag
544       --  is placed on the expression of this association, or an expression,
545       --  in which case the flag is placed directly on the expression. The
546       --  message is placed using Error_Msg_N, so the message may also contain
547       --  an & insertion character which will reference the given Arg value.
548       --  After placing the message, Pragma_Exit is raised.
549
550       procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id);
551       pragma No_Return (Error_Pragma_Arg);
552       --  Similar to above form of Error_Pragma_Arg except that two messages
553       --  are provided, the second is a continuation comment starting with \.
554
555       procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id);
556       pragma No_Return (Error_Pragma_Arg_Ident);
557       --  Outputs error message for current pragma. The message may contain
558       --  a % that will be replaced with the pragma name. The parameter Arg
559       --  must be a pragma argument association with a non-empty identifier
560       --  (i.e. its Chars field must be set), and the error message is placed
561       --  on the identifier. The message is placed using Error_Msg_N so
562       --  the message may also contain an & insertion character which will
563       --  reference the identifier. After placing the message, Pragma_Exit
564       --  is raised.
565
566       procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id);
567       pragma No_Return (Error_Pragma_Ref);
568       --  Outputs error message for current pragma. The message may contain
569       --  a % that will be replaced with the pragma name. The parameter Ref
570       --  must be an entity whose name can be referenced by & and sloc by #.
571       --  After placing the message, Pragma_Exit is raised.
572
573       function Find_Lib_Unit_Name return Entity_Id;
574       --  Used for a library unit pragma to find the entity to which the
575       --  library unit pragma applies, returns the entity found.
576
577       procedure Find_Program_Unit_Name (Id : Node_Id);
578       --  If the pragma is a compilation unit pragma, the id must denote the
579       --  compilation unit in the same compilation, and the pragma must appear
580       --  in the list of preceding or trailing pragmas. If it is a program
581       --  unit pragma that is not a compilation unit pragma, then the
582       --  identifier must be visible.
583
584       function Find_Unique_Parameterless_Procedure
585         (Name : Entity_Id;
586          Arg  : Node_Id) return Entity_Id;
587       --  Used for a procedure pragma to find the unique parameterless
588       --  procedure identified by Name, returns it if it exists, otherwise
589       --  errors out and uses Arg as the pragma argument for the message.
590
591       procedure Fix_Error (Msg : in out String);
592       --  This is called prior to issuing an error message. Msg is a string
593       --  which typically contains the substring pragma. If the current pragma
594       --  comes from an aspect, each such "pragma" substring is replaced with
595       --  the characters "aspect", and if Error_Msg_Name_1 is Name_Precondition
596       --  (resp Name_Postcondition) it is changed to Name_Pre (resp Name_Post).
597
598       procedure Gather_Associations
599         (Names : Name_List;
600          Args  : out Args_List);
601       --  This procedure is used to gather the arguments for a pragma that
602       --  permits arbitrary ordering of parameters using the normal rules
603       --  for named and positional parameters. The Names argument is a list
604       --  of Name_Id values that corresponds to the allowed pragma argument
605       --  association identifiers in order. The result returned in Args is
606       --  a list of corresponding expressions that are the pragma arguments.
607       --  Note that this is a list of expressions, not of pragma argument
608       --  associations (Gather_Associations has completely checked all the
609       --  optional identifiers when it returns). An entry in Args is Empty
610       --  on return if the corresponding argument is not present.
611
612       procedure GNAT_Pragma;
613       --  Called for all GNAT defined pragmas to check the relevant restriction
614       --  (No_Implementation_Pragmas).
615
616       function Is_Before_First_Decl
617         (Pragma_Node : Node_Id;
618          Decls       : List_Id) return Boolean;
619       --  Return True if Pragma_Node is before the first declarative item in
620       --  Decls where Decls is the list of declarative items.
621
622       function Is_Configuration_Pragma return Boolean;
623       --  Determines if the placement of the current pragma is appropriate
624       --  for a configuration pragma.
625
626       function Is_In_Context_Clause return Boolean;
627       --  Returns True if pragma appears within the context clause of a unit,
628       --  and False for any other placement (does not generate any messages).
629
630       function Is_Static_String_Expression (Arg : Node_Id) return Boolean;
631       --  Analyzes the argument, and determines if it is a static string
632       --  expression, returns True if so, False if non-static or not String.
633
634       procedure Pragma_Misplaced;
635       pragma No_Return (Pragma_Misplaced);
636       --  Issue fatal error message for misplaced pragma
637
638       procedure Process_Atomic_Shared_Volatile;
639       --  Common processing for pragmas Atomic, Shared, Volatile. Note that
640       --  Shared is an obsolete Ada 83 pragma, treated as being identical
641       --  in effect to pragma Atomic.
642
643       procedure Process_Compile_Time_Warning_Or_Error;
644       --  Common processing for Compile_Time_Error and Compile_Time_Warning
645
646       procedure Process_Convention
647         (C   : out Convention_Id;
648          Ent : out Entity_Id);
649       --  Common processing for Convention, Interface, Import and Export.
650       --  Checks first two arguments of pragma, and sets the appropriate
651       --  convention value in the specified entity or entities. On return
652       --  C is the convention, Ent is the referenced entity.
653
654       procedure Process_Extended_Import_Export_Exception_Pragma
655         (Arg_Internal : Node_Id;
656          Arg_External : Node_Id;
657          Arg_Form     : Node_Id;
658          Arg_Code     : Node_Id);
659       --  Common processing for the pragmas Import/Export_Exception. The three
660       --  arguments correspond to the three named parameters of the pragma. An
661       --  argument is empty if the corresponding parameter is not present in
662       --  the pragma.
663
664       procedure Process_Extended_Import_Export_Object_Pragma
665         (Arg_Internal : Node_Id;
666          Arg_External : Node_Id;
667          Arg_Size     : Node_Id);
668       --  Common processing for the pragmas Import/Export_Object. The three
669       --  arguments correspond to the three named parameters of the pragmas. An
670       --  argument is empty if the corresponding parameter is not present in
671       --  the pragma.
672
673       procedure Process_Extended_Import_Export_Internal_Arg
674         (Arg_Internal : Node_Id := Empty);
675       --  Common processing for all extended Import and Export pragmas. The
676       --  argument is the pragma parameter for the Internal argument. If
677       --  Arg_Internal is empty or inappropriate, an error message is posted.
678       --  Otherwise, on normal return, the Entity_Field of Arg_Internal is
679       --  set to identify the referenced entity.
680
681       procedure Process_Extended_Import_Export_Subprogram_Pragma
682         (Arg_Internal                 : Node_Id;
683          Arg_External                 : Node_Id;
684          Arg_Parameter_Types          : Node_Id;
685          Arg_Result_Type              : Node_Id := Empty;
686          Arg_Mechanism                : Node_Id;
687          Arg_Result_Mechanism         : Node_Id := Empty;
688          Arg_First_Optional_Parameter : Node_Id := Empty);
689       --  Common processing for all extended Import and Export pragmas applying
690       --  to subprograms. The caller omits any arguments that do not apply to
691       --  the pragma in question (for example, Arg_Result_Type can be non-Empty
692       --  only in the Import_Function and Export_Function cases). The argument
693       --  names correspond to the allowed pragma association identifiers.
694
695       procedure Process_Generic_List;
696       --  Common processing for Share_Generic and Inline_Generic
697
698       procedure Process_Import_Or_Interface;
699       --  Common processing for Import of Interface
700
701       procedure Process_Import_Predefined_Type;
702       --  Processing for completing a type with pragma Import. This is used
703       --  to declare types that match predefined C types, especially for cases
704       --  without corresponding Ada predefined type.
705
706       procedure Process_Inline (Active : Boolean);
707       --  Common processing for Inline and Inline_Always. The parameter
708       --  indicates if the inline pragma is active, i.e. if it should actually
709       --  cause inlining to occur.
710
711       procedure Process_Interface_Name
712         (Subprogram_Def : Entity_Id;
713          Ext_Arg        : Node_Id;
714          Link_Arg       : Node_Id);
715       --  Given the last two arguments of pragma Import, pragma Export, or
716       --  pragma Interface_Name, performs validity checks and sets the
717       --  Interface_Name field of the given subprogram entity to the
718       --  appropriate external or link name, depending on the arguments given.
719       --  Ext_Arg is always present, but Link_Arg may be missing. Note that
720       --  Ext_Arg may represent the Link_Name if Link_Arg is missing, and
721       --  appropriate named notation is used for Ext_Arg. If neither Ext_Arg
722       --  nor Link_Arg is present, the interface name is set to the default
723       --  from the subprogram name.
724
725       procedure Process_Interrupt_Or_Attach_Handler;
726       --  Common processing for Interrupt and Attach_Handler pragmas
727
728       procedure Process_Restrictions_Or_Restriction_Warnings (Warn : Boolean);
729       --  Common processing for Restrictions and Restriction_Warnings pragmas.
730       --  Warn is True for Restriction_Warnings, or for Restrictions if the
731       --  flag Treat_Restrictions_As_Warnings is set, and False if this flag
732       --  is not set in the Restrictions case.
733
734       procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean);
735       --  Common processing for Suppress and Unsuppress. The boolean parameter
736       --  Suppress_Case is True for the Suppress case, and False for the
737       --  Unsuppress case.
738
739       procedure Set_Exported (E : Entity_Id; Arg : Node_Id);
740       --  This procedure sets the Is_Exported flag for the given entity,
741       --  checking that the entity was not previously imported. Arg is
742       --  the argument that specified the entity. A check is also made
743       --  for exporting inappropriate entities.
744
745       procedure Set_Extended_Import_Export_External_Name
746         (Internal_Ent : Entity_Id;
747          Arg_External : Node_Id);
748       --  Common processing for all extended import export pragmas. The first
749       --  argument, Internal_Ent, is the internal entity, which has already
750       --  been checked for validity by the caller. Arg_External is from the
751       --  Import or Export pragma, and may be null if no External parameter
752       --  was present. If Arg_External is present and is a non-null string
753       --  (a null string is treated as the default), then the Interface_Name
754       --  field of Internal_Ent is set appropriately.
755
756       procedure Set_Imported (E : Entity_Id);
757       --  This procedure sets the Is_Imported flag for the given entity,
758       --  checking that it is not previously exported or imported.
759
760       procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id);
761       --  Mech is a parameter passing mechanism (see Import_Function syntax
762       --  for MECHANISM_NAME). This routine checks that the mechanism argument
763       --  has the right form, and if not issues an error message. If the
764       --  argument has the right form then the Mechanism field of Ent is
765       --  set appropriately.
766
767       procedure Set_Ravenscar_Profile (N : Node_Id);
768       --  Activate the set of configuration pragmas and restrictions that make
769       --  up the Ravenscar Profile. N is the corresponding pragma node, which
770       --  is used for error messages on any constructs that violate the
771       --  profile.
772
773       ---------------------
774       -- Ada_2005_Pragma --
775       ---------------------
776
777       procedure Ada_2005_Pragma is
778       begin
779          if Ada_Version <= Ada_95 then
780             Check_Restriction (No_Implementation_Pragmas, N);
781          end if;
782       end Ada_2005_Pragma;
783
784       ---------------------
785       -- Ada_2012_Pragma --
786       ---------------------
787
788       procedure Ada_2012_Pragma is
789       begin
790          if Ada_Version <= Ada_2005 then
791             Check_Restriction (No_Implementation_Pragmas, N);
792          end if;
793       end Ada_2012_Pragma;
794
795       --------------------------
796       -- Check_Ada_83_Warning --
797       --------------------------
798
799       procedure Check_Ada_83_Warning is
800       begin
801          if Ada_Version = Ada_83 and then Comes_From_Source (N) then
802             Error_Msg_N ("(Ada 83) pragma& is non-standard?", N);
803          end if;
804       end Check_Ada_83_Warning;
805
806       ---------------------
807       -- Check_Arg_Count --
808       ---------------------
809
810       procedure Check_Arg_Count (Required : Nat) is
811       begin
812          if Arg_Count /= Required then
813             Error_Pragma ("wrong number of arguments for pragma%");
814          end if;
815       end Check_Arg_Count;
816
817       --------------------------------
818       -- Check_Arg_Is_External_Name --
819       --------------------------------
820
821       procedure Check_Arg_Is_External_Name (Arg : Node_Id) is
822          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
823
824       begin
825          if Nkind (Argx) = N_Identifier then
826             return;
827
828          else
829             Analyze_And_Resolve (Argx, Standard_String);
830
831             if Is_OK_Static_Expression (Argx) then
832                return;
833
834             elsif Etype (Argx) = Any_Type then
835                raise Pragma_Exit;
836
837             --  An interesting special case, if we have a string literal and
838             --  we are in Ada 83 mode, then we allow it even though it will
839             --  not be flagged as static. This allows expected Ada 83 mode
840             --  use of external names which are string literals, even though
841             --  technically these are not static in Ada 83.
842
843             elsif Ada_Version = Ada_83
844               and then Nkind (Argx) = N_String_Literal
845             then
846                return;
847
848             --  Static expression that raises Constraint_Error. This has
849             --  already been flagged, so just exit from pragma processing.
850
851             elsif Is_Static_Expression (Argx) then
852                raise Pragma_Exit;
853
854             --  Here we have a real error (non-static expression)
855
856             else
857                Error_Msg_Name_1 := Pname;
858
859                declare
860                   Msg : String :=
861                           "argument for pragma% must be a identifier or "
862                           & "static string expression!";
863                begin
864                   Fix_Error (Msg);
865                   Flag_Non_Static_Expr (Msg, Argx);
866                   raise Pragma_Exit;
867                end;
868             end if;
869          end if;
870       end Check_Arg_Is_External_Name;
871
872       -----------------------------
873       -- Check_Arg_Is_Identifier --
874       -----------------------------
875
876       procedure Check_Arg_Is_Identifier (Arg : Node_Id) is
877          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
878       begin
879          if Nkind (Argx) /= N_Identifier then
880             Error_Pragma_Arg
881               ("argument for pragma% must be identifier", Argx);
882          end if;
883       end Check_Arg_Is_Identifier;
884
885       ----------------------------------
886       -- Check_Arg_Is_Integer_Literal --
887       ----------------------------------
888
889       procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id) is
890          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
891       begin
892          if Nkind (Argx) /= N_Integer_Literal then
893             Error_Pragma_Arg
894               ("argument for pragma% must be integer literal", Argx);
895          end if;
896       end Check_Arg_Is_Integer_Literal;
897
898       -------------------------------------------
899       -- Check_Arg_Is_Library_Level_Local_Name --
900       -------------------------------------------
901
902       --  LOCAL_NAME ::=
903       --    DIRECT_NAME
904       --  | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
905       --  | library_unit_NAME
906
907       procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id) is
908       begin
909          Check_Arg_Is_Local_Name (Arg);
910
911          if not Is_Library_Level_Entity (Entity (Get_Pragma_Arg (Arg)))
912            and then Comes_From_Source (N)
913          then
914             Error_Pragma_Arg
915               ("argument for pragma% must be library level entity", Arg);
916          end if;
917       end Check_Arg_Is_Library_Level_Local_Name;
918
919       -----------------------------
920       -- Check_Arg_Is_Local_Name --
921       -----------------------------
922
923       --  LOCAL_NAME ::=
924       --    DIRECT_NAME
925       --  | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
926       --  | library_unit_NAME
927
928       procedure Check_Arg_Is_Local_Name (Arg : Node_Id) is
929          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
930
931       begin
932          Analyze (Argx);
933
934          if Nkind (Argx) not in N_Direct_Name
935            and then (Nkind (Argx) /= N_Attribute_Reference
936                       or else Present (Expressions (Argx))
937                       or else Nkind (Prefix (Argx)) /= N_Identifier)
938            and then (not Is_Entity_Name (Argx)
939                       or else not Is_Compilation_Unit (Entity (Argx)))
940          then
941             Error_Pragma_Arg ("argument for pragma% must be local name", Argx);
942          end if;
943
944          --  No further check required if not an entity name
945
946          if not Is_Entity_Name (Argx) then
947             null;
948
949          else
950             declare
951                OK   : Boolean;
952                Ent  : constant Entity_Id := Entity (Argx);
953                Scop : constant Entity_Id := Scope (Ent);
954             begin
955                --  Case of a pragma applied to a compilation unit: pragma must
956                --  occur immediately after the program unit in the compilation.
957
958                if Is_Compilation_Unit (Ent) then
959                   declare
960                      Decl : constant Node_Id := Unit_Declaration_Node (Ent);
961                   begin
962                      --  Case of pragma placed immediately after spec
963
964                      if Parent (N) = Aux_Decls_Node (Parent (Decl)) then
965                         OK := True;
966
967                      --  Case of pragma placed immediately after body
968
969                      elsif Nkind (Decl) = N_Subprogram_Declaration
970                              and then Present (Corresponding_Body (Decl))
971                      then
972                         OK := Parent (N) =
973                                 Aux_Decls_Node
974                                   (Parent (Unit_Declaration_Node
975                                              (Corresponding_Body (Decl))));
976
977                      --  All other cases are illegal
978
979                      else
980                         OK := False;
981                      end if;
982                   end;
983
984                --  Special restricted placement rule from 10.2.1(11.8/2)
985
986                elsif Is_Generic_Formal (Ent)
987                        and then Prag_Id = Pragma_Preelaborable_Initialization
988                then
989                   OK := List_Containing (N) =
990                           Generic_Formal_Declarations
991                             (Unit_Declaration_Node (Scop));
992
993                --  Default case, just check that the pragma occurs in the scope
994                --  of the entity denoted by the name.
995
996                else
997                   OK := Current_Scope = Scop;
998                end if;
999
1000                if not OK then
1001                   Error_Pragma_Arg
1002                     ("pragma% argument must be in same declarative part", Arg);
1003                end if;
1004             end;
1005          end if;
1006       end Check_Arg_Is_Local_Name;
1007
1008       ---------------------------------
1009       -- Check_Arg_Is_Locking_Policy --
1010       ---------------------------------
1011
1012       procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id) is
1013          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1014
1015       begin
1016          Check_Arg_Is_Identifier (Argx);
1017
1018          if not Is_Locking_Policy_Name (Chars (Argx)) then
1019             Error_Pragma_Arg ("& is not a valid locking policy name", Argx);
1020          end if;
1021       end Check_Arg_Is_Locking_Policy;
1022
1023       -------------------------
1024       -- Check_Arg_Is_One_Of --
1025       -------------------------
1026
1027       procedure Check_Arg_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
1028          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1029
1030       begin
1031          Check_Arg_Is_Identifier (Argx);
1032
1033          if Chars (Argx) /= N1 and then Chars (Argx) /= N2 then
1034             Error_Msg_Name_2 := N1;
1035             Error_Msg_Name_3 := N2;
1036             Error_Pragma_Arg ("argument for pragma% must be% or%", Argx);
1037          end if;
1038       end Check_Arg_Is_One_Of;
1039
1040       procedure Check_Arg_Is_One_Of
1041         (Arg        : Node_Id;
1042          N1, N2, N3 : Name_Id)
1043       is
1044          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1045
1046       begin
1047          Check_Arg_Is_Identifier (Argx);
1048
1049          if Chars (Argx) /= N1
1050            and then Chars (Argx) /= N2
1051            and then Chars (Argx) /= N3
1052          then
1053             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1054          end if;
1055       end Check_Arg_Is_One_Of;
1056
1057       procedure Check_Arg_Is_One_Of
1058         (Arg            : Node_Id;
1059          N1, N2, N3, N4 : Name_Id)
1060       is
1061          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1062
1063       begin
1064          Check_Arg_Is_Identifier (Argx);
1065
1066          if Chars (Argx) /= N1
1067            and then Chars (Argx) /= N2
1068            and then Chars (Argx) /= N3
1069            and then Chars (Argx) /= N4
1070          then
1071             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1072          end if;
1073       end Check_Arg_Is_One_Of;
1074
1075       ---------------------------------
1076       -- Check_Arg_Is_Queuing_Policy --
1077       ---------------------------------
1078
1079       procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id) is
1080          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1081
1082       begin
1083          Check_Arg_Is_Identifier (Argx);
1084
1085          if not Is_Queuing_Policy_Name (Chars (Argx)) then
1086             Error_Pragma_Arg ("& is not a valid queuing policy name", Argx);
1087          end if;
1088       end Check_Arg_Is_Queuing_Policy;
1089
1090       ------------------------------------
1091       -- Check_Arg_Is_Static_Expression --
1092       ------------------------------------
1093
1094       procedure Check_Arg_Is_Static_Expression
1095         (Arg : Node_Id;
1096          Typ : Entity_Id := Empty)
1097       is
1098          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1099
1100       begin
1101          if Present (Typ) then
1102             Analyze_And_Resolve (Argx, Typ);
1103          else
1104             Analyze_And_Resolve (Argx);
1105          end if;
1106
1107          if Is_OK_Static_Expression (Argx) then
1108             return;
1109
1110          elsif Etype (Argx) = Any_Type then
1111             raise Pragma_Exit;
1112
1113          --  An interesting special case, if we have a string literal and we
1114          --  are in Ada 83 mode, then we allow it even though it will not be
1115          --  flagged as static. This allows the use of Ada 95 pragmas like
1116          --  Import in Ada 83 mode. They will of course be flagged with
1117          --  warnings as usual, but will not cause errors.
1118
1119          elsif Ada_Version = Ada_83
1120            and then Nkind (Argx) = N_String_Literal
1121          then
1122             return;
1123
1124          --  Static expression that raises Constraint_Error. This has already
1125          --  been flagged, so just exit from pragma processing.
1126
1127          elsif Is_Static_Expression (Argx) then
1128             raise Pragma_Exit;
1129
1130          --  Finally, we have a real error
1131
1132          else
1133             Error_Msg_Name_1 := Pname;
1134
1135             declare
1136                Msg : String :=
1137                        "argument for pragma% must be a static expression!";
1138             begin
1139                Fix_Error (Msg);
1140                Flag_Non_Static_Expr (Msg, Argx);
1141             end;
1142
1143             raise Pragma_Exit;
1144          end if;
1145       end Check_Arg_Is_Static_Expression;
1146
1147       ------------------------------------------
1148       -- Check_Arg_Is_Task_Dispatching_Policy --
1149       ------------------------------------------
1150
1151       procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id) is
1152          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1153
1154       begin
1155          Check_Arg_Is_Identifier (Argx);
1156
1157          if not Is_Task_Dispatching_Policy_Name (Chars (Argx)) then
1158             Error_Pragma_Arg
1159               ("& is not a valid task dispatching policy name", Argx);
1160          end if;
1161       end Check_Arg_Is_Task_Dispatching_Policy;
1162
1163       ---------------------
1164       -- Check_Arg_Order --
1165       ---------------------
1166
1167       procedure Check_Arg_Order (Names : Name_List) is
1168          Arg : Node_Id;
1169
1170          Highest_So_Far : Natural := 0;
1171          --  Highest index in Names seen do far
1172
1173       begin
1174          Arg := Arg1;
1175          for J in 1 .. Arg_Count loop
1176             if Chars (Arg) /= No_Name then
1177                for K in Names'Range loop
1178                   if Chars (Arg) = Names (K) then
1179                      if K < Highest_So_Far then
1180                         Error_Msg_Name_1 := Pname;
1181                         Error_Msg_N
1182                           ("parameters out of order for pragma%", Arg);
1183                         Error_Msg_Name_1 := Names (K);
1184                         Error_Msg_Name_2 := Names (Highest_So_Far);
1185                         Error_Msg_N ("\% must appear before %", Arg);
1186                         raise Pragma_Exit;
1187
1188                      else
1189                         Highest_So_Far := K;
1190                      end if;
1191                   end if;
1192                end loop;
1193             end if;
1194
1195             Arg := Next (Arg);
1196          end loop;
1197       end Check_Arg_Order;
1198
1199       --------------------------------
1200       -- Check_At_Least_N_Arguments --
1201       --------------------------------
1202
1203       procedure Check_At_Least_N_Arguments (N : Nat) is
1204       begin
1205          if Arg_Count < N then
1206             Error_Pragma ("too few arguments for pragma%");
1207          end if;
1208       end Check_At_Least_N_Arguments;
1209
1210       -------------------------------
1211       -- Check_At_Most_N_Arguments --
1212       -------------------------------
1213
1214       procedure Check_At_Most_N_Arguments (N : Nat) is
1215          Arg : Node_Id;
1216       begin
1217          if Arg_Count > N then
1218             Arg := Arg1;
1219             for J in 1 .. N loop
1220                Next (Arg);
1221                Error_Pragma_Arg ("too many arguments for pragma%", Arg);
1222             end loop;
1223          end if;
1224       end Check_At_Most_N_Arguments;
1225
1226       ---------------------
1227       -- Check_Component --
1228       ---------------------
1229
1230       procedure Check_Component
1231         (Comp            : Node_Id;
1232          UU_Typ          : Entity_Id;
1233          In_Variant_Part : Boolean := False)
1234       is
1235          Comp_Id : constant Entity_Id := Defining_Identifier (Comp);
1236          Sindic  : constant Node_Id :=
1237                      Subtype_Indication (Component_Definition (Comp));
1238          Typ     : constant Entity_Id := Etype (Comp_Id);
1239
1240          function Inside_Generic_Body (Id : Entity_Id) return Boolean;
1241          --  Determine whether entity Id appears inside a generic body.
1242          --  Shouldn't this be in a more general place ???
1243
1244          -------------------------
1245          -- Inside_Generic_Body --
1246          -------------------------
1247
1248          function Inside_Generic_Body (Id : Entity_Id) return Boolean is
1249             S : Entity_Id;
1250
1251          begin
1252             S := Id;
1253             while Present (S) and then S /= Standard_Standard loop
1254                if Ekind (S) = E_Generic_Package
1255                  and then In_Package_Body (S)
1256                then
1257                   return True;
1258                end if;
1259
1260                S := Scope (S);
1261             end loop;
1262
1263             return False;
1264          end Inside_Generic_Body;
1265
1266       --  Start of processing for Check_Component
1267
1268       begin
1269          --  Ada 2005 (AI-216): If a component subtype is subject to a per-
1270          --  object constraint, then the component type shall be an Unchecked_
1271          --  Union.
1272
1273          if Nkind (Sindic) = N_Subtype_Indication
1274            and then Has_Per_Object_Constraint (Comp_Id)
1275            and then not Is_Unchecked_Union (Etype (Subtype_Mark (Sindic)))
1276          then
1277             Error_Msg_N
1278               ("component subtype subject to per-object constraint " &
1279                "must be an Unchecked_Union", Comp);
1280
1281          --  Ada 2012 (AI05-0026): For an unchecked union type declared within
1282          --  the body of a generic unit, or within the body of any of its
1283          --  descendant library units, no part of the type of a component
1284          --  declared in a variant_part of the unchecked union type shall be of
1285          --  a formal private type or formal private extension declared within
1286          --  the formal part of the generic unit.
1287
1288          elsif Ada_Version >= Ada_2012
1289            and then Inside_Generic_Body (UU_Typ)
1290            and then In_Variant_Part
1291            and then Is_Private_Type (Typ)
1292            and then Is_Generic_Type (Typ)
1293          then
1294             Error_Msg_N
1295               ("component of Unchecked_Union cannot be of generic type", Comp);
1296
1297          elsif Needs_Finalization (Typ) then
1298             Error_Msg_N
1299               ("component of Unchecked_Union cannot be controlled", Comp);
1300
1301          elsif Has_Task (Typ) then
1302             Error_Msg_N
1303               ("component of Unchecked_Union cannot have tasks", Comp);
1304          end if;
1305       end Check_Component;
1306
1307       ----------------------------
1308       -- Check_Duplicate_Pragma --
1309       ----------------------------
1310
1311       procedure Check_Duplicate_Pragma (E : Entity_Id) is
1312          P : Node_Id;
1313
1314       begin
1315          --  Nothing to do if this pragma comes from an aspect specification,
1316          --  since we could not be duplicating a pragma, and we dealt with the
1317          --  case of duplicated aspects in Analyze_Aspect_Specifications.
1318
1319          if From_Aspect_Specification (N) then
1320             return;
1321          end if;
1322
1323          --  Otherwise current pragma may duplicate previous pragma or a
1324          --  previously given aspect specification for the same pragma.
1325
1326          P := Get_Rep_Item_For_Entity (E, Pragma_Name (N));
1327
1328          if Present (P) then
1329             Error_Msg_Name_1 := Pragma_Name (N);
1330             Error_Msg_Sloc := Sloc (P);
1331
1332             if Nkind (P) = N_Aspect_Specification
1333               or else From_Aspect_Specification (P)
1334             then
1335                Error_Msg_NE ("aspect% for & previously given#", N, E);
1336             else
1337                Error_Msg_NE ("pragma% for & duplicates pragma#", N, E);
1338             end if;
1339
1340             raise Pragma_Exit;
1341          end if;
1342       end Check_Duplicate_Pragma;
1343
1344       ----------------------------------
1345       -- Check_Duplicated_Export_Name --
1346       ----------------------------------
1347
1348       procedure Check_Duplicated_Export_Name (Nam : Node_Id) is
1349          String_Val : constant String_Id := Strval (Nam);
1350
1351       begin
1352          --  We are only interested in the export case, and in the case of
1353          --  generics, it is the instance, not the template, that is the
1354          --  problem (the template will generate a warning in any case).
1355
1356          if not Inside_A_Generic
1357            and then (Prag_Id = Pragma_Export
1358                        or else
1359                      Prag_Id = Pragma_Export_Procedure
1360                        or else
1361                      Prag_Id = Pragma_Export_Valued_Procedure
1362                        or else
1363                      Prag_Id = Pragma_Export_Function)
1364          then
1365             for J in Externals.First .. Externals.Last loop
1366                if String_Equal (String_Val, Strval (Externals.Table (J))) then
1367                   Error_Msg_Sloc := Sloc (Externals.Table (J));
1368                   Error_Msg_N ("external name duplicates name given#", Nam);
1369                   exit;
1370                end if;
1371             end loop;
1372
1373             Externals.Append (Nam);
1374          end if;
1375       end Check_Duplicated_Export_Name;
1376
1377       -------------------------
1378       -- Check_First_Subtype --
1379       -------------------------
1380
1381       procedure Check_First_Subtype (Arg : Node_Id) is
1382          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1383          Ent  : constant Entity_Id := Entity (Argx);
1384
1385       begin
1386          if Is_First_Subtype (Ent) then
1387             null;
1388
1389          elsif Is_Type (Ent) then
1390             Error_Pragma_Arg
1391               ("pragma% cannot apply to subtype", Argx);
1392
1393          elsif Is_Object (Ent) then
1394             Error_Pragma_Arg
1395               ("pragma% cannot apply to object, requires a type", Argx);
1396
1397          else
1398             Error_Pragma_Arg
1399               ("pragma% cannot apply to&, requires a type", Argx);
1400          end if;
1401       end Check_First_Subtype;
1402
1403       ----------------------
1404       -- Check_Identifier --
1405       ----------------------
1406
1407       procedure Check_Identifier (Arg : Node_Id; Id : Name_Id) is
1408       begin
1409          if Present (Arg)
1410            and then Nkind (Arg) = N_Pragma_Argument_Association
1411          then
1412             if Chars (Arg) = No_Name or else Chars (Arg) /= Id then
1413                Error_Msg_Name_1 := Pname;
1414                Error_Msg_Name_2 := Id;
1415                Error_Msg_N ("pragma% argument expects identifier%", Arg);
1416                raise Pragma_Exit;
1417             end if;
1418          end if;
1419       end Check_Identifier;
1420
1421       --------------------------------
1422       -- Check_Identifier_Is_One_Of --
1423       --------------------------------
1424
1425       procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
1426       begin
1427          if Present (Arg)
1428            and then Nkind (Arg) = N_Pragma_Argument_Association
1429          then
1430             if Chars (Arg) = No_Name then
1431                Error_Msg_Name_1 := Pname;
1432                Error_Msg_N ("pragma% argument expects an identifier", Arg);
1433                raise Pragma_Exit;
1434
1435             elsif Chars (Arg) /= N1
1436               and then Chars (Arg) /= N2
1437             then
1438                Error_Msg_Name_1 := Pname;
1439                Error_Msg_N ("invalid identifier for pragma% argument", Arg);
1440                raise Pragma_Exit;
1441             end if;
1442          end if;
1443       end Check_Identifier_Is_One_Of;
1444
1445       ---------------------------
1446       -- Check_In_Main_Program --
1447       ---------------------------
1448
1449       procedure Check_In_Main_Program is
1450          P : constant Node_Id := Parent (N);
1451
1452       begin
1453          --  Must be at in subprogram body
1454
1455          if Nkind (P) /= N_Subprogram_Body then
1456             Error_Pragma ("% pragma allowed only in subprogram");
1457
1458          --  Otherwise warn if obviously not main program
1459
1460          elsif Present (Parameter_Specifications (Specification (P)))
1461            or else not Is_Compilation_Unit (Defining_Entity (P))
1462          then
1463             Error_Msg_Name_1 := Pname;
1464             Error_Msg_N
1465               ("?pragma% is only effective in main program", N);
1466          end if;
1467       end Check_In_Main_Program;
1468
1469       ---------------------------------------
1470       -- Check_Interrupt_Or_Attach_Handler --
1471       ---------------------------------------
1472
1473       procedure Check_Interrupt_Or_Attach_Handler is
1474          Arg1_X : constant Node_Id := Get_Pragma_Arg (Arg1);
1475          Handler_Proc, Proc_Scope : Entity_Id;
1476
1477       begin
1478          Analyze (Arg1_X);
1479
1480          if Prag_Id = Pragma_Interrupt_Handler then
1481             Check_Restriction (No_Dynamic_Attachment, N);
1482          end if;
1483
1484          Handler_Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
1485          Proc_Scope := Scope (Handler_Proc);
1486
1487          --  On AAMP only, a pragma Interrupt_Handler is supported for
1488          --  nonprotected parameterless procedures.
1489
1490          if not AAMP_On_Target
1491            or else Prag_Id = Pragma_Attach_Handler
1492          then
1493             if Ekind (Proc_Scope) /= E_Protected_Type then
1494                Error_Pragma_Arg
1495                  ("argument of pragma% must be protected procedure", Arg1);
1496             end if;
1497
1498             if Parent (N) /= Protected_Definition (Parent (Proc_Scope)) then
1499                Error_Pragma ("pragma% must be in protected definition");
1500             end if;
1501          end if;
1502
1503          if not Is_Library_Level_Entity (Proc_Scope)
1504            or else (AAMP_On_Target
1505                      and then not Is_Library_Level_Entity (Handler_Proc))
1506          then
1507             Error_Pragma_Arg
1508               ("argument for pragma% must be library level entity", Arg1);
1509          end if;
1510
1511          --  AI05-0033: A pragma cannot appear within a generic body, because
1512          --  instance can be in a nested scope. The check that protected type
1513          --  is itself a library-level declaration is done elsewhere.
1514
1515          --  Note: we omit this check in Codepeer mode to properly handle code
1516          --  prior to AI-0033 (pragmas don't matter to codepeer in any case).
1517
1518          if Inside_A_Generic then
1519             if Ekind (Scope (Current_Scope)) = E_Generic_Package
1520               and then In_Package_Body (Scope (Current_Scope))
1521               and then not CodePeer_Mode
1522             then
1523                Error_Pragma ("pragma% cannot be used inside a generic");
1524             end if;
1525          end if;
1526       end Check_Interrupt_Or_Attach_Handler;
1527
1528       -------------------------------------------
1529       -- Check_Is_In_Decl_Part_Or_Package_Spec --
1530       -------------------------------------------
1531
1532       procedure Check_Is_In_Decl_Part_Or_Package_Spec is
1533          P : Node_Id;
1534
1535       begin
1536          P := Parent (N);
1537          loop
1538             if No (P) then
1539                exit;
1540
1541             elsif Nkind (P) = N_Handled_Sequence_Of_Statements then
1542                exit;
1543
1544             elsif Nkind_In (P, N_Package_Specification,
1545                                N_Block_Statement)
1546             then
1547                return;
1548
1549             --  Note: the following tests seem a little peculiar, because
1550             --  they test for bodies, but if we were in the statement part
1551             --  of the body, we would already have hit the handled statement
1552             --  sequence, so the only way we get here is by being in the
1553             --  declarative part of the body.
1554
1555             elsif Nkind_In (P, N_Subprogram_Body,
1556                                N_Package_Body,
1557                                N_Task_Body,
1558                                N_Entry_Body)
1559             then
1560                return;
1561             end if;
1562
1563             P := Parent (P);
1564          end loop;
1565
1566          Error_Pragma ("pragma% is not in declarative part or package spec");
1567       end Check_Is_In_Decl_Part_Or_Package_Spec;
1568
1569       -------------------------
1570       -- Check_No_Identifier --
1571       -------------------------
1572
1573       procedure Check_No_Identifier (Arg : Node_Id) is
1574       begin
1575          if Nkind (Arg) = N_Pragma_Argument_Association
1576            and then Chars (Arg) /= No_Name
1577          then
1578             Error_Pragma_Arg_Ident
1579               ("pragma% does not permit identifier& here", Arg);
1580          end if;
1581       end Check_No_Identifier;
1582
1583       --------------------------
1584       -- Check_No_Identifiers --
1585       --------------------------
1586
1587       procedure Check_No_Identifiers is
1588          Arg_Node : Node_Id;
1589       begin
1590          if Arg_Count > 0 then
1591             Arg_Node := Arg1;
1592             while Present (Arg_Node) loop
1593                Check_No_Identifier (Arg_Node);
1594                Next (Arg_Node);
1595             end loop;
1596          end if;
1597       end Check_No_Identifiers;
1598
1599       ------------------------
1600       -- Check_No_Link_Name --
1601       ------------------------
1602
1603       procedure Check_No_Link_Name is
1604       begin
1605          if Present (Arg3)
1606            and then Chars (Arg3) = Name_Link_Name
1607          then
1608             Arg4 := Arg3;
1609          end if;
1610
1611          if Present (Arg4) then
1612             Error_Pragma_Arg
1613               ("Link_Name argument not allowed for Import Intrinsic", Arg4);
1614          end if;
1615       end Check_No_Link_Name;
1616
1617       -------------------------------
1618       -- Check_Optional_Identifier --
1619       -------------------------------
1620
1621       procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id) is
1622       begin
1623          if Present (Arg)
1624            and then Nkind (Arg) = N_Pragma_Argument_Association
1625            and then Chars (Arg) /= No_Name
1626          then
1627             if Chars (Arg) /= Id then
1628                Error_Msg_Name_1 := Pname;
1629                Error_Msg_Name_2 := Id;
1630                Error_Msg_N ("pragma% argument expects identifier%", Arg);
1631                raise Pragma_Exit;
1632             end if;
1633          end if;
1634       end Check_Optional_Identifier;
1635
1636       procedure Check_Optional_Identifier (Arg : Node_Id; Id : String) is
1637       begin
1638          Name_Buffer (1 .. Id'Length) := Id;
1639          Name_Len := Id'Length;
1640          Check_Optional_Identifier (Arg, Name_Find);
1641       end Check_Optional_Identifier;
1642
1643       --------------------------------------
1644       -- Check_Precondition_Postcondition --
1645       --------------------------------------
1646
1647       procedure Check_Precondition_Postcondition (In_Body : out Boolean) is
1648          P  : Node_Id;
1649          PO : Node_Id;
1650
1651          procedure Chain_PPC (PO : Node_Id);
1652          --  If PO is an entry or a [generic] subprogram declaration node, then
1653          --  the precondition/postcondition applies to this subprogram and the
1654          --  processing for the pragma is completed. Otherwise the pragma is
1655          --  misplaced.
1656
1657          ---------------
1658          -- Chain_PPC --
1659          ---------------
1660
1661          procedure Chain_PPC (PO : Node_Id) is
1662             S   : Entity_Id;
1663             P   : Node_Id;
1664
1665          begin
1666             if Nkind (PO) = N_Abstract_Subprogram_Declaration then
1667                if not From_Aspect_Specification (N) then
1668                   Error_Pragma
1669                     ("pragma% cannot be applied to abstract subprogram");
1670
1671                elsif Class_Present (N) then
1672                   null;
1673
1674                else
1675                   Error_Pragma
1676                     ("aspect % requires ''Class for abstract subprogram");
1677                end if;
1678
1679             --  AI05-0230: The same restriction applies to null procedures. For
1680             --  compatibility with earlier uses of the Ada pragma, apply this
1681             --  rule only to aspect specifications.
1682
1683             --  The above discrpency needs documentation. Robert is dubious
1684             --  about whether it is a good idea ???
1685
1686             elsif Nkind (PO) = N_Subprogram_Declaration
1687               and then Nkind (Specification (PO)) = N_Procedure_Specification
1688               and then Null_Present (Specification (PO))
1689               and then From_Aspect_Specification (N)
1690               and then not Class_Present (N)
1691             then
1692                Error_Pragma
1693                  ("aspect % requires ''Class for null procedure");
1694
1695             elsif not Nkind_In (PO, N_Subprogram_Declaration,
1696                                     N_Generic_Subprogram_Declaration,
1697                                     N_Entry_Declaration)
1698             then
1699                Pragma_Misplaced;
1700             end if;
1701
1702             --  Here if we have [generic] subprogram or entry declaration
1703
1704             if Nkind (PO) = N_Entry_Declaration then
1705                S := Defining_Entity (PO);
1706             else
1707                S := Defining_Unit_Name (Specification (PO));
1708             end if;
1709
1710             --  Make sure we do not have the case of a precondition pragma when
1711             --  the Pre'Class aspect is present.
1712
1713             --  We do this by looking at pragmas already chained to the entity
1714             --  since the aspect derived pragma will be put on this list first.
1715
1716             if Pragma_Name (N) = Name_Precondition then
1717                if not From_Aspect_Specification (N) then
1718                   P := Spec_PPC_List (Contract (S));
1719                   while Present (P) loop
1720                      if Pragma_Name (P) = Name_Precondition
1721                        and then From_Aspect_Specification (P)
1722                        and then Class_Present (P)
1723                      then
1724                         Error_Msg_Sloc := Sloc (P);
1725                         Error_Pragma
1726                           ("pragma% not allowed, `Pre''Class` aspect given#");
1727                      end if;
1728
1729                      P := Next_Pragma (P);
1730                   end loop;
1731                end if;
1732             end if;
1733
1734             --  Similarly check for Pre with inherited Pre'Class. Note that
1735             --  we cover the aspect case as well here.
1736
1737             if Pragma_Name (N) = Name_Precondition
1738               and then not Class_Present (N)
1739             then
1740                declare
1741                   Inherited : constant Subprogram_List :=
1742                                 Inherited_Subprograms (S);
1743                   P         : Node_Id;
1744
1745                begin
1746                   for J in Inherited'Range loop
1747                      P := Spec_PPC_List (Contract (Inherited (J)));
1748                      while Present (P) loop
1749                         if Pragma_Name (P) = Name_Precondition
1750                           and then Class_Present (P)
1751                         then
1752                            Error_Msg_Sloc := Sloc (P);
1753                            Error_Pragma
1754                              ("pragma% not allowed, `Pre''Class` "
1755                               & "aspect inherited from#");
1756                         end if;
1757
1758                         P := Next_Pragma (P);
1759                      end loop;
1760                   end loop;
1761                end;
1762             end if;
1763
1764             --  Note: we do not analyze the pragma at this point. Instead we
1765             --  delay this analysis until the end of the declarative part in
1766             --  which the pragma appears. This implements the required delay
1767             --  in this analysis, allowing forward references. The analysis
1768             --  happens at the end of Analyze_Declarations.
1769
1770             --  Chain spec PPC pragma to list for subprogram
1771
1772             Set_Next_Pragma (N, Spec_PPC_List (Contract (S)));
1773             Set_Spec_PPC_List (Contract (S), N);
1774
1775             --  Return indicating spec case
1776
1777             In_Body := False;
1778             return;
1779          end Chain_PPC;
1780
1781       --  Start of processing for Check_Precondition_Postcondition
1782
1783       begin
1784          if not Is_List_Member (N) then
1785             Pragma_Misplaced;
1786          end if;
1787
1788          --  Preanalyze message argument if present. Visibility in this
1789          --  argument is established at the point of pragma occurrence.
1790
1791          if Arg_Count = 2 then
1792             Check_Optional_Identifier (Arg2, Name_Message);
1793             Preanalyze_Spec_Expression
1794               (Get_Pragma_Arg (Arg2), Standard_String);
1795          end if;
1796
1797          --  Record if pragma is enabled
1798
1799          if Check_Enabled (Pname) then
1800             Set_SCO_Pragma_Enabled (Loc);
1801          end if;
1802
1803          --  If we are within an inlined body, the legality of the pragma
1804          --  has been checked already.
1805
1806          if In_Inlined_Body then
1807             In_Body := True;
1808             return;
1809          end if;
1810
1811          --  Search prior declarations
1812
1813          P := N;
1814          while Present (Prev (P)) loop
1815             P := Prev (P);
1816
1817             --  If the previous node is a generic subprogram, do not go to to
1818             --  the original node, which is the unanalyzed tree: we need to
1819             --  attach the pre/postconditions to the analyzed version at this
1820             --  point. They get propagated to the original tree when analyzing
1821             --  the corresponding body.
1822
1823             if Nkind (P) not in N_Generic_Declaration then
1824                PO := Original_Node (P);
1825             else
1826                PO := P;
1827             end if;
1828
1829             --  Skip past prior pragma
1830
1831             if Nkind (PO) = N_Pragma then
1832                null;
1833
1834             --  Skip stuff not coming from source
1835
1836             elsif not Comes_From_Source (PO) then
1837
1838                --  The condition may apply to a subprogram instantiation
1839
1840                if Nkind (PO) = N_Subprogram_Declaration
1841                  and then Present (Generic_Parent (Specification (PO)))
1842                then
1843                   Chain_PPC (PO);
1844                   return;
1845
1846                --  For all other cases of non source code, do nothing
1847
1848                else
1849                   null;
1850                end if;
1851
1852             --  Only remaining possibility is subprogram declaration
1853
1854             else
1855                Chain_PPC (PO);
1856                return;
1857             end if;
1858          end loop;
1859
1860          --  If we fall through loop, pragma is at start of list, so see if it
1861          --  is at the start of declarations of a subprogram body.
1862
1863          if Nkind (Parent (N)) = N_Subprogram_Body
1864            and then List_Containing (N) = Declarations (Parent (N))
1865          then
1866             if Operating_Mode /= Generate_Code
1867               or else Inside_A_Generic
1868             then
1869                --  Analyze pragma expression for correctness and for ASIS use
1870
1871                Preanalyze_Spec_Expression
1872                  (Get_Pragma_Arg (Arg1), Standard_Boolean);
1873             end if;
1874
1875             In_Body := True;
1876             return;
1877
1878          --  See if it is in the pragmas after a library level subprogram
1879
1880          elsif Nkind (Parent (N)) = N_Compilation_Unit_Aux then
1881             Chain_PPC (Unit (Parent (Parent (N))));
1882             return;
1883          end if;
1884
1885          --  If we fall through, pragma was misplaced
1886
1887          Pragma_Misplaced;
1888       end Check_Precondition_Postcondition;
1889
1890       -----------------------------
1891       -- Check_Static_Constraint --
1892       -----------------------------
1893
1894       --  Note: for convenience in writing this procedure, in addition to
1895       --  the officially (i.e. by spec) allowed argument which is always a
1896       --  constraint, it also allows ranges and discriminant associations.
1897       --  Above is not clear ???
1898
1899       procedure Check_Static_Constraint (Constr : Node_Id) is
1900
1901          procedure Require_Static (E : Node_Id);
1902          --  Require given expression to be static expression
1903
1904          --------------------
1905          -- Require_Static --
1906          --------------------
1907
1908          procedure Require_Static (E : Node_Id) is
1909          begin
1910             if not Is_OK_Static_Expression (E) then
1911                Flag_Non_Static_Expr
1912                  ("non-static constraint not allowed in Unchecked_Union!", E);
1913                raise Pragma_Exit;
1914             end if;
1915          end Require_Static;
1916
1917       --  Start of processing for Check_Static_Constraint
1918
1919       begin
1920          case Nkind (Constr) is
1921             when N_Discriminant_Association =>
1922                Require_Static (Expression (Constr));
1923
1924             when N_Range =>
1925                Require_Static (Low_Bound (Constr));
1926                Require_Static (High_Bound (Constr));
1927
1928             when N_Attribute_Reference =>
1929                Require_Static (Type_Low_Bound  (Etype (Prefix (Constr))));
1930                Require_Static (Type_High_Bound (Etype (Prefix (Constr))));
1931
1932             when N_Range_Constraint =>
1933                Check_Static_Constraint (Range_Expression (Constr));
1934
1935             when N_Index_Or_Discriminant_Constraint =>
1936                declare
1937                   IDC : Entity_Id;
1938                begin
1939                   IDC := First (Constraints (Constr));
1940                   while Present (IDC) loop
1941                      Check_Static_Constraint (IDC);
1942                      Next (IDC);
1943                   end loop;
1944                end;
1945
1946             when others =>
1947                null;
1948          end case;
1949       end Check_Static_Constraint;
1950
1951       ---------------------
1952       -- Check_Test_Case --
1953       ---------------------
1954
1955       procedure Check_Test_Case is
1956          P  : Node_Id;
1957          PO : Node_Id;
1958
1959          procedure Chain_TC (PO : Node_Id);
1960          --  If PO is an entry or a [generic] subprogram declaration node, then
1961          --  the test-case applies to this subprogram and the processing for
1962          --  the pragma is completed. Otherwise the pragma is misplaced.
1963
1964          --------------
1965          -- Chain_TC --
1966          --------------
1967
1968          procedure Chain_TC (PO : Node_Id) is
1969             S   : Entity_Id;
1970
1971          begin
1972             if Nkind (PO) = N_Abstract_Subprogram_Declaration then
1973                if From_Aspect_Specification (N) then
1974                   Error_Pragma
1975                     ("aspect% cannot be applied to abstract subprogram");
1976                else
1977                   Error_Pragma
1978                     ("pragma% cannot be applied to abstract subprogram");
1979                end if;
1980
1981             elsif not Nkind_In (PO, N_Subprogram_Declaration,
1982                                     N_Generic_Subprogram_Declaration,
1983                                     N_Entry_Declaration)
1984             then
1985                Pragma_Misplaced;
1986             end if;
1987
1988             --  Here if we have [generic] subprogram or entry declaration
1989
1990             if Nkind (PO) = N_Entry_Declaration then
1991                S := Defining_Entity (PO);
1992             else
1993                S := Defining_Unit_Name (Specification (PO));
1994             end if;
1995
1996             --  Note: we do not analyze the pragma at this point. Instead we
1997             --  delay this analysis until the end of the declarative part in
1998             --  which the pragma appears. This implements the required delay
1999             --  in this analysis, allowing forward references. The analysis
2000             --  happens at the end of Analyze_Declarations.
2001
2002             --  There should not be another test case with the same name
2003             --  associated to this subprogram.
2004
2005             declare
2006                Name : constant String_Id := Get_Name_From_Test_Case_Pragma (N);
2007                TC   : Node_Id;
2008
2009             begin
2010                TC := Spec_TC_List (Contract (S));
2011                while Present (TC) loop
2012
2013                   if String_Equal
2014                     (Name, Get_Name_From_Test_Case_Pragma (TC))
2015                   then
2016                      Error_Msg_Sloc := Sloc (TC);
2017
2018                      if From_Aspect_Specification (N) then
2019                         Error_Pragma ("name for aspect% is already used#");
2020                      else
2021                         Error_Pragma ("name for pragma% is already used#");
2022                      end if;
2023                   end if;
2024
2025                   TC := Next_Pragma (TC);
2026                end loop;
2027             end;
2028
2029             --  Chain spec TC pragma to list for subprogram
2030
2031             Set_Next_Pragma (N, Spec_TC_List (Contract (S)));
2032             Set_Spec_TC_List (Contract (S), N);
2033          end Chain_TC;
2034
2035       --  Start of processing for Check_Test_Case
2036
2037       begin
2038          if not Is_List_Member (N) then
2039             Pragma_Misplaced;
2040          end if;
2041
2042          --  Search prior declarations
2043
2044          P := N;
2045          while Present (Prev (P)) loop
2046             P := Prev (P);
2047
2048             --  If the previous node is a generic subprogram, do not go to to
2049             --  the original node, which is the unanalyzed tree: we need to
2050             --  attach the test-case to the analyzed version at this point.
2051             --  They get propagated to the original tree when analyzing the
2052             --  corresponding body.
2053
2054             if Nkind (P) not in N_Generic_Declaration then
2055                PO := Original_Node (P);
2056             else
2057                PO := P;
2058             end if;
2059
2060             --  Skip past prior pragma
2061
2062             if Nkind (PO) = N_Pragma then
2063                null;
2064
2065             --  Skip stuff not coming from source
2066
2067             elsif not Comes_From_Source (PO) then
2068                null;
2069
2070             --  Only remaining possibility is subprogram declaration
2071
2072             else
2073                Chain_TC (PO);
2074                return;
2075             end if;
2076          end loop;
2077
2078          --  If we fall through loop, pragma is at start of list, so see if it
2079          --  is in the pragmas after a library level subprogram.
2080
2081          if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
2082             Chain_TC (Unit (Parent (Parent (N))));
2083             return;
2084          end if;
2085
2086          --  If we fall through, pragma was misplaced
2087
2088          Pragma_Misplaced;
2089       end Check_Test_Case;
2090
2091       --------------------------------------
2092       -- Check_Valid_Configuration_Pragma --
2093       --------------------------------------
2094
2095       --  A configuration pragma must appear in the context clause of a
2096       --  compilation unit, and only other pragmas may precede it. Note that
2097       --  the test also allows use in a configuration pragma file.
2098
2099       procedure Check_Valid_Configuration_Pragma is
2100       begin
2101          if not Is_Configuration_Pragma then
2102             Error_Pragma ("incorrect placement for configuration pragma%");
2103          end if;
2104       end Check_Valid_Configuration_Pragma;
2105
2106       -------------------------------------
2107       -- Check_Valid_Library_Unit_Pragma --
2108       -------------------------------------
2109
2110       procedure Check_Valid_Library_Unit_Pragma is
2111          Plist       : List_Id;
2112          Parent_Node : Node_Id;
2113          Unit_Name   : Entity_Id;
2114          Unit_Kind   : Node_Kind;
2115          Unit_Node   : Node_Id;
2116          Sindex      : Source_File_Index;
2117
2118       begin
2119          if not Is_List_Member (N) then
2120             Pragma_Misplaced;
2121
2122          else
2123             Plist := List_Containing (N);
2124             Parent_Node := Parent (Plist);
2125
2126             if Parent_Node = Empty then
2127                Pragma_Misplaced;
2128
2129             --  Case of pragma appearing after a compilation unit. In this case
2130             --  it must have an argument with the corresponding name and must
2131             --  be part of the following pragmas of its parent.
2132
2133             elsif Nkind (Parent_Node) = N_Compilation_Unit_Aux then
2134                if Plist /= Pragmas_After (Parent_Node) then
2135                   Pragma_Misplaced;
2136
2137                elsif Arg_Count = 0 then
2138                   Error_Pragma
2139                     ("argument required if outside compilation unit");
2140
2141                else
2142                   Check_No_Identifiers;
2143                   Check_Arg_Count (1);
2144                   Unit_Node := Unit (Parent (Parent_Node));
2145                   Unit_Kind := Nkind (Unit_Node);
2146
2147                   Analyze (Get_Pragma_Arg (Arg1));
2148
2149                   if Unit_Kind = N_Generic_Subprogram_Declaration
2150                     or else Unit_Kind = N_Subprogram_Declaration
2151                   then
2152                      Unit_Name := Defining_Entity (Unit_Node);
2153
2154                   elsif Unit_Kind in N_Generic_Instantiation then
2155                      Unit_Name := Defining_Entity (Unit_Node);
2156
2157                   else
2158                      Unit_Name := Cunit_Entity (Current_Sem_Unit);
2159                   end if;
2160
2161                   if Chars (Unit_Name) /=
2162                      Chars (Entity (Get_Pragma_Arg (Arg1)))
2163                   then
2164                      Error_Pragma_Arg
2165                        ("pragma% argument is not current unit name", Arg1);
2166                   end if;
2167
2168                   if Ekind (Unit_Name) = E_Package
2169                     and then Present (Renamed_Entity (Unit_Name))
2170                   then
2171                      Error_Pragma ("pragma% not allowed for renamed package");
2172                   end if;
2173                end if;
2174
2175             --  Pragma appears other than after a compilation unit
2176
2177             else
2178                --  Here we check for the generic instantiation case and also
2179                --  for the case of processing a generic formal package. We
2180                --  detect these cases by noting that the Sloc on the node
2181                --  does not belong to the current compilation unit.
2182
2183                Sindex := Source_Index (Current_Sem_Unit);
2184
2185                if Loc not in Source_First (Sindex) .. Source_Last (Sindex) then
2186                   Rewrite (N, Make_Null_Statement (Loc));
2187                   return;
2188
2189                --  If before first declaration, the pragma applies to the
2190                --  enclosing unit, and the name if present must be this name.
2191
2192                elsif Is_Before_First_Decl (N, Plist) then
2193                   Unit_Node := Unit_Declaration_Node (Current_Scope);
2194                   Unit_Kind := Nkind (Unit_Node);
2195
2196                   if Nkind (Parent (Unit_Node)) /= N_Compilation_Unit then
2197                      Pragma_Misplaced;
2198
2199                   elsif Unit_Kind = N_Subprogram_Body
2200                     and then not Acts_As_Spec (Unit_Node)
2201                   then
2202                      Pragma_Misplaced;
2203
2204                   elsif Nkind (Parent_Node) = N_Package_Body then
2205                      Pragma_Misplaced;
2206
2207                   elsif Nkind (Parent_Node) = N_Package_Specification
2208                     and then Plist = Private_Declarations (Parent_Node)
2209                   then
2210                      Pragma_Misplaced;
2211
2212                   elsif (Nkind (Parent_Node) = N_Generic_Package_Declaration
2213                            or else Nkind (Parent_Node) =
2214                                              N_Generic_Subprogram_Declaration)
2215                     and then Plist = Generic_Formal_Declarations (Parent_Node)
2216                   then
2217                      Pragma_Misplaced;
2218
2219                   elsif Arg_Count > 0 then
2220                      Analyze (Get_Pragma_Arg (Arg1));
2221
2222                      if Entity (Get_Pragma_Arg (Arg1)) /= Current_Scope then
2223                         Error_Pragma_Arg
2224                           ("name in pragma% must be enclosing unit", Arg1);
2225                      end if;
2226
2227                   --  It is legal to have no argument in this context
2228
2229                   else
2230                      return;
2231                   end if;
2232
2233                --  Error if not before first declaration. This is because a
2234                --  library unit pragma argument must be the name of a library
2235                --  unit (RM 10.1.5(7)), but the only names permitted in this
2236                --  context are (RM 10.1.5(6)) names of subprogram declarations,
2237                --  generic subprogram declarations or generic instantiations.
2238
2239                else
2240                   Error_Pragma
2241                     ("pragma% misplaced, must be before first declaration");
2242                end if;
2243             end if;
2244          end if;
2245       end Check_Valid_Library_Unit_Pragma;
2246
2247       -------------------
2248       -- Check_Variant --
2249       -------------------
2250
2251       procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id) is
2252          Clist : constant Node_Id := Component_List (Variant);
2253          Comp  : Node_Id;
2254
2255       begin
2256          if not Is_Non_Empty_List (Component_Items (Clist)) then
2257             Error_Msg_N
2258               ("Unchecked_Union may not have empty component list",
2259                Variant);
2260             return;
2261          end if;
2262
2263          Comp := First (Component_Items (Clist));
2264          while Present (Comp) loop
2265             Check_Component (Comp, UU_Typ, In_Variant_Part => True);
2266             Next (Comp);
2267          end loop;
2268       end Check_Variant;
2269
2270       ------------------
2271       -- Error_Pragma --
2272       ------------------
2273
2274       procedure Error_Pragma (Msg : String) is
2275          MsgF : String := Msg;
2276       begin
2277          Error_Msg_Name_1 := Pname;
2278          Fix_Error (MsgF);
2279          Error_Msg_N (MsgF, N);
2280          raise Pragma_Exit;
2281       end Error_Pragma;
2282
2283       ----------------------
2284       -- Error_Pragma_Arg --
2285       ----------------------
2286
2287       procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id) is
2288          MsgF : String := Msg;
2289       begin
2290          Error_Msg_Name_1 := Pname;
2291          Fix_Error (MsgF);
2292          Error_Msg_N (MsgF, Get_Pragma_Arg (Arg));
2293          raise Pragma_Exit;
2294       end Error_Pragma_Arg;
2295
2296       procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id) is
2297          MsgF : String := Msg1;
2298       begin
2299          Error_Msg_Name_1 := Pname;
2300          Fix_Error (MsgF);
2301          Error_Msg_N (MsgF, Get_Pragma_Arg (Arg));
2302          Error_Pragma_Arg (Msg2, Arg);
2303       end Error_Pragma_Arg;
2304
2305       ----------------------------
2306       -- Error_Pragma_Arg_Ident --
2307       ----------------------------
2308
2309       procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id) is
2310          MsgF : String := Msg;
2311       begin
2312          Error_Msg_Name_1 := Pname;
2313          Fix_Error (MsgF);
2314          Error_Msg_N (MsgF, Arg);
2315          raise Pragma_Exit;
2316       end Error_Pragma_Arg_Ident;
2317
2318       ----------------------
2319       -- Error_Pragma_Ref --
2320       ----------------------
2321
2322       procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id) is
2323          MsgF : String := Msg;
2324       begin
2325          Error_Msg_Name_1 := Pname;
2326          Fix_Error (MsgF);
2327          Error_Msg_Sloc   := Sloc (Ref);
2328          Error_Msg_NE (MsgF, N, Ref);
2329          raise Pragma_Exit;
2330       end Error_Pragma_Ref;
2331
2332       ------------------------
2333       -- Find_Lib_Unit_Name --
2334       ------------------------
2335
2336       function Find_Lib_Unit_Name return Entity_Id is
2337       begin
2338          --  Return inner compilation unit entity, for case of nested
2339          --  categorization pragmas. This happens in generic unit.
2340
2341          if Nkind (Parent (N)) = N_Package_Specification
2342            and then Defining_Entity (Parent (N)) /= Current_Scope
2343          then
2344             return Defining_Entity (Parent (N));
2345          else
2346             return Current_Scope;
2347          end if;
2348       end Find_Lib_Unit_Name;
2349
2350       ----------------------------
2351       -- Find_Program_Unit_Name --
2352       ----------------------------
2353
2354       procedure Find_Program_Unit_Name (Id : Node_Id) is
2355          Unit_Name : Entity_Id;
2356          Unit_Kind : Node_Kind;
2357          P         : constant Node_Id := Parent (N);
2358
2359       begin
2360          if Nkind (P) = N_Compilation_Unit then
2361             Unit_Kind := Nkind (Unit (P));
2362
2363             if Unit_Kind = N_Subprogram_Declaration
2364               or else Unit_Kind = N_Package_Declaration
2365               or else Unit_Kind in N_Generic_Declaration
2366             then
2367                Unit_Name := Defining_Entity (Unit (P));
2368
2369                if Chars (Id) = Chars (Unit_Name) then
2370                   Set_Entity (Id, Unit_Name);
2371                   Set_Etype (Id, Etype (Unit_Name));
2372                else
2373                   Set_Etype (Id, Any_Type);
2374                   Error_Pragma
2375                     ("cannot find program unit referenced by pragma%");
2376                end if;
2377
2378             else
2379                Set_Etype (Id, Any_Type);
2380                Error_Pragma ("pragma% inapplicable to this unit");
2381             end if;
2382
2383          else
2384             Analyze (Id);
2385          end if;
2386       end Find_Program_Unit_Name;
2387
2388       -----------------------------------------
2389       -- Find_Unique_Parameterless_Procedure --
2390       -----------------------------------------
2391
2392       function Find_Unique_Parameterless_Procedure
2393         (Name : Entity_Id;
2394          Arg  : Node_Id) return Entity_Id
2395       is
2396          Proc : Entity_Id := Empty;
2397
2398       begin
2399          --  The body of this procedure needs some comments ???
2400
2401          if not Is_Entity_Name (Name) then
2402             Error_Pragma_Arg
2403               ("argument of pragma% must be entity name", Arg);
2404
2405          elsif not Is_Overloaded (Name) then
2406             Proc := Entity (Name);
2407
2408             if Ekind (Proc) /= E_Procedure
2409               or else Present (First_Formal (Proc))
2410             then
2411                Error_Pragma_Arg
2412                  ("argument of pragma% must be parameterless procedure", Arg);
2413             end if;
2414
2415          else
2416             declare
2417                Found : Boolean := False;
2418                It    : Interp;
2419                Index : Interp_Index;
2420
2421             begin
2422                Get_First_Interp (Name, Index, It);
2423                while Present (It.Nam) loop
2424                   Proc := It.Nam;
2425
2426                   if Ekind (Proc) = E_Procedure
2427                     and then No (First_Formal (Proc))
2428                   then
2429                      if not Found then
2430                         Found := True;
2431                         Set_Entity (Name, Proc);
2432                         Set_Is_Overloaded (Name, False);
2433                      else
2434                         Error_Pragma_Arg
2435                           ("ambiguous handler name for pragma% ", Arg);
2436                      end if;
2437                   end if;
2438
2439                   Get_Next_Interp (Index, It);
2440                end loop;
2441
2442                if not Found then
2443                   Error_Pragma_Arg
2444                     ("argument of pragma% must be parameterless procedure",
2445                      Arg);
2446                else
2447                   Proc := Entity (Name);
2448                end if;
2449             end;
2450          end if;
2451
2452          return Proc;
2453       end Find_Unique_Parameterless_Procedure;
2454
2455       ---------------
2456       -- Fix_Error --
2457       ---------------
2458
2459       procedure Fix_Error (Msg : in out String) is
2460       begin
2461          if From_Aspect_Specification (N) then
2462             for J in Msg'First .. Msg'Last - 5 loop
2463                if Msg (J .. J + 5) = "pragma" then
2464                   Msg (J .. J + 5) := "aspect";
2465                end if;
2466             end loop;
2467
2468             if Error_Msg_Name_1 = Name_Precondition then
2469                Error_Msg_Name_1 := Name_Pre;
2470             elsif Error_Msg_Name_1 = Name_Postcondition then
2471                Error_Msg_Name_1 := Name_Post;
2472             end if;
2473          end if;
2474       end Fix_Error;
2475
2476       -------------------------
2477       -- Gather_Associations --
2478       -------------------------
2479
2480       procedure Gather_Associations
2481         (Names : Name_List;
2482          Args  : out Args_List)
2483       is
2484          Arg : Node_Id;
2485
2486       begin
2487          --  Initialize all parameters to Empty
2488
2489          for J in Args'Range loop
2490             Args (J) := Empty;
2491          end loop;
2492
2493          --  That's all we have to do if there are no argument associations
2494
2495          if No (Pragma_Argument_Associations (N)) then
2496             return;
2497          end if;
2498
2499          --  Otherwise first deal with any positional parameters present
2500
2501          Arg := First (Pragma_Argument_Associations (N));
2502          for Index in Args'Range loop
2503             exit when No (Arg) or else Chars (Arg) /= No_Name;
2504             Args (Index) := Get_Pragma_Arg (Arg);
2505             Next (Arg);
2506          end loop;
2507
2508          --  Positional parameters all processed, if any left, then we
2509          --  have too many positional parameters.
2510
2511          if Present (Arg) and then Chars (Arg) = No_Name then
2512             Error_Pragma_Arg
2513               ("too many positional associations for pragma%", Arg);
2514          end if;
2515
2516          --  Process named parameters if any are present
2517
2518          while Present (Arg) loop
2519             if Chars (Arg) = No_Name then
2520                Error_Pragma_Arg
2521                  ("positional association cannot follow named association",
2522                   Arg);
2523
2524             else
2525                for Index in Names'Range loop
2526                   if Names (Index) = Chars (Arg) then
2527                      if Present (Args (Index)) then
2528                         Error_Pragma_Arg
2529                           ("duplicate argument association for pragma%", Arg);
2530                      else
2531                         Args (Index) := Get_Pragma_Arg (Arg);
2532                         exit;
2533                      end if;
2534                   end if;
2535
2536                   if Index = Names'Last then
2537                      Error_Msg_Name_1 := Pname;
2538                      Error_Msg_N ("pragma% does not allow & argument", Arg);
2539
2540                      --  Check for possible misspelling
2541
2542                      for Index1 in Names'Range loop
2543                         if Is_Bad_Spelling_Of
2544                              (Chars (Arg), Names (Index1))
2545                         then
2546                            Error_Msg_Name_1 := Names (Index1);
2547                            Error_Msg_N -- CODEFIX
2548                              ("\possible misspelling of%", Arg);
2549                            exit;
2550                         end if;
2551                      end loop;
2552
2553                      raise Pragma_Exit;
2554                   end if;
2555                end loop;
2556             end if;
2557
2558             Next (Arg);
2559          end loop;
2560       end Gather_Associations;
2561
2562       -----------------
2563       -- GNAT_Pragma --
2564       -----------------
2565
2566       procedure GNAT_Pragma is
2567       begin
2568          Check_Restriction (No_Implementation_Pragmas, N);
2569       end GNAT_Pragma;
2570
2571       --------------------------
2572       -- Is_Before_First_Decl --
2573       --------------------------
2574
2575       function Is_Before_First_Decl
2576         (Pragma_Node : Node_Id;
2577          Decls       : List_Id) return Boolean
2578       is
2579          Item : Node_Id := First (Decls);
2580
2581       begin
2582          --  Only other pragmas can come before this pragma
2583
2584          loop
2585             if No (Item) or else Nkind (Item) /= N_Pragma then
2586                return False;
2587
2588             elsif Item = Pragma_Node then
2589                return True;
2590             end if;
2591
2592             Next (Item);
2593          end loop;
2594       end Is_Before_First_Decl;
2595
2596       -----------------------------
2597       -- Is_Configuration_Pragma --
2598       -----------------------------
2599
2600       --  A configuration pragma must appear in the context clause of a
2601       --  compilation unit, and only other pragmas may precede it. Note that
2602       --  the test below also permits use in a configuration pragma file.
2603
2604       function Is_Configuration_Pragma return Boolean is
2605          Lis : constant List_Id := List_Containing (N);
2606          Par : constant Node_Id := Parent (N);
2607          Prg : Node_Id;
2608
2609       begin
2610          --  If no parent, then we are in the configuration pragma file,
2611          --  so the placement is definitely appropriate.
2612
2613          if No (Par) then
2614             return True;
2615
2616          --  Otherwise we must be in the context clause of a compilation unit
2617          --  and the only thing allowed before us in the context list is more
2618          --  configuration pragmas.
2619
2620          elsif Nkind (Par) = N_Compilation_Unit
2621            and then Context_Items (Par) = Lis
2622          then
2623             Prg := First (Lis);
2624
2625             loop
2626                if Prg = N then
2627                   return True;
2628                elsif Nkind (Prg) /= N_Pragma then
2629                   return False;
2630                end if;
2631
2632                Next (Prg);
2633             end loop;
2634
2635          else
2636             return False;
2637          end if;
2638       end Is_Configuration_Pragma;
2639
2640       --------------------------
2641       -- Is_In_Context_Clause --
2642       --------------------------
2643
2644       function Is_In_Context_Clause return Boolean is
2645          Plist       : List_Id;
2646          Parent_Node : Node_Id;
2647
2648       begin
2649          if not Is_List_Member (N) then
2650             return False;
2651
2652          else
2653             Plist := List_Containing (N);
2654             Parent_Node := Parent (Plist);
2655
2656             if Parent_Node = Empty
2657               or else Nkind (Parent_Node) /= N_Compilation_Unit
2658               or else Context_Items (Parent_Node) /= Plist
2659             then
2660                return False;
2661             end if;
2662          end if;
2663
2664          return True;
2665       end Is_In_Context_Clause;
2666
2667       ---------------------------------
2668       -- Is_Static_String_Expression --
2669       ---------------------------------
2670
2671       function Is_Static_String_Expression (Arg : Node_Id) return Boolean is
2672          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
2673
2674       begin
2675          Analyze_And_Resolve (Argx);
2676          return Is_OK_Static_Expression (Argx)
2677            and then Nkind (Argx) = N_String_Literal;
2678       end Is_Static_String_Expression;
2679
2680       ----------------------
2681       -- Pragma_Misplaced --
2682       ----------------------
2683
2684       procedure Pragma_Misplaced is
2685       begin
2686          Error_Pragma ("incorrect placement of pragma%");
2687       end Pragma_Misplaced;
2688
2689       ------------------------------------
2690       -- Process Atomic_Shared_Volatile --
2691       ------------------------------------
2692
2693       procedure Process_Atomic_Shared_Volatile is
2694          E_Id : Node_Id;
2695          E    : Entity_Id;
2696          D    : Node_Id;
2697          K    : Node_Kind;
2698          Utyp : Entity_Id;
2699
2700          procedure Set_Atomic (E : Entity_Id);
2701          --  Set given type as atomic, and if no explicit alignment was given,
2702          --  set alignment to unknown, since back end knows what the alignment
2703          --  requirements are for atomic arrays. Note: this step is necessary
2704          --  for derived types.
2705
2706          ----------------
2707          -- Set_Atomic --
2708          ----------------
2709
2710          procedure Set_Atomic (E : Entity_Id) is
2711          begin
2712             Set_Is_Atomic (E);
2713
2714             if not Has_Alignment_Clause (E) then
2715                Set_Alignment (E, Uint_0);
2716             end if;
2717          end Set_Atomic;
2718
2719       --  Start of processing for Process_Atomic_Shared_Volatile
2720
2721       begin
2722          Check_Ada_83_Warning;
2723          Check_No_Identifiers;
2724          Check_Arg_Count (1);
2725          Check_Arg_Is_Local_Name (Arg1);
2726          E_Id := Get_Pragma_Arg (Arg1);
2727
2728          if Etype (E_Id) = Any_Type then
2729             return;
2730          end if;
2731
2732          E := Entity (E_Id);
2733          D := Declaration_Node (E);
2734          K := Nkind (D);
2735
2736          --  Check duplicate before we chain ourselves!
2737
2738          Check_Duplicate_Pragma (E);
2739
2740          --  Now check appropriateness of the entity
2741
2742          if Is_Type (E) then
2743             if Rep_Item_Too_Early (E, N)
2744                  or else
2745                Rep_Item_Too_Late (E, N)
2746             then
2747                return;
2748             else
2749                Check_First_Subtype (Arg1);
2750             end if;
2751
2752             if Prag_Id /= Pragma_Volatile then
2753                Set_Atomic (E);
2754                Set_Atomic (Underlying_Type (E));
2755                Set_Atomic (Base_Type (E));
2756             end if;
2757
2758             --  Attribute belongs on the base type. If the view of the type is
2759             --  currently private, it also belongs on the underlying type.
2760
2761             Set_Is_Volatile (Base_Type (E));
2762             Set_Is_Volatile (Underlying_Type (E));
2763
2764             Set_Treat_As_Volatile (E);
2765             Set_Treat_As_Volatile (Underlying_Type (E));
2766
2767          elsif K = N_Object_Declaration
2768            or else (K = N_Component_Declaration
2769                      and then Original_Record_Component (E) = E)
2770          then
2771             if Rep_Item_Too_Late (E, N) then
2772                return;
2773             end if;
2774
2775             if Prag_Id /= Pragma_Volatile then
2776                Set_Is_Atomic (E);
2777
2778                --  If the object declaration has an explicit initialization, a
2779                --  temporary may have to be created to hold the expression, to
2780                --  ensure that access to the object remain atomic.
2781
2782                if Nkind (Parent (E)) = N_Object_Declaration
2783                  and then Present (Expression (Parent (E)))
2784                then
2785                   Set_Has_Delayed_Freeze (E);
2786                end if;
2787
2788                --  An interesting improvement here. If an object of type X is
2789                --  declared atomic, and the type X is not atomic, that's a
2790                --  pity, since it may not have appropriate alignment etc. We
2791                --  can rescue this in the special case where the object and
2792                --  type are in the same unit by just setting the type as
2793                --  atomic, so that the back end will process it as atomic.
2794
2795                Utyp := Underlying_Type (Etype (E));
2796
2797                if Present (Utyp)
2798                  and then Sloc (E) > No_Location
2799                  and then Sloc (Utyp) > No_Location
2800                  and then
2801                    Get_Source_File_Index (Sloc (E)) =
2802                    Get_Source_File_Index (Sloc (Underlying_Type (Etype (E))))
2803                then
2804                   Set_Is_Atomic (Underlying_Type (Etype (E)));
2805                end if;
2806             end if;
2807
2808             Set_Is_Volatile (E);
2809             Set_Treat_As_Volatile (E);
2810
2811          else
2812             Error_Pragma_Arg
2813               ("inappropriate entity for pragma%", Arg1);
2814          end if;
2815       end Process_Atomic_Shared_Volatile;
2816
2817       -------------------------------------------
2818       -- Process_Compile_Time_Warning_Or_Error --
2819       -------------------------------------------
2820
2821       procedure Process_Compile_Time_Warning_Or_Error is
2822          Arg1x : constant Node_Id := Get_Pragma_Arg (Arg1);
2823
2824       begin
2825          Check_Arg_Count (2);
2826          Check_No_Identifiers;
2827          Check_Arg_Is_Static_Expression (Arg2, Standard_String);
2828          Analyze_And_Resolve (Arg1x, Standard_Boolean);
2829
2830          if Compile_Time_Known_Value (Arg1x) then
2831             if Is_True (Expr_Value (Get_Pragma_Arg (Arg1))) then
2832                declare
2833                   Str   : constant String_Id :=
2834                             Strval (Get_Pragma_Arg (Arg2));
2835                   Len   : constant Int := String_Length (Str);
2836                   Cont  : Boolean;
2837                   Ptr   : Nat;
2838                   CC    : Char_Code;
2839                   C     : Character;
2840                   Cent  : constant Entity_Id :=
2841                             Cunit_Entity (Current_Sem_Unit);
2842
2843                   Force : constant Boolean :=
2844                             Prag_Id = Pragma_Compile_Time_Warning
2845                               and then
2846                                 Is_Spec_Name (Unit_Name (Current_Sem_Unit))
2847                               and then (Ekind (Cent) /= E_Package
2848                                           or else not In_Private_Part (Cent));
2849                   --  Set True if this is the warning case, and we are in the
2850                   --  visible part of a package spec, or in a subprogram spec,
2851                   --  in which case we want to force the client to see the
2852                   --  warning, even though it is not in the main unit.
2853
2854                begin
2855                   --  Loop through segments of message separated by line feeds.
2856                   --  We output these segments as separate messages with
2857                   --  continuation marks for all but the first.
2858
2859                   Cont := False;
2860                   Ptr := 1;
2861                   loop
2862                      Error_Msg_Strlen := 0;
2863
2864                      --  Loop to copy characters from argument to error message
2865                      --  string buffer.
2866
2867                      loop
2868                         exit when Ptr > Len;
2869                         CC := Get_String_Char (Str, Ptr);
2870                         Ptr := Ptr + 1;
2871
2872                         --  Ignore wide chars ??? else store character
2873
2874                         if In_Character_Range (CC) then
2875                            C := Get_Character (CC);
2876                            exit when C = ASCII.LF;
2877                            Error_Msg_Strlen := Error_Msg_Strlen + 1;
2878                            Error_Msg_String (Error_Msg_Strlen) := C;
2879                         end if;
2880                      end loop;
2881
2882                      --  Here with one line ready to go
2883
2884                      Error_Msg_Warn := Prag_Id = Pragma_Compile_Time_Warning;
2885
2886                      --  If this is a warning in a spec, then we want clients
2887                      --  to see the warning, so mark the message with the
2888                      --  special sequence !! to force the warning. In the case
2889                      --  of a package spec, we do not force this if we are in
2890                      --  the private part of the spec.
2891
2892                      if Force then
2893                         if Cont = False then
2894                            Error_Msg_N ("<~!!", Arg1);
2895                            Cont := True;
2896                         else
2897                            Error_Msg_N ("\<~!!", Arg1);
2898                         end if;
2899
2900                      --  Error, rather than warning, or in a body, so we do not
2901                      --  need to force visibility for client (error will be
2902                      --  output in any case, and this is the situation in which
2903                      --  we do not want a client to get a warning, since the
2904                      --  warning is in the body or the spec private part).
2905
2906                      else
2907                         if Cont = False then
2908                            Error_Msg_N ("<~", Arg1);
2909                            Cont := True;
2910                         else
2911                            Error_Msg_N ("\<~", Arg1);
2912                         end if;
2913                      end if;
2914
2915                      exit when Ptr > Len;
2916                   end loop;
2917                end;
2918             end if;
2919          end if;
2920       end Process_Compile_Time_Warning_Or_Error;
2921
2922       ------------------------
2923       -- Process_Convention --
2924       ------------------------
2925
2926       procedure Process_Convention
2927         (C   : out Convention_Id;
2928          Ent : out Entity_Id)
2929       is
2930          Id        : Node_Id;
2931          E         : Entity_Id;
2932          E1        : Entity_Id;
2933          Cname     : Name_Id;
2934          Comp_Unit : Unit_Number_Type;
2935
2936          procedure Diagnose_Multiple_Pragmas (S : Entity_Id);
2937          --  Called if we have more than one Export/Import/Convention pragma.
2938          --  This is generally illegal, but we have a special case of allowing
2939          --  Import and Interface to coexist if they specify the convention in
2940          --  a consistent manner. We are allowed to do this, since Interface is
2941          --  an implementation defined pragma, and we choose to do it since we
2942          --  know Rational allows this combination. S is the entity id of the
2943          --  subprogram in question. This procedure also sets the special flag
2944          --  Import_Interface_Present in both pragmas in the case where we do
2945          --  have matching Import and Interface pragmas.
2946
2947          procedure Set_Convention_From_Pragma (E : Entity_Id);
2948          --  Set convention in entity E, and also flag that the entity has a
2949          --  convention pragma. If entity is for a private or incomplete type,
2950          --  also set convention and flag on underlying type. This procedure
2951          --  also deals with the special case of C_Pass_By_Copy convention.
2952
2953          -------------------------------
2954          -- Diagnose_Multiple_Pragmas --
2955          -------------------------------
2956
2957          procedure Diagnose_Multiple_Pragmas (S : Entity_Id) is
2958             Pdec : constant Node_Id := Declaration_Node (S);
2959             Decl : Node_Id;
2960             Err  : Boolean;
2961
2962             function Same_Convention (Decl : Node_Id) return Boolean;
2963             --  Decl is a pragma node. This function returns True if this
2964             --  pragma has a first argument that is an identifier with a
2965             --  Chars field corresponding to the Convention_Id C.
2966
2967             function Same_Name (Decl : Node_Id) return Boolean;
2968             --  Decl is a pragma node. This function returns True if this
2969             --  pragma has a second argument that is an identifier with a
2970             --  Chars field that matches the Chars of the current subprogram.
2971
2972             ---------------------
2973             -- Same_Convention --
2974             ---------------------
2975
2976             function Same_Convention (Decl : Node_Id) return Boolean is
2977                Arg1 : constant Node_Id :=
2978                         First (Pragma_Argument_Associations (Decl));
2979
2980             begin
2981                if Present (Arg1) then
2982                   declare
2983                      Arg : constant Node_Id := Get_Pragma_Arg (Arg1);
2984                   begin
2985                      if Nkind (Arg) = N_Identifier
2986                        and then Is_Convention_Name (Chars (Arg))
2987                        and then Get_Convention_Id (Chars (Arg)) = C
2988                      then
2989                         return True;
2990                      end if;
2991                   end;
2992                end if;
2993
2994                return False;
2995             end Same_Convention;
2996
2997             ---------------
2998             -- Same_Name --
2999             ---------------
3000
3001             function Same_Name (Decl : Node_Id) return Boolean is
3002                Arg1 : constant Node_Id :=
3003                         First (Pragma_Argument_Associations (Decl));
3004                Arg2 : Node_Id;
3005
3006             begin
3007                if No (Arg1) then
3008                   return False;
3009                end if;
3010
3011                Arg2 := Next (Arg1);
3012
3013                if No (Arg2) then
3014                   return False;
3015                end if;
3016
3017                declare
3018                   Arg : constant Node_Id := Get_Pragma_Arg (Arg2);
3019                begin
3020                   if Nkind (Arg) = N_Identifier
3021                     and then Chars (Arg) = Chars (S)
3022                   then
3023                      return True;
3024                   end if;
3025                end;
3026
3027                return False;
3028             end Same_Name;
3029
3030          --  Start of processing for Diagnose_Multiple_Pragmas
3031
3032          begin
3033             Err := True;
3034
3035             --  Definitely give message if we have Convention/Export here
3036
3037             if Prag_Id = Pragma_Convention or else Prag_Id = Pragma_Export then
3038                null;
3039
3040                --  If we have an Import or Export, scan back from pragma to
3041                --  find any previous pragma applying to the same procedure.
3042                --  The scan will be terminated by the start of the list, or
3043                --  hitting the subprogram declaration. This won't allow one
3044                --  pragma to appear in the public part and one in the private
3045                --  part, but that seems very unlikely in practice.
3046
3047             else
3048                Decl := Prev (N);
3049                while Present (Decl) and then Decl /= Pdec loop
3050
3051                   --  Look for pragma with same name as us
3052
3053                   if Nkind (Decl) = N_Pragma
3054                     and then Same_Name (Decl)
3055                   then
3056                      --  Give error if same as our pragma or Export/Convention
3057
3058                      if Pragma_Name (Decl) = Name_Export
3059                           or else
3060                         Pragma_Name (Decl) = Name_Convention
3061                           or else
3062                         Pragma_Name (Decl) = Pragma_Name (N)
3063                      then
3064                         exit;
3065
3066                      --  Case of Import/Interface or the other way round
3067
3068                      elsif Pragma_Name (Decl) = Name_Interface
3069                              or else
3070                            Pragma_Name (Decl) = Name_Import
3071                      then
3072                         --  Here we know that we have Import and Interface. It
3073                         --  doesn't matter which way round they are. See if
3074                         --  they specify the same convention. If so, all OK,
3075                         --  and set special flags to stop other messages
3076
3077                         if Same_Convention (Decl) then
3078                            Set_Import_Interface_Present (N);
3079                            Set_Import_Interface_Present (Decl);
3080                            Err := False;
3081
3082                         --  If different conventions, special message
3083
3084                         else
3085                            Error_Msg_Sloc := Sloc (Decl);
3086                            Error_Pragma_Arg
3087                              ("convention differs from that given#", Arg1);
3088                            return;
3089                         end if;
3090                      end if;
3091                   end if;
3092
3093                   Next (Decl);
3094                end loop;
3095             end if;
3096
3097             --  Give message if needed if we fall through those tests
3098
3099             if Err then
3100                Error_Pragma_Arg
3101                  ("at most one Convention/Export/Import pragma is allowed",
3102                   Arg2);
3103             end if;
3104          end Diagnose_Multiple_Pragmas;
3105
3106          --------------------------------
3107          -- Set_Convention_From_Pragma --
3108          --------------------------------
3109
3110          procedure Set_Convention_From_Pragma (E : Entity_Id) is
3111          begin
3112             --  Ada 2005 (AI-430): Check invalid attempt to change convention
3113             --  for an overridden dispatching operation. Technically this is
3114             --  an amendment and should only be done in Ada 2005 mode. However,
3115             --  this is clearly a mistake, since the problem that is addressed
3116             --  by this AI is that there is a clear gap in the RM!
3117
3118             if Is_Dispatching_Operation (E)
3119               and then Present (Overridden_Operation (E))
3120               and then C /= Convention (Overridden_Operation (E))
3121             then
3122                Error_Pragma_Arg
3123                  ("cannot change convention for " &
3124                   "overridden dispatching operation",
3125                   Arg1);
3126             end if;
3127
3128             --  Set the convention
3129
3130             Set_Convention (E, C);
3131             Set_Has_Convention_Pragma (E);
3132
3133             if Is_Incomplete_Or_Private_Type (E)
3134               and then Present (Underlying_Type (E))
3135             then
3136                Set_Convention            (Underlying_Type (E), C);
3137                Set_Has_Convention_Pragma (Underlying_Type (E), True);
3138             end if;
3139
3140             --  A class-wide type should inherit the convention of the specific
3141             --  root type (although this isn't specified clearly by the RM).
3142
3143             if Is_Type (E) and then Present (Class_Wide_Type (E)) then
3144                Set_Convention (Class_Wide_Type (E), C);
3145             end if;
3146
3147             --  If the entity is a record type, then check for special case of
3148             --  C_Pass_By_Copy, which is treated the same as C except that the
3149             --  special record flag is set. This convention is only permitted
3150             --  on record types (see AI95-00131).
3151
3152             if Cname = Name_C_Pass_By_Copy then
3153                if Is_Record_Type (E) then
3154                   Set_C_Pass_By_Copy (Base_Type (E));
3155                elsif Is_Incomplete_Or_Private_Type (E)
3156                  and then Is_Record_Type (Underlying_Type (E))
3157                then
3158                   Set_C_Pass_By_Copy (Base_Type (Underlying_Type (E)));
3159                else
3160                   Error_Pragma_Arg
3161                     ("C_Pass_By_Copy convention allowed only for record type",
3162                      Arg2);
3163                end if;
3164             end if;
3165
3166             --  If the entity is a derived boolean type, check for the special
3167             --  case of convention C, C++, or Fortran, where we consider any
3168             --  nonzero value to represent true.
3169
3170             if Is_Discrete_Type (E)
3171               and then Root_Type (Etype (E)) = Standard_Boolean
3172               and then
3173                 (C = Convention_C
3174                    or else
3175                  C = Convention_CPP
3176                    or else
3177                  C = Convention_Fortran)
3178             then
3179                Set_Nonzero_Is_True (Base_Type (E));
3180             end if;
3181          end Set_Convention_From_Pragma;
3182
3183       --  Start of processing for Process_Convention
3184
3185       begin
3186          Check_At_Least_N_Arguments (2);
3187          Check_Optional_Identifier (Arg1, Name_Convention);
3188          Check_Arg_Is_Identifier (Arg1);
3189          Cname := Chars (Get_Pragma_Arg (Arg1));
3190
3191          --  C_Pass_By_Copy is treated as a synonym for convention C (this is
3192          --  tested again below to set the critical flag).
3193
3194          if Cname = Name_C_Pass_By_Copy then
3195             C := Convention_C;
3196
3197          --  Otherwise we must have something in the standard convention list
3198
3199          elsif Is_Convention_Name (Cname) then
3200             C := Get_Convention_Id (Chars (Get_Pragma_Arg (Arg1)));
3201
3202          --  In DEC VMS, it seems that there is an undocumented feature that
3203          --  any unrecognized convention is treated as the default, which for
3204          --  us is convention C. It does not seem so terrible to do this
3205          --  unconditionally, silently in the VMS case, and with a warning
3206          --  in the non-VMS case.
3207
3208          else
3209             if Warn_On_Export_Import and not OpenVMS_On_Target then
3210                Error_Msg_N
3211                  ("?unrecognized convention name, C assumed",
3212                   Get_Pragma_Arg (Arg1));
3213             end if;
3214
3215             C := Convention_C;
3216          end if;
3217
3218          Check_Optional_Identifier (Arg2, Name_Entity);
3219          Check_Arg_Is_Local_Name (Arg2);
3220
3221          Id := Get_Pragma_Arg (Arg2);
3222          Analyze (Id);
3223
3224          if not Is_Entity_Name (Id) then
3225             Error_Pragma_Arg ("entity name required", Arg2);
3226          end if;
3227
3228          E := Entity (Id);
3229
3230          --  Set entity to return
3231
3232          Ent := E;
3233
3234          --  Ada_Pass_By_Copy special checking
3235
3236          if C = Convention_Ada_Pass_By_Copy then
3237             if not Is_First_Subtype (E) then
3238                Error_Pragma_Arg
3239                  ("convention `Ada_Pass_By_Copy` only "
3240                   & "allowed for types", Arg2);
3241             end if;
3242
3243             if Is_By_Reference_Type (E) then
3244                Error_Pragma_Arg
3245                  ("convention `Ada_Pass_By_Copy` not allowed for "
3246                   & "by-reference type", Arg1);
3247             end if;
3248          end if;
3249
3250          --  Ada_Pass_By_Reference special checking
3251
3252          if C = Convention_Ada_Pass_By_Reference then
3253             if not Is_First_Subtype (E) then
3254                Error_Pragma_Arg
3255                  ("convention `Ada_Pass_By_Reference` only "
3256                   & "allowed for types", Arg2);
3257             end if;
3258
3259             if Is_By_Copy_Type (E) then
3260                Error_Pragma_Arg
3261                  ("convention `Ada_Pass_By_Reference` not allowed for "
3262                   & "by-copy type", Arg1);
3263             end if;
3264          end if;
3265
3266          --  Go to renamed subprogram if present, since convention applies to
3267          --  the actual renamed entity, not to the renaming entity. If the
3268          --  subprogram is inherited, go to parent subprogram.
3269
3270          if Is_Subprogram (E)
3271            and then Present (Alias (E))
3272          then
3273             if Nkind (Parent (Declaration_Node (E))) =
3274                                        N_Subprogram_Renaming_Declaration
3275             then
3276                if Scope (E) /= Scope (Alias (E)) then
3277                   Error_Pragma_Ref
3278                     ("cannot apply pragma% to non-local entity&#", E);
3279                end if;
3280
3281                E := Alias (E);
3282
3283             elsif Nkind_In (Parent (E), N_Full_Type_Declaration,
3284                                         N_Private_Extension_Declaration)
3285               and then Scope (E) = Scope (Alias (E))
3286             then
3287                E := Alias (E);
3288
3289                --  Return the parent subprogram the entity was inherited from
3290
3291                Ent := E;
3292             end if;
3293          end if;
3294
3295          --  Check that we are not applying this to a specless body
3296
3297          if Is_Subprogram (E)
3298            and then Nkind (Parent (Declaration_Node (E))) = N_Subprogram_Body
3299          then
3300             Error_Pragma
3301               ("pragma% requires separate spec and must come before body");
3302          end if;
3303
3304          --  Check that we are not applying this to a named constant
3305
3306          if Ekind_In (E, E_Named_Integer, E_Named_Real) then
3307             Error_Msg_Name_1 := Pname;
3308             Error_Msg_N
3309               ("cannot apply pragma% to named constant!",
3310                Get_Pragma_Arg (Arg2));
3311             Error_Pragma_Arg
3312               ("\supply appropriate type for&!", Arg2);
3313          end if;
3314
3315          if Ekind (E) = E_Enumeration_Literal then
3316             Error_Pragma ("enumeration literal not allowed for pragma%");
3317          end if;
3318
3319          --  Check for rep item appearing too early or too late
3320
3321          if Etype (E) = Any_Type
3322            or else Rep_Item_Too_Early (E, N)
3323          then
3324             raise Pragma_Exit;
3325
3326          elsif Present (Underlying_Type (E)) then
3327             E := Underlying_Type (E);
3328          end if;
3329
3330          if Rep_Item_Too_Late (E, N) then
3331             raise Pragma_Exit;
3332          end if;
3333
3334          if Has_Convention_Pragma (E) then
3335             Diagnose_Multiple_Pragmas (E);
3336
3337          elsif Convention (E) = Convention_Protected
3338            or else Ekind (Scope (E)) = E_Protected_Type
3339          then
3340             Error_Pragma_Arg
3341               ("a protected operation cannot be given a different convention",
3342                 Arg2);
3343          end if;
3344
3345          --  For Intrinsic, a subprogram is required
3346
3347          if C = Convention_Intrinsic
3348            and then not Is_Subprogram (E)
3349            and then not Is_Generic_Subprogram (E)
3350          then
3351             Error_Pragma_Arg
3352               ("second argument of pragma% must be a subprogram", Arg2);
3353          end if;
3354
3355          --  For Stdcall, a subprogram, variable or subprogram type is required
3356
3357          if C = Convention_Stdcall
3358            and then not Is_Subprogram (E)
3359            and then not Is_Generic_Subprogram (E)
3360            and then Ekind (E) /= E_Variable
3361            and then not
3362              (Is_Access_Type (E)
3363                and then Ekind (Designated_Type (E)) = E_Subprogram_Type)
3364          then
3365             Error_Pragma_Arg
3366               ("second argument of pragma% must be subprogram (type)",
3367                Arg2);
3368          end if;
3369
3370          if not Is_Subprogram (E)
3371            and then not Is_Generic_Subprogram (E)
3372          then
3373             Set_Convention_From_Pragma (E);
3374
3375             if Is_Type (E) then
3376                Check_First_Subtype (Arg2);
3377                Set_Convention_From_Pragma (Base_Type (E));
3378
3379                --  For subprograms, we must set the convention on the
3380                --  internally generated directly designated type as well.
3381
3382                if Ekind (E) = E_Access_Subprogram_Type then
3383                   Set_Convention_From_Pragma (Directly_Designated_Type (E));
3384                end if;
3385             end if;
3386
3387          --  For the subprogram case, set proper convention for all homonyms
3388          --  in same scope and the same declarative part, i.e. the same
3389          --  compilation unit.
3390
3391          else
3392             Comp_Unit := Get_Source_Unit (E);
3393             Set_Convention_From_Pragma (E);
3394
3395             --  Treat a pragma Import as an implicit body, for GPS use
3396
3397             if Prag_Id = Pragma_Import then
3398                Generate_Reference (E, Id, 'b');
3399             end if;
3400
3401             --  Loop through the homonyms of the pragma argument's entity
3402
3403             E1 := Ent;
3404             loop
3405                E1 := Homonym (E1);
3406                exit when No (E1) or else Scope (E1) /= Current_Scope;
3407
3408                --  Do not set the pragma on inherited operations or on formal
3409                --  subprograms.
3410
3411                if Comes_From_Source (E1)
3412                  and then Comp_Unit = Get_Source_Unit (E1)
3413                  and then not Is_Formal_Subprogram (E1)
3414                  and then Nkind (Original_Node (Parent (E1))) /=
3415                                                     N_Full_Type_Declaration
3416                then
3417                   if Present (Alias (E1))
3418                     and then Scope (E1) /= Scope (Alias (E1))
3419                   then
3420                      Error_Pragma_Ref
3421                        ("cannot apply pragma% to non-local entity& declared#",
3422                         E1);
3423                   end if;
3424
3425                   Set_Convention_From_Pragma (E1);
3426
3427                   if Prag_Id = Pragma_Import then
3428                      Generate_Reference (E1, Id, 'b');
3429                   end if;
3430                end if;
3431
3432                --  For aspect case, do NOT apply to homonyms
3433
3434                exit when From_Aspect_Specification (N);
3435             end loop;
3436          end if;
3437       end Process_Convention;
3438
3439       -----------------------------------------------------
3440       -- Process_Extended_Import_Export_Exception_Pragma --
3441       -----------------------------------------------------
3442
3443       procedure Process_Extended_Import_Export_Exception_Pragma
3444         (Arg_Internal : Node_Id;
3445          Arg_External : Node_Id;
3446          Arg_Form     : Node_Id;
3447          Arg_Code     : Node_Id)
3448       is
3449          Def_Id   : Entity_Id;
3450          Code_Val : Uint;
3451
3452       begin
3453          if not OpenVMS_On_Target then
3454             Error_Pragma
3455               ("?pragma% ignored (applies only to Open'V'M'S)");
3456          end if;
3457
3458          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3459          Def_Id := Entity (Arg_Internal);
3460
3461          if Ekind (Def_Id) /= E_Exception then
3462             Error_Pragma_Arg
3463               ("pragma% must refer to declared exception", Arg_Internal);
3464          end if;
3465
3466          Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
3467
3468          if Present (Arg_Form) then
3469             Check_Arg_Is_One_Of (Arg_Form, Name_Ada, Name_VMS);
3470          end if;
3471
3472          if Present (Arg_Form)
3473            and then Chars (Arg_Form) = Name_Ada
3474          then
3475             null;
3476          else
3477             Set_Is_VMS_Exception (Def_Id);
3478             Set_Exception_Code (Def_Id, No_Uint);
3479          end if;
3480
3481          if Present (Arg_Code) then
3482             if not Is_VMS_Exception (Def_Id) then
3483                Error_Pragma_Arg
3484                  ("Code option for pragma% not allowed for Ada case",
3485                   Arg_Code);
3486             end if;
3487
3488             Check_Arg_Is_Static_Expression (Arg_Code, Any_Integer);
3489             Code_Val := Expr_Value (Arg_Code);
3490
3491             if not UI_Is_In_Int_Range (Code_Val) then
3492                Error_Pragma_Arg
3493                  ("Code option for pragma% must be in 32-bit range",
3494                   Arg_Code);
3495
3496             else
3497                Set_Exception_Code (Def_Id, Code_Val);
3498             end if;
3499          end if;
3500       end Process_Extended_Import_Export_Exception_Pragma;
3501
3502       -------------------------------------------------
3503       -- Process_Extended_Import_Export_Internal_Arg --
3504       -------------------------------------------------
3505
3506       procedure Process_Extended_Import_Export_Internal_Arg
3507         (Arg_Internal : Node_Id := Empty)
3508       is
3509       begin
3510          if No (Arg_Internal) then
3511             Error_Pragma ("Internal parameter required for pragma%");
3512          end if;
3513
3514          if Nkind (Arg_Internal) = N_Identifier then
3515             null;
3516
3517          elsif Nkind (Arg_Internal) = N_Operator_Symbol
3518            and then (Prag_Id = Pragma_Import_Function
3519                        or else
3520                      Prag_Id = Pragma_Export_Function)
3521          then
3522             null;
3523
3524          else
3525             Error_Pragma_Arg
3526               ("wrong form for Internal parameter for pragma%", Arg_Internal);
3527          end if;
3528
3529          Check_Arg_Is_Local_Name (Arg_Internal);
3530       end Process_Extended_Import_Export_Internal_Arg;
3531
3532       --------------------------------------------------
3533       -- Process_Extended_Import_Export_Object_Pragma --
3534       --------------------------------------------------
3535
3536       procedure Process_Extended_Import_Export_Object_Pragma
3537         (Arg_Internal : Node_Id;
3538          Arg_External : Node_Id;
3539          Arg_Size     : Node_Id)
3540       is
3541          Def_Id : Entity_Id;
3542
3543       begin
3544          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3545          Def_Id := Entity (Arg_Internal);
3546
3547          if not Ekind_In (Def_Id, E_Constant, E_Variable) then
3548             Error_Pragma_Arg
3549               ("pragma% must designate an object", Arg_Internal);
3550          end if;
3551
3552          if Has_Rep_Pragma (Def_Id, Name_Common_Object)
3553               or else
3554             Has_Rep_Pragma (Def_Id, Name_Psect_Object)
3555          then
3556             Error_Pragma_Arg
3557               ("previous Common/Psect_Object applies, pragma % not permitted",
3558                Arg_Internal);
3559          end if;
3560
3561          if Rep_Item_Too_Late (Def_Id, N) then
3562             raise Pragma_Exit;
3563          end if;
3564
3565          Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
3566
3567          if Present (Arg_Size) then
3568             Check_Arg_Is_External_Name (Arg_Size);
3569          end if;
3570
3571          --  Export_Object case
3572
3573          if Prag_Id = Pragma_Export_Object then
3574             if not Is_Library_Level_Entity (Def_Id) then
3575                Error_Pragma_Arg
3576                  ("argument for pragma% must be library level entity",
3577                   Arg_Internal);
3578             end if;
3579
3580             if Ekind (Current_Scope) = E_Generic_Package then
3581                Error_Pragma ("pragma& cannot appear in a generic unit");
3582             end if;
3583
3584             if not Size_Known_At_Compile_Time (Etype (Def_Id)) then
3585                Error_Pragma_Arg
3586                  ("exported object must have compile time known size",
3587                   Arg_Internal);
3588             end if;
3589
3590             if Warn_On_Export_Import and then Is_Exported (Def_Id) then
3591                Error_Msg_N ("?duplicate Export_Object pragma", N);
3592             else
3593                Set_Exported (Def_Id, Arg_Internal);
3594             end if;
3595
3596          --  Import_Object case
3597
3598          else
3599             if Is_Concurrent_Type (Etype (Def_Id)) then
3600                Error_Pragma_Arg
3601                  ("cannot use pragma% for task/protected object",
3602                   Arg_Internal);
3603             end if;
3604
3605             if Ekind (Def_Id) = E_Constant then
3606                Error_Pragma_Arg
3607                  ("cannot import a constant", Arg_Internal);
3608             end if;
3609
3610             if Warn_On_Export_Import
3611               and then Has_Discriminants (Etype (Def_Id))
3612             then
3613                Error_Msg_N
3614                  ("imported value must be initialized?", Arg_Internal);
3615             end if;
3616
3617             if Warn_On_Export_Import
3618               and then Is_Access_Type (Etype (Def_Id))
3619             then
3620                Error_Pragma_Arg
3621                  ("cannot import object of an access type?", Arg_Internal);
3622             end if;
3623
3624             if Warn_On_Export_Import
3625               and then Is_Imported (Def_Id)
3626             then
3627                Error_Msg_N
3628                  ("?duplicate Import_Object pragma", N);
3629
3630             --  Check for explicit initialization present. Note that an
3631             --  initialization generated by the code generator, e.g. for an
3632             --  access type, does not count here.
3633
3634             elsif Present (Expression (Parent (Def_Id)))
3635                and then
3636                  Comes_From_Source
3637                    (Original_Node (Expression (Parent (Def_Id))))
3638             then
3639                Error_Msg_Sloc := Sloc (Def_Id);
3640                Error_Pragma_Arg
3641                  ("imported entities cannot be initialized (RM B.1(24))",
3642                   "\no initialization allowed for & declared#", Arg1);
3643             else
3644                Set_Imported (Def_Id);
3645                Note_Possible_Modification (Arg_Internal, Sure => False);
3646             end if;
3647          end if;
3648       end Process_Extended_Import_Export_Object_Pragma;
3649
3650       ------------------------------------------------------
3651       -- Process_Extended_Import_Export_Subprogram_Pragma --
3652       ------------------------------------------------------
3653
3654       procedure Process_Extended_Import_Export_Subprogram_Pragma
3655         (Arg_Internal                 : Node_Id;
3656          Arg_External                 : Node_Id;
3657          Arg_Parameter_Types          : Node_Id;
3658          Arg_Result_Type              : Node_Id := Empty;
3659          Arg_Mechanism                : Node_Id;
3660          Arg_Result_Mechanism         : Node_Id := Empty;
3661          Arg_First_Optional_Parameter : Node_Id := Empty)
3662       is
3663          Ent       : Entity_Id;
3664          Def_Id    : Entity_Id;
3665          Hom_Id    : Entity_Id;
3666          Formal    : Entity_Id;
3667          Ambiguous : Boolean;
3668          Match     : Boolean;
3669          Dval      : Node_Id;
3670
3671          function Same_Base_Type
3672           (Ptype  : Node_Id;
3673            Formal : Entity_Id) return Boolean;
3674          --  Determines if Ptype references the type of Formal. Note that only
3675          --  the base types need to match according to the spec. Ptype here is
3676          --  the argument from the pragma, which is either a type name, or an
3677          --  access attribute.
3678
3679          --------------------
3680          -- Same_Base_Type --
3681          --------------------
3682
3683          function Same_Base_Type
3684            (Ptype  : Node_Id;
3685             Formal : Entity_Id) return Boolean
3686          is
3687             Ftyp : constant Entity_Id := Base_Type (Etype (Formal));
3688             Pref : Node_Id;
3689
3690          begin
3691             --  Case where pragma argument is typ'Access
3692
3693             if Nkind (Ptype) = N_Attribute_Reference
3694               and then Attribute_Name (Ptype) = Name_Access
3695             then
3696                Pref := Prefix (Ptype);
3697                Find_Type (Pref);
3698
3699                if not Is_Entity_Name (Pref)
3700                  or else Entity (Pref) = Any_Type
3701                then
3702                   raise Pragma_Exit;
3703                end if;
3704
3705                --  We have a match if the corresponding argument is of an
3706                --  anonymous access type, and its designated type matches the
3707                --  type of the prefix of the access attribute
3708
3709                return Ekind (Ftyp) = E_Anonymous_Access_Type
3710                  and then Base_Type (Entity (Pref)) =
3711                             Base_Type (Etype (Designated_Type (Ftyp)));
3712
3713             --  Case where pragma argument is a type name
3714
3715             else
3716                Find_Type (Ptype);
3717
3718                if not Is_Entity_Name (Ptype)
3719                  or else Entity (Ptype) = Any_Type
3720                then
3721                   raise Pragma_Exit;
3722                end if;
3723
3724                --  We have a match if the corresponding argument is of the type
3725                --  given in the pragma (comparing base types)
3726
3727                return Base_Type (Entity (Ptype)) = Ftyp;
3728             end if;
3729          end Same_Base_Type;
3730
3731       --  Start of processing for
3732       --  Process_Extended_Import_Export_Subprogram_Pragma
3733
3734       begin
3735          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3736          Ent := Empty;
3737          Ambiguous := False;
3738
3739          --  Loop through homonyms (overloadings) of the entity
3740
3741          Hom_Id := Entity (Arg_Internal);
3742          while Present (Hom_Id) loop
3743             Def_Id := Get_Base_Subprogram (Hom_Id);
3744
3745             --  We need a subprogram in the current scope
3746
3747             if not Is_Subprogram (Def_Id)
3748               or else Scope (Def_Id) /= Current_Scope
3749             then
3750                null;
3751
3752             else
3753                Match := True;
3754
3755                --  Pragma cannot apply to subprogram body
3756
3757                if Is_Subprogram (Def_Id)
3758                  and then Nkind (Parent (Declaration_Node (Def_Id))) =
3759                                                              N_Subprogram_Body
3760                then
3761                   Error_Pragma
3762                     ("pragma% requires separate spec"
3763                       & " and must come before body");
3764                end if;
3765
3766                --  Test result type if given, note that the result type
3767                --  parameter can only be present for the function cases.
3768
3769                if Present (Arg_Result_Type)
3770                  and then not Same_Base_Type (Arg_Result_Type, Def_Id)
3771                then
3772                   Match := False;
3773
3774                elsif Etype (Def_Id) /= Standard_Void_Type
3775                  and then
3776                    (Pname = Name_Export_Procedure
3777                       or else
3778                     Pname = Name_Import_Procedure)
3779                then
3780                   Match := False;
3781
3782                --  Test parameter types if given. Note that this parameter
3783                --  has not been analyzed (and must not be, since it is
3784                --  semantic nonsense), so we get it as the parser left it.
3785
3786                elsif Present (Arg_Parameter_Types) then
3787                   Check_Matching_Types : declare
3788                      Formal : Entity_Id;
3789                      Ptype  : Node_Id;
3790
3791                   begin
3792                      Formal := First_Formal (Def_Id);
3793
3794                      if Nkind (Arg_Parameter_Types) = N_Null then
3795                         if Present (Formal) then
3796                            Match := False;
3797                         end if;
3798
3799                      --  A list of one type, e.g. (List) is parsed as
3800                      --  a parenthesized expression.
3801
3802                      elsif Nkind (Arg_Parameter_Types) /= N_Aggregate
3803                        and then Paren_Count (Arg_Parameter_Types) = 1
3804                      then
3805                         if No (Formal)
3806                           or else Present (Next_Formal (Formal))
3807                         then
3808                            Match := False;
3809                         else
3810                            Match :=
3811                              Same_Base_Type (Arg_Parameter_Types, Formal);
3812                         end if;
3813
3814                      --  A list of more than one type is parsed as a aggregate
3815
3816                      elsif Nkind (Arg_Parameter_Types) = N_Aggregate
3817                        and then Paren_Count (Arg_Parameter_Types) = 0
3818                      then
3819                         Ptype := First (Expressions (Arg_Parameter_Types));
3820                         while Present (Ptype) or else Present (Formal) loop
3821                            if No (Ptype)
3822                              or else No (Formal)
3823                              or else not Same_Base_Type (Ptype, Formal)
3824                            then
3825                               Match := False;
3826                               exit;
3827                            else
3828                               Next_Formal (Formal);
3829                               Next (Ptype);
3830                            end if;
3831                         end loop;
3832
3833                      --  Anything else is of the wrong form
3834
3835                      else
3836                         Error_Pragma_Arg
3837                           ("wrong form for Parameter_Types parameter",
3838                            Arg_Parameter_Types);
3839                      end if;
3840                   end Check_Matching_Types;
3841                end if;
3842
3843                --  Match is now False if the entry we found did not match
3844                --  either a supplied Parameter_Types or Result_Types argument
3845
3846                if Match then
3847                   if No (Ent) then
3848                      Ent := Def_Id;
3849
3850                   --  Ambiguous case, the flag Ambiguous shows if we already
3851                   --  detected this and output the initial messages.
3852
3853                   else
3854                      if not Ambiguous then
3855                         Ambiguous := True;
3856                         Error_Msg_Name_1 := Pname;
3857                         Error_Msg_N
3858                           ("pragma% does not uniquely identify subprogram!",
3859                            N);
3860                         Error_Msg_Sloc := Sloc (Ent);
3861                         Error_Msg_N ("matching subprogram #!", N);
3862                         Ent := Empty;
3863                      end if;
3864
3865                      Error_Msg_Sloc := Sloc (Def_Id);
3866                      Error_Msg_N ("matching subprogram #!", N);
3867                   end if;
3868                end if;
3869             end if;
3870
3871             Hom_Id := Homonym (Hom_Id);
3872          end loop;
3873
3874          --  See if we found an entry
3875
3876          if No (Ent) then
3877             if not Ambiguous then
3878                if Is_Generic_Subprogram (Entity (Arg_Internal)) then
3879                   Error_Pragma
3880                     ("pragma% cannot be given for generic subprogram");
3881                else
3882                   Error_Pragma
3883                     ("pragma% does not identify local subprogram");
3884                end if;
3885             end if;
3886
3887             return;
3888          end if;
3889
3890          --  Import pragmas must be for imported entities
3891
3892          if Prag_Id = Pragma_Import_Function
3893               or else
3894             Prag_Id = Pragma_Import_Procedure
3895               or else
3896             Prag_Id = Pragma_Import_Valued_Procedure
3897          then
3898             if not Is_Imported (Ent) then
3899                Error_Pragma
3900                  ("pragma Import or Interface must precede pragma%");
3901             end if;
3902
3903          --  Here we have the Export case which can set the entity as exported
3904
3905          --  But does not do so if the specified external name is null, since
3906          --  that is taken as a signal in DEC Ada 83 (with which we want to be
3907          --  compatible) to request no external name.
3908
3909          elsif Nkind (Arg_External) = N_String_Literal
3910            and then String_Length (Strval (Arg_External)) = 0
3911          then
3912             null;
3913
3914          --  In all other cases, set entity as exported
3915
3916          else
3917             Set_Exported (Ent, Arg_Internal);
3918          end if;
3919
3920          --  Special processing for Valued_Procedure cases
3921
3922          if Prag_Id = Pragma_Import_Valued_Procedure
3923            or else
3924             Prag_Id = Pragma_Export_Valued_Procedure
3925          then
3926             Formal := First_Formal (Ent);
3927
3928             if No (Formal) then
3929                Error_Pragma ("at least one parameter required for pragma%");
3930
3931             elsif Ekind (Formal) /= E_Out_Parameter then
3932                Error_Pragma ("first parameter must have mode out for pragma%");
3933
3934             else
3935                Set_Is_Valued_Procedure (Ent);
3936             end if;
3937          end if;
3938
3939          Set_Extended_Import_Export_External_Name (Ent, Arg_External);
3940
3941          --  Process Result_Mechanism argument if present. We have already
3942          --  checked that this is only allowed for the function case.
3943
3944          if Present (Arg_Result_Mechanism) then
3945             Set_Mechanism_Value (Ent, Arg_Result_Mechanism);
3946          end if;
3947
3948          --  Process Mechanism parameter if present. Note that this parameter
3949          --  is not analyzed, and must not be analyzed since it is semantic
3950          --  nonsense, so we get it in exactly as the parser left it.
3951
3952          if Present (Arg_Mechanism) then
3953             declare
3954                Formal : Entity_Id;
3955                Massoc : Node_Id;
3956                Mname  : Node_Id;
3957                Choice : Node_Id;
3958
3959             begin
3960                --  A single mechanism association without a formal parameter
3961                --  name is parsed as a parenthesized expression. All other
3962                --  cases are parsed as aggregates, so we rewrite the single
3963                --  parameter case as an aggregate for consistency.
3964
3965                if Nkind (Arg_Mechanism) /= N_Aggregate
3966                  and then Paren_Count (Arg_Mechanism) = 1
3967                then
3968                   Rewrite (Arg_Mechanism,
3969                     Make_Aggregate (Sloc (Arg_Mechanism),
3970                       Expressions => New_List (
3971                         Relocate_Node (Arg_Mechanism))));
3972                end if;
3973
3974                --  Case of only mechanism name given, applies to all formals
3975
3976                if Nkind (Arg_Mechanism) /= N_Aggregate then
3977                   Formal := First_Formal (Ent);
3978                   while Present (Formal) loop
3979                      Set_Mechanism_Value (Formal, Arg_Mechanism);
3980                      Next_Formal (Formal);
3981                   end loop;
3982
3983                --  Case of list of mechanism associations given
3984
3985                else
3986                   if Null_Record_Present (Arg_Mechanism) then
3987                      Error_Pragma_Arg
3988                        ("inappropriate form for Mechanism parameter",
3989                         Arg_Mechanism);
3990                   end if;
3991
3992                   --  Deal with positional ones first
3993
3994                   Formal := First_Formal (Ent);
3995
3996                   if Present (Expressions (Arg_Mechanism)) then
3997                      Mname := First (Expressions (Arg_Mechanism));
3998                      while Present (Mname) loop
3999                         if No (Formal) then
4000                            Error_Pragma_Arg
4001                              ("too many mechanism associations", Mname);
4002                         end if;
4003
4004                         Set_Mechanism_Value (Formal, Mname);
4005                         Next_Formal (Formal);
4006                         Next (Mname);
4007                      end loop;
4008                   end if;
4009
4010                   --  Deal with named entries
4011
4012                   if Present (Component_Associations (Arg_Mechanism)) then
4013                      Massoc := First (Component_Associations (Arg_Mechanism));
4014                      while Present (Massoc) loop
4015                         Choice := First (Choices (Massoc));
4016
4017                         if Nkind (Choice) /= N_Identifier
4018                           or else Present (Next (Choice))
4019                         then
4020                            Error_Pragma_Arg
4021                              ("incorrect form for mechanism association",
4022                               Massoc);
4023                         end if;
4024
4025                         Formal := First_Formal (Ent);
4026                         loop
4027                            if No (Formal) then
4028                               Error_Pragma_Arg
4029                                 ("parameter name & not present", Choice);
4030                            end if;
4031
4032                            if Chars (Choice) = Chars (Formal) then
4033                               Set_Mechanism_Value
4034                                 (Formal, Expression (Massoc));
4035
4036                               --  Set entity on identifier (needed by ASIS)
4037
4038                               Set_Entity (Choice, Formal);
4039
4040                               exit;
4041                            end if;
4042
4043                            Next_Formal (Formal);
4044                         end loop;
4045
4046                         Next (Massoc);
4047                      end loop;
4048                   end if;
4049                end if;
4050             end;
4051          end if;
4052
4053          --  Process First_Optional_Parameter argument if present. We have
4054          --  already checked that this is only allowed for the Import case.
4055
4056          if Present (Arg_First_Optional_Parameter) then
4057             if Nkind (Arg_First_Optional_Parameter) /= N_Identifier then
4058                Error_Pragma_Arg
4059                  ("first optional parameter must be formal parameter name",
4060                   Arg_First_Optional_Parameter);
4061             end if;
4062
4063             Formal := First_Formal (Ent);
4064             loop
4065                if No (Formal) then
4066                   Error_Pragma_Arg
4067                     ("specified formal parameter& not found",
4068                      Arg_First_Optional_Parameter);
4069                end if;
4070
4071                exit when Chars (Formal) =
4072                          Chars (Arg_First_Optional_Parameter);
4073
4074                Next_Formal (Formal);
4075             end loop;
4076
4077             Set_First_Optional_Parameter (Ent, Formal);
4078
4079             --  Check specified and all remaining formals have right form
4080
4081             while Present (Formal) loop
4082                if Ekind (Formal) /= E_In_Parameter then
4083                   Error_Msg_NE
4084                     ("optional formal& is not of mode in!",
4085                      Arg_First_Optional_Parameter, Formal);
4086
4087                else
4088                   Dval := Default_Value (Formal);
4089
4090                   if No (Dval) then
4091                      Error_Msg_NE
4092                        ("optional formal& does not have default value!",
4093                         Arg_First_Optional_Parameter, Formal);
4094
4095                   elsif Compile_Time_Known_Value_Or_Aggr (Dval) then
4096                      null;
4097
4098                   else
4099                      Error_Msg_FE
4100                        ("default value for optional formal& is non-static!",
4101                         Arg_First_Optional_Parameter, Formal);
4102                   end if;
4103                end if;
4104
4105                Set_Is_Optional_Parameter (Formal);
4106                Next_Formal (Formal);
4107             end loop;
4108          end if;
4109       end Process_Extended_Import_Export_Subprogram_Pragma;
4110
4111       --------------------------
4112       -- Process_Generic_List --
4113       --------------------------
4114
4115       procedure Process_Generic_List is
4116          Arg : Node_Id;
4117          Exp : Node_Id;
4118
4119       begin
4120          Check_No_Identifiers;
4121          Check_At_Least_N_Arguments (1);
4122
4123          Arg := Arg1;
4124          while Present (Arg) loop
4125             Exp := Get_Pragma_Arg (Arg);
4126             Analyze (Exp);
4127
4128             if not Is_Entity_Name (Exp)
4129               or else
4130                 (not Is_Generic_Instance (Entity (Exp))
4131                   and then
4132                  not Is_Generic_Unit (Entity (Exp)))
4133             then
4134                Error_Pragma_Arg
4135                  ("pragma% argument must be name of generic unit/instance",
4136                   Arg);
4137             end if;
4138
4139             Next (Arg);
4140          end loop;
4141       end Process_Generic_List;
4142
4143       ------------------------------------
4144       -- Process_Import_Predefined_Type --
4145       ------------------------------------
4146
4147       procedure Process_Import_Predefined_Type is
4148          Loc  : constant Source_Ptr := Sloc (N);
4149          Elmt : Elmt_Id;
4150          Ftyp : Node_Id := Empty;
4151          Decl : Node_Id;
4152          Def  : Node_Id;
4153          Nam  : Name_Id;
4154
4155       begin
4156          String_To_Name_Buffer (Strval (Expression (Arg3)));
4157          Nam := Name_Find;
4158
4159          Elmt := First_Elmt (Predefined_Float_Types);
4160          while Present (Elmt) and then Chars (Node (Elmt)) /= Nam loop
4161             Next_Elmt (Elmt);
4162          end loop;
4163
4164          Ftyp := Node (Elmt);
4165
4166          if Present (Ftyp) then
4167
4168             --  Don't build a derived type declaration, because predefined C
4169             --  types have no declaration anywhere, so cannot really be named.
4170             --  Instead build a full type declaration, starting with an
4171             --  appropriate type definition is built
4172
4173             if Is_Floating_Point_Type (Ftyp) then
4174                Def := Make_Floating_Point_Definition (Loc,
4175                  Make_Integer_Literal (Loc, Digits_Value (Ftyp)),
4176                  Make_Real_Range_Specification (Loc,
4177                    Make_Real_Literal (Loc, Realval (Type_Low_Bound (Ftyp))),
4178                    Make_Real_Literal (Loc, Realval (Type_High_Bound (Ftyp)))));
4179
4180             --  Should never have a predefined type we cannot handle
4181
4182             else
4183                raise Program_Error;
4184             end if;
4185
4186             --  Build and insert a Full_Type_Declaration, which will be
4187             --  analyzed as soon as this list entry has been analyzed.
4188
4189             Decl := Make_Full_Type_Declaration (Loc,
4190               Make_Defining_Identifier (Loc, Chars (Expression (Arg2))),
4191               Type_Definition => Def);
4192
4193             Insert_After (N, Decl);
4194             Mark_Rewrite_Insertion (Decl);
4195
4196          else
4197             Error_Pragma_Arg ("no matching type found for pragma%",
4198             Arg2);
4199          end if;
4200       end Process_Import_Predefined_Type;
4201
4202       ---------------------------------
4203       -- Process_Import_Or_Interface --
4204       ---------------------------------
4205
4206       procedure Process_Import_Or_Interface is
4207          C      : Convention_Id;
4208          Def_Id : Entity_Id;
4209          Hom_Id : Entity_Id;
4210
4211       begin
4212          Process_Convention (C, Def_Id);
4213          Kill_Size_Check_Code (Def_Id);
4214          Note_Possible_Modification (Get_Pragma_Arg (Arg2), Sure => False);
4215
4216          if Ekind_In (Def_Id, E_Variable, E_Constant) then
4217
4218             --  We do not permit Import to apply to a renaming declaration
4219
4220             if Present (Renamed_Object (Def_Id)) then
4221                Error_Pragma_Arg
4222                  ("pragma% not allowed for object renaming", Arg2);
4223
4224             --  User initialization is not allowed for imported object, but
4225             --  the object declaration may contain a default initialization,
4226             --  that will be discarded. Note that an explicit initialization
4227             --  only counts if it comes from source, otherwise it is simply
4228             --  the code generator making an implicit initialization explicit.
4229
4230             elsif Present (Expression (Parent (Def_Id)))
4231               and then Comes_From_Source (Expression (Parent (Def_Id)))
4232             then
4233                Error_Msg_Sloc := Sloc (Def_Id);
4234                Error_Pragma_Arg
4235                  ("no initialization allowed for declaration of& #",
4236                   "\imported entities cannot be initialized (RM B.1(24))",
4237                   Arg2);
4238
4239             else
4240                Set_Imported (Def_Id);
4241                Process_Interface_Name (Def_Id, Arg3, Arg4);
4242
4243                --  Note that we do not set Is_Public here. That's because we
4244                --  only want to set it if there is no address clause, and we
4245                --  don't know that yet, so we delay that processing till
4246                --  freeze time.
4247
4248                --  pragma Import completes deferred constants
4249
4250                if Ekind (Def_Id) = E_Constant then
4251                   Set_Has_Completion (Def_Id);
4252                end if;
4253
4254                --  It is not possible to import a constant of an unconstrained
4255                --  array type (e.g. string) because there is no simple way to
4256                --  write a meaningful subtype for it.
4257
4258                if Is_Array_Type (Etype (Def_Id))
4259                  and then not Is_Constrained (Etype (Def_Id))
4260                then
4261                   Error_Msg_NE
4262                     ("imported constant& must have a constrained subtype",
4263                       N, Def_Id);
4264                end if;
4265             end if;
4266
4267          elsif Is_Subprogram (Def_Id)
4268            or else Is_Generic_Subprogram (Def_Id)
4269          then
4270             --  If the name is overloaded, pragma applies to all of the denoted
4271             --  entities in the same declarative part.
4272
4273             Hom_Id := Def_Id;
4274             while Present (Hom_Id) loop
4275                Def_Id := Get_Base_Subprogram (Hom_Id);
4276
4277                --  Ignore inherited subprograms because the pragma will apply
4278                --  to the parent operation, which is the one called.
4279
4280                if Is_Overloadable (Def_Id)
4281                  and then Present (Alias (Def_Id))
4282                then
4283                   null;
4284
4285                --  If it is not a subprogram, it must be in an outer scope and
4286                --  pragma does not apply.
4287
4288                elsif not Is_Subprogram (Def_Id)
4289                  and then not Is_Generic_Subprogram (Def_Id)
4290                then
4291                   null;
4292
4293                --  The pragma does not apply to primitives of interfaces
4294
4295                elsif Is_Dispatching_Operation (Def_Id)
4296                  and then Present (Find_Dispatching_Type (Def_Id))
4297                  and then Is_Interface (Find_Dispatching_Type (Def_Id))
4298                then
4299                   null;
4300
4301                --  Verify that the homonym is in the same declarative part (not
4302                --  just the same scope).
4303
4304                elsif Parent (Unit_Declaration_Node (Def_Id)) /= Parent (N)
4305                  and then Nkind (Parent (N)) /= N_Compilation_Unit_Aux
4306                then
4307                   exit;
4308
4309                else
4310                   Set_Imported (Def_Id);
4311
4312                   --  Reject an Import applied to an abstract subprogram
4313
4314                   if Is_Subprogram (Def_Id)
4315                     and then Is_Abstract_Subprogram (Def_Id)
4316                   then
4317                      Error_Msg_Sloc := Sloc (Def_Id);
4318                      Error_Msg_NE
4319                        ("cannot import abstract subprogram& declared#",
4320                         Arg2, Def_Id);
4321                   end if;
4322
4323                   --  Special processing for Convention_Intrinsic
4324
4325                   if C = Convention_Intrinsic then
4326
4327                      --  Link_Name argument not allowed for intrinsic
4328
4329                      Check_No_Link_Name;
4330
4331                      Set_Is_Intrinsic_Subprogram (Def_Id);
4332
4333                      --  If no external name is present, then check that this
4334                      --  is a valid intrinsic subprogram. If an external name
4335                      --  is present, then this is handled by the back end.
4336
4337                      if No (Arg3) then
4338                         Check_Intrinsic_Subprogram
4339                           (Def_Id, Get_Pragma_Arg (Arg2));
4340                      end if;
4341                   end if;
4342
4343                   --  All interfaced procedures need an external symbol created
4344                   --  for them since they are always referenced from another
4345                   --  object file.
4346
4347                   Set_Is_Public (Def_Id);
4348
4349                   --  Verify that the subprogram does not have a completion
4350                   --  through a renaming declaration. For other completions the
4351                   --  pragma appears as a too late representation.
4352
4353                   declare
4354                      Decl : constant Node_Id := Unit_Declaration_Node (Def_Id);
4355
4356                   begin
4357                      if Present (Decl)
4358                        and then Nkind (Decl) = N_Subprogram_Declaration
4359                        and then Present (Corresponding_Body (Decl))
4360                        and then Nkind (Unit_Declaration_Node
4361                                         (Corresponding_Body (Decl))) =
4362                                              N_Subprogram_Renaming_Declaration
4363                      then
4364                         Error_Msg_Sloc := Sloc (Def_Id);
4365                         Error_Msg_NE
4366                           ("cannot import&, renaming already provided for " &
4367                            "declaration #", N, Def_Id);
4368                      end if;
4369                   end;
4370
4371                   Set_Has_Completion (Def_Id);
4372                   Process_Interface_Name (Def_Id, Arg3, Arg4);
4373                end if;
4374
4375                if Is_Compilation_Unit (Hom_Id) then
4376
4377                   --  Its possible homonyms are not affected by the pragma.
4378                   --  Such homonyms might be present in the context of other
4379                   --  units being compiled.
4380
4381                   exit;
4382
4383                else
4384                   Hom_Id := Homonym (Hom_Id);
4385                end if;
4386             end loop;
4387
4388          --  When the convention is Java or CIL, we also allow Import to be
4389          --  given for packages, generic packages, exceptions, record
4390          --  components, and access to subprograms.
4391
4392          elsif (C = Convention_Java or else C = Convention_CIL)
4393            and then
4394              (Is_Package_Or_Generic_Package (Def_Id)
4395                or else Ekind (Def_Id) = E_Exception
4396                or else Ekind (Def_Id) = E_Access_Subprogram_Type
4397                or else Nkind (Parent (Def_Id)) = N_Component_Declaration)
4398          then
4399             Set_Imported (Def_Id);
4400             Set_Is_Public (Def_Id);
4401             Process_Interface_Name (Def_Id, Arg3, Arg4);
4402
4403          --  Import a CPP class
4404
4405          elsif Is_Record_Type (Def_Id)
4406            and then C = Convention_CPP
4407          then
4408             --  Types treated as CPP classes must be declared limited (note:
4409             --  this used to be a warning but there is no real benefit to it
4410             --  since we did effectively intend to treat the type as limited
4411             --  anyway).
4412
4413             if not Is_Limited_Type (Def_Id) then
4414                Error_Msg_N
4415                  ("imported 'C'P'P type must be limited",
4416                   Get_Pragma_Arg (Arg2));
4417             end if;
4418
4419             Set_Is_CPP_Class (Def_Id);
4420
4421             --  Imported CPP types must not have discriminants (because C++
4422             --  classes do not have discriminants).
4423
4424             if Has_Discriminants (Def_Id) then
4425                Error_Msg_N
4426                  ("imported 'C'P'P type cannot have discriminants",
4427                   First (Discriminant_Specifications
4428                           (Declaration_Node (Def_Id))));
4429             end if;
4430
4431             --  Components of imported CPP types must not have default
4432             --  expressions because the constructor (if any) is on the
4433             --  C++ side.
4434
4435             declare
4436                Tdef  : constant Node_Id :=
4437                          Type_Definition (Declaration_Node (Def_Id));
4438                Clist : Node_Id;
4439                Comp  : Node_Id;
4440
4441             begin
4442                if Nkind (Tdef) = N_Record_Definition then
4443                   Clist := Component_List (Tdef);
4444
4445                else
4446                   pragma Assert (Nkind (Tdef) = N_Derived_Type_Definition);
4447                   Clist := Component_List (Record_Extension_Part (Tdef));
4448                end if;
4449
4450                if Present (Clist) then
4451                   Comp := First (Component_Items (Clist));
4452                   while Present (Comp) loop
4453                      if Present (Expression (Comp)) then
4454                         Error_Msg_N
4455                           ("component of imported 'C'P'P type cannot have" &
4456                            " default expression", Expression (Comp));
4457                      end if;
4458
4459                      Next (Comp);
4460                   end loop;
4461                end if;
4462             end;
4463
4464          elsif Nkind (Parent (Def_Id)) = N_Incomplete_Type_Declaration then
4465             Check_No_Link_Name;
4466             Check_Arg_Count (3);
4467             Check_Arg_Is_Static_Expression (Arg3, Standard_String);
4468
4469             Process_Import_Predefined_Type;
4470
4471          else
4472             Error_Pragma_Arg
4473               ("second argument of pragma% must be object, subprogram" &
4474                " or incomplete type",
4475                Arg2);
4476          end if;
4477
4478          --  If this pragma applies to a compilation unit, then the unit, which
4479          --  is a subprogram, does not require (or allow) a body. We also do
4480          --  not need to elaborate imported procedures.
4481
4482          if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
4483             declare
4484                Cunit : constant Node_Id := Parent (Parent (N));
4485             begin
4486                Set_Body_Required (Cunit, False);
4487             end;
4488          end if;
4489       end Process_Import_Or_Interface;
4490
4491       --------------------
4492       -- Process_Inline --
4493       --------------------
4494
4495       procedure Process_Inline (Active : Boolean) is
4496          Assoc     : Node_Id;
4497          Decl      : Node_Id;
4498          Subp_Id   : Node_Id;
4499          Subp      : Entity_Id;
4500          Applies   : Boolean;
4501
4502          Effective : Boolean := False;
4503          --  Set True if inline has some effect, i.e. if there is at least one
4504          --  subprogram set as inlined as a result of the use of the pragma.
4505
4506          procedure Make_Inline (Subp : Entity_Id);
4507          --  Subp is the defining unit name of the subprogram declaration. Set
4508          --  the flag, as well as the flag in the corresponding body, if there
4509          --  is one present.
4510
4511          procedure Set_Inline_Flags (Subp : Entity_Id);
4512          --  Sets Is_Inlined and Has_Pragma_Inline flags for Subp and also
4513          --  Has_Pragma_Inline_Always for the Inline_Always case.
4514
4515          function Inlining_Not_Possible (Subp : Entity_Id) return Boolean;
4516          --  Returns True if it can be determined at this stage that inlining
4517          --  is not possible, for example if the body is available and contains
4518          --  exception handlers, we prevent inlining, since otherwise we can
4519          --  get undefined symbols at link time. This function also emits a
4520          --  warning if front-end inlining is enabled and the pragma appears
4521          --  too late.
4522          --
4523          --  ??? is business with link symbols still valid, or does it relate
4524          --  to front end ZCX which is being phased out ???
4525
4526          ---------------------------
4527          -- Inlining_Not_Possible --
4528          ---------------------------
4529
4530          function Inlining_Not_Possible (Subp : Entity_Id) return Boolean is
4531             Decl  : constant Node_Id := Unit_Declaration_Node (Subp);
4532             Stats : Node_Id;
4533
4534          begin
4535             if Nkind (Decl) = N_Subprogram_Body then
4536                Stats := Handled_Statement_Sequence (Decl);
4537                return Present (Exception_Handlers (Stats))
4538                  or else Present (At_End_Proc (Stats));
4539
4540             elsif Nkind (Decl) = N_Subprogram_Declaration
4541               and then Present (Corresponding_Body (Decl))
4542             then
4543                if Front_End_Inlining
4544                  and then Analyzed (Corresponding_Body (Decl))
4545                then
4546                   Error_Msg_N ("pragma appears too late, ignored?", N);
4547                   return True;
4548
4549                --  If the subprogram is a renaming as body, the body is just a
4550                --  call to the renamed subprogram, and inlining is trivially
4551                --  possible.
4552
4553                elsif
4554                  Nkind (Unit_Declaration_Node (Corresponding_Body (Decl))) =
4555                                              N_Subprogram_Renaming_Declaration
4556                then
4557                   return False;
4558
4559                else
4560                   Stats :=
4561                     Handled_Statement_Sequence
4562                         (Unit_Declaration_Node (Corresponding_Body (Decl)));
4563
4564                   return
4565                     Present (Exception_Handlers (Stats))
4566                       or else Present (At_End_Proc (Stats));
4567                end if;
4568
4569             else
4570                --  If body is not available, assume the best, the check is
4571                --  performed again when compiling enclosing package bodies.
4572
4573                return False;
4574             end if;
4575          end Inlining_Not_Possible;
4576
4577          -----------------
4578          -- Make_Inline --
4579          -----------------
4580
4581          procedure Make_Inline (Subp : Entity_Id) is
4582             Kind       : constant Entity_Kind := Ekind (Subp);
4583             Inner_Subp : Entity_Id   := Subp;
4584
4585          begin
4586             --  Ignore if bad type, avoid cascaded error
4587
4588             if Etype (Subp) = Any_Type then
4589                Applies := True;
4590                return;
4591
4592             --  Ignore if all inlining is suppressed
4593
4594             elsif Suppress_All_Inlining then
4595                Applies := True;
4596                return;
4597
4598             --  If inlining is not possible, for now do not treat as an error
4599
4600             elsif Inlining_Not_Possible (Subp) then
4601                Applies := True;
4602                return;
4603
4604             --  Here we have a candidate for inlining, but we must exclude
4605             --  derived operations. Otherwise we would end up trying to inline
4606             --  a phantom declaration, and the result would be to drag in a
4607             --  body which has no direct inlining associated with it. That
4608             --  would not only be inefficient but would also result in the
4609             --  backend doing cross-unit inlining in cases where it was
4610             --  definitely inappropriate to do so.
4611
4612             --  However, a simple Comes_From_Source test is insufficient, since
4613             --  we do want to allow inlining of generic instances which also do
4614             --  not come from source. We also need to recognize specs generated
4615             --  by the front-end for bodies that carry the pragma. Finally,
4616             --  predefined operators do not come from source but are not
4617             --  inlineable either.
4618
4619             elsif Is_Generic_Instance (Subp)
4620               or else Nkind (Parent (Parent (Subp))) = N_Subprogram_Declaration
4621             then
4622                null;
4623
4624             elsif not Comes_From_Source (Subp)
4625               and then Scope (Subp) /= Standard_Standard
4626             then
4627                Applies := True;
4628                return;
4629             end if;
4630
4631             --  The referenced entity must either be the enclosing entity, or
4632             --  an entity declared within the current open scope.
4633
4634             if Present (Scope (Subp))
4635               and then Scope (Subp) /= Current_Scope
4636               and then Subp /= Current_Scope
4637             then
4638                Error_Pragma_Arg
4639                  ("argument of% must be entity in current scope", Assoc);
4640                return;
4641             end if;
4642
4643             --  Processing for procedure, operator or function. If subprogram
4644             --  is aliased (as for an instance) indicate that the renamed
4645             --  entity (if declared in the same unit) is inlined.
4646
4647             if Is_Subprogram (Subp) then
4648                Inner_Subp := Ultimate_Alias (Inner_Subp);
4649
4650                if In_Same_Source_Unit (Subp, Inner_Subp) then
4651                   Set_Inline_Flags (Inner_Subp);
4652
4653                   Decl := Parent (Parent (Inner_Subp));
4654
4655                   if Nkind (Decl) = N_Subprogram_Declaration
4656                     and then Present (Corresponding_Body (Decl))
4657                   then
4658                      Set_Inline_Flags (Corresponding_Body (Decl));
4659
4660                   elsif Is_Generic_Instance (Subp) then
4661
4662                      --  Indicate that the body needs to be created for
4663                      --  inlining subsequent calls. The instantiation node
4664                      --  follows the declaration of the wrapper package
4665                      --  created for it.
4666
4667                      if Scope (Subp) /= Standard_Standard
4668                        and then
4669                          Need_Subprogram_Instance_Body
4670                           (Next (Unit_Declaration_Node (Scope (Alias (Subp)))),
4671                               Subp)
4672                      then
4673                         null;
4674                      end if;
4675                   end if;
4676                end if;
4677
4678                Applies := True;
4679
4680             --  For a generic subprogram set flag as well, for use at the point
4681             --  of instantiation, to determine whether the body should be
4682             --  generated.
4683
4684             elsif Is_Generic_Subprogram (Subp) then
4685                Set_Inline_Flags (Subp);
4686                Applies := True;
4687
4688             --  Literals are by definition inlined
4689
4690             elsif Kind = E_Enumeration_Literal then
4691                null;
4692
4693             --  Anything else is an error
4694
4695             else
4696                Error_Pragma_Arg
4697                  ("expect subprogram name for pragma%", Assoc);
4698             end if;
4699          end Make_Inline;
4700
4701          ----------------------
4702          -- Set_Inline_Flags --
4703          ----------------------
4704
4705          procedure Set_Inline_Flags (Subp : Entity_Id) is
4706          begin
4707             if Active then
4708                Set_Is_Inlined (Subp);
4709             end if;
4710
4711             if not Has_Pragma_Inline (Subp) then
4712                Set_Has_Pragma_Inline (Subp);
4713                Effective := True;
4714             end if;
4715
4716             if Prag_Id = Pragma_Inline_Always then
4717                Set_Has_Pragma_Inline_Always (Subp);
4718             end if;
4719          end Set_Inline_Flags;
4720
4721       --  Start of processing for Process_Inline
4722
4723       begin
4724          Check_No_Identifiers;
4725          Check_At_Least_N_Arguments (1);
4726
4727          if Active then
4728             Inline_Processing_Required := True;
4729          end if;
4730
4731          Assoc := Arg1;
4732          while Present (Assoc) loop
4733             Subp_Id := Get_Pragma_Arg (Assoc);
4734             Analyze (Subp_Id);
4735             Applies := False;
4736
4737             if Is_Entity_Name (Subp_Id) then
4738                Subp := Entity (Subp_Id);
4739
4740                if Subp = Any_Id then
4741
4742                   --  If previous error, avoid cascaded errors
4743
4744                   Applies := True;
4745                   Effective := True;
4746
4747                else
4748                   Make_Inline (Subp);
4749
4750                   --  For the pragma case, climb homonym chain. This is
4751                   --  what implements allowing the pragma in the renaming
4752                   --  case, with the result applying to the ancestors.
4753
4754                   if not From_Aspect_Specification (N) then
4755                      while Present (Homonym (Subp))
4756                        and then Scope (Homonym (Subp)) = Current_Scope
4757                      loop
4758                         Make_Inline (Homonym (Subp));
4759                         Subp := Homonym (Subp);
4760                      end loop;
4761                   end if;
4762                end if;
4763             end if;
4764
4765             if not Applies then
4766                Error_Pragma_Arg
4767                  ("inappropriate argument for pragma%", Assoc);
4768
4769             elsif not Effective
4770               and then Warn_On_Redundant_Constructs
4771               and then not Suppress_All_Inlining
4772             then
4773                if Inlining_Not_Possible (Subp) then
4774                   Error_Msg_NE
4775                     ("pragma Inline for& is ignored?", N, Entity (Subp_Id));
4776                else
4777                   Error_Msg_NE
4778                     ("pragma Inline for& is redundant?", N, Entity (Subp_Id));
4779                end if;
4780             end if;
4781
4782             Next (Assoc);
4783          end loop;
4784       end Process_Inline;
4785
4786       ----------------------------
4787       -- Process_Interface_Name --
4788       ----------------------------
4789
4790       procedure Process_Interface_Name
4791         (Subprogram_Def : Entity_Id;
4792          Ext_Arg        : Node_Id;
4793          Link_Arg       : Node_Id)
4794       is
4795          Ext_Nam    : Node_Id;
4796          Link_Nam   : Node_Id;
4797          String_Val : String_Id;
4798
4799          procedure Check_Form_Of_Interface_Name
4800            (SN            : Node_Id;
4801             Ext_Name_Case : Boolean);
4802          --  SN is a string literal node for an interface name. This routine
4803          --  performs some minimal checks that the name is reasonable. In
4804          --  particular that no spaces or other obviously incorrect characters
4805          --  appear. This is only a warning, since any characters are allowed.
4806          --  Ext_Name_Case is True for an External_Name, False for a Link_Name.
4807
4808          ----------------------------------
4809          -- Check_Form_Of_Interface_Name --
4810          ----------------------------------
4811
4812          procedure Check_Form_Of_Interface_Name
4813            (SN            : Node_Id;
4814             Ext_Name_Case : Boolean)
4815          is
4816             S  : constant String_Id := Strval (Expr_Value_S (SN));
4817             SL : constant Nat       := String_Length (S);
4818             C  : Char_Code;
4819
4820          begin
4821             if SL = 0 then
4822                Error_Msg_N ("interface name cannot be null string", SN);
4823             end if;
4824
4825             for J in 1 .. SL loop
4826                C := Get_String_Char (S, J);
4827
4828                --  Look for dubious character and issue unconditional warning.
4829                --  Definitely dubious if not in character range.
4830
4831                if not In_Character_Range (C)
4832
4833                   --  For all cases except CLI target,
4834                   --  commas, spaces and slashes are dubious (in CLI, we use
4835                   --  commas and backslashes in external names to specify
4836                   --  assembly version and public key, while slashes and spaces
4837                   --  can be used in names to mark nested classes and
4838                   --  valuetypes).
4839
4840                   or else ((not Ext_Name_Case or else VM_Target /= CLI_Target)
4841                              and then (Get_Character (C) = ','
4842                                          or else
4843                                        Get_Character (C) = '\'))
4844                  or else (VM_Target /= CLI_Target
4845                             and then (Get_Character (C) = ' '
4846                                         or else
4847                                       Get_Character (C) = '/'))
4848                then
4849                   Error_Msg
4850                     ("?interface name contains illegal character",
4851                      Sloc (SN) + Source_Ptr (J));
4852                end if;
4853             end loop;
4854          end Check_Form_Of_Interface_Name;
4855
4856       --  Start of processing for Process_Interface_Name
4857
4858       begin
4859          if No (Link_Arg) then
4860             if No (Ext_Arg) then
4861                if VM_Target = CLI_Target
4862                  and then Ekind (Subprogram_Def) = E_Package
4863                  and then Nkind (Parent (Subprogram_Def)) =
4864                                                  N_Package_Specification
4865                  and then Present (Generic_Parent (Parent (Subprogram_Def)))
4866                then
4867                   Set_Interface_Name
4868                      (Subprogram_Def,
4869                       Interface_Name
4870                         (Generic_Parent (Parent (Subprogram_Def))));
4871                end if;
4872
4873                return;
4874
4875             elsif Chars (Ext_Arg) = Name_Link_Name then
4876                Ext_Nam  := Empty;
4877                Link_Nam := Expression (Ext_Arg);
4878
4879             else
4880                Check_Optional_Identifier (Ext_Arg, Name_External_Name);
4881                Ext_Nam  := Expression (Ext_Arg);
4882                Link_Nam := Empty;
4883             end if;
4884
4885          else
4886             Check_Optional_Identifier (Ext_Arg,  Name_External_Name);
4887             Check_Optional_Identifier (Link_Arg, Name_Link_Name);
4888             Ext_Nam  := Expression (Ext_Arg);
4889             Link_Nam := Expression (Link_Arg);
4890          end if;
4891
4892          --  Check expressions for external name and link name are static
4893
4894          if Present (Ext_Nam) then
4895             Check_Arg_Is_Static_Expression (Ext_Nam, Standard_String);
4896             Check_Form_Of_Interface_Name (Ext_Nam, Ext_Name_Case => True);
4897
4898             --  Verify that external name is not the name of a local entity,
4899             --  which would hide the imported one and could lead to run-time
4900             --  surprises. The problem can only arise for entities declared in
4901             --  a package body (otherwise the external name is fully qualified
4902             --  and will not conflict).
4903
4904             declare
4905                Nam : Name_Id;
4906                E   : Entity_Id;
4907                Par : Node_Id;
4908
4909             begin
4910                if Prag_Id = Pragma_Import then
4911                   String_To_Name_Buffer (Strval (Expr_Value_S (Ext_Nam)));
4912                   Nam := Name_Find;
4913                   E   := Entity_Id (Get_Name_Table_Info (Nam));
4914
4915                   if Nam /= Chars (Subprogram_Def)
4916                     and then Present (E)
4917                     and then not Is_Overloadable (E)
4918                     and then Is_Immediately_Visible (E)
4919                     and then not Is_Imported (E)
4920                     and then Ekind (Scope (E)) = E_Package
4921                   then
4922                      Par := Parent (E);
4923                      while Present (Par) loop
4924                         if Nkind (Par) = N_Package_Body then
4925                            Error_Msg_Sloc := Sloc (E);
4926                            Error_Msg_NE
4927                              ("imported entity is hidden by & declared#",
4928                               Ext_Arg, E);
4929                            exit;
4930                         end if;
4931
4932                         Par := Parent (Par);
4933                      end loop;
4934                   end if;
4935                end if;
4936             end;
4937          end if;
4938
4939          if Present (Link_Nam) then
4940             Check_Arg_Is_Static_Expression (Link_Nam, Standard_String);
4941             Check_Form_Of_Interface_Name (Link_Nam, Ext_Name_Case => False);
4942          end if;
4943
4944          --  If there is no link name, just set the external name
4945
4946          if No (Link_Nam) then
4947             Link_Nam := Adjust_External_Name_Case (Expr_Value_S (Ext_Nam));
4948
4949          --  For the Link_Name case, the given literal is preceded by an
4950          --  asterisk, which indicates to GCC that the given name should be
4951          --  taken literally, and in particular that no prepending of
4952          --  underlines should occur, even in systems where this is the
4953          --  normal default.
4954
4955          else
4956             Start_String;
4957
4958             if VM_Target = No_VM then
4959                Store_String_Char (Get_Char_Code ('*'));
4960             end if;
4961
4962             String_Val := Strval (Expr_Value_S (Link_Nam));
4963             Store_String_Chars (String_Val);
4964             Link_Nam :=
4965               Make_String_Literal (Sloc (Link_Nam),
4966                 Strval => End_String);
4967          end if;
4968
4969          --  Set the interface name. If the entity is a generic instance, use
4970          --  its alias, which is the callable entity.
4971
4972          if Is_Generic_Instance (Subprogram_Def) then
4973             Set_Encoded_Interface_Name
4974               (Alias (Get_Base_Subprogram (Subprogram_Def)), Link_Nam);
4975          else
4976             Set_Encoded_Interface_Name
4977               (Get_Base_Subprogram (Subprogram_Def), Link_Nam);
4978          end if;
4979
4980          --  We allow duplicated export names in CIL/Java, as they are always
4981          --  enclosed in a namespace that differentiates them, and overloaded
4982          --  entities are supported by the VM.
4983
4984          if Convention (Subprogram_Def) /= Convention_CIL
4985               and then
4986             Convention (Subprogram_Def) /= Convention_Java
4987          then
4988             Check_Duplicated_Export_Name (Link_Nam);
4989          end if;
4990       end Process_Interface_Name;
4991
4992       -----------------------------------------
4993       -- Process_Interrupt_Or_Attach_Handler --
4994       -----------------------------------------
4995
4996       procedure Process_Interrupt_Or_Attach_Handler is
4997          Arg1_X       : constant Node_Id   := Get_Pragma_Arg (Arg1);
4998          Handler_Proc : constant Entity_Id := Entity (Arg1_X);
4999          Proc_Scope   : constant Entity_Id := Scope (Handler_Proc);
5000
5001       begin
5002          Set_Is_Interrupt_Handler (Handler_Proc);
5003
5004          --  If the pragma is not associated with a handler procedure within a
5005          --  protected type, then it must be for a nonprotected procedure for
5006          --  the AAMP target, in which case we don't associate a representation
5007          --  item with the procedure's scope.
5008
5009          if Ekind (Proc_Scope) = E_Protected_Type then
5010             if Prag_Id = Pragma_Interrupt_Handler
5011                  or else
5012                Prag_Id = Pragma_Attach_Handler
5013             then
5014                Record_Rep_Item (Proc_Scope, N);
5015             end if;
5016          end if;
5017       end Process_Interrupt_Or_Attach_Handler;
5018
5019       --------------------------------------------------
5020       -- Process_Restrictions_Or_Restriction_Warnings --
5021       --------------------------------------------------
5022
5023       --  Note: some of the simple identifier cases were handled in par-prag,
5024       --  but it is harmless (and more straightforward) to simply handle all
5025       --  cases here, even if it means we repeat a bit of work in some cases.
5026
5027       procedure Process_Restrictions_Or_Restriction_Warnings
5028         (Warn : Boolean)
5029       is
5030          Arg   : Node_Id;
5031          R_Id  : Restriction_Id;
5032          Id    : Name_Id;
5033          Expr  : Node_Id;
5034          Val   : Uint;
5035
5036          procedure Check_Unit_Name (N : Node_Id);
5037          --  Checks unit name parameter for No_Dependence. Returns if it has
5038          --  an appropriate form, otherwise raises pragma argument error.
5039
5040          ---------------------
5041          -- Check_Unit_Name --
5042          ---------------------
5043
5044          procedure Check_Unit_Name (N : Node_Id) is
5045          begin
5046             if Nkind (N) = N_Selected_Component then
5047                Check_Unit_Name (Prefix (N));
5048                Check_Unit_Name (Selector_Name (N));
5049
5050             elsif Nkind (N) = N_Identifier then
5051                return;
5052
5053             else
5054                Error_Pragma_Arg
5055                  ("wrong form for unit name for No_Dependence", N);
5056             end if;
5057          end Check_Unit_Name;
5058
5059       --  Start of processing for Process_Restrictions_Or_Restriction_Warnings
5060
5061       begin
5062          --  Ignore all Restrictions pragma in CodePeer mode
5063
5064          if CodePeer_Mode then
5065             return;
5066          end if;
5067
5068          Check_Ada_83_Warning;
5069          Check_At_Least_N_Arguments (1);
5070          Check_Valid_Configuration_Pragma;
5071
5072          Arg := Arg1;
5073          while Present (Arg) loop
5074             Id := Chars (Arg);
5075             Expr := Get_Pragma_Arg (Arg);
5076
5077             --  Case of no restriction identifier present
5078
5079             if Id = No_Name then
5080                if Nkind (Expr) /= N_Identifier then
5081                   Error_Pragma_Arg
5082                     ("invalid form for restriction", Arg);
5083                end if;
5084
5085                R_Id :=
5086                  Get_Restriction_Id
5087                    (Process_Restriction_Synonyms (Expr));
5088
5089                if R_Id not in All_Boolean_Restrictions then
5090                   Error_Msg_Name_1 := Pname;
5091                   Error_Msg_N
5092                     ("invalid restriction identifier&", Get_Pragma_Arg (Arg));
5093
5094                   --  Check for possible misspelling
5095
5096                   for J in Restriction_Id loop
5097                      declare
5098                         Rnm : constant String := Restriction_Id'Image (J);
5099
5100                      begin
5101                         Name_Buffer (1 .. Rnm'Length) := Rnm;
5102                         Name_Len := Rnm'Length;
5103                         Set_Casing (All_Lower_Case);
5104
5105                         if Is_Bad_Spelling_Of (Chars (Expr), Name_Enter) then
5106                            Set_Casing
5107                              (Identifier_Casing (Current_Source_File));
5108                            Error_Msg_String (1 .. Rnm'Length) :=
5109                              Name_Buffer (1 .. Name_Len);
5110                            Error_Msg_Strlen := Rnm'Length;
5111                            Error_Msg_N -- CODEFIX
5112                              ("\possible misspelling of ""~""",
5113                               Get_Pragma_Arg (Arg));
5114                            exit;
5115                         end if;
5116                      end;
5117                   end loop;
5118
5119                   raise Pragma_Exit;
5120                end if;
5121
5122                if Implementation_Restriction (R_Id) then
5123                   Check_Restriction (No_Implementation_Restrictions, Arg);
5124                end if;
5125
5126                --  If this is a warning, then set the warning unless we already
5127                --  have a real restriction active (we never want a warning to
5128                --  override a real restriction).
5129
5130                if Warn then
5131                   if not Restriction_Active (R_Id) then
5132                      Set_Restriction (R_Id, N);
5133                      Restriction_Warnings (R_Id) := True;
5134                   end if;
5135
5136                --  If real restriction case, then set it and make sure that the
5137                --  restriction warning flag is off, since a real restriction
5138                --  always overrides a warning.
5139
5140                else
5141                   Set_Restriction (R_Id, N);
5142                   Restriction_Warnings (R_Id) := False;
5143                end if;
5144
5145                --  Check for obsolescent restrictions in Ada 2005 mode
5146
5147                if not Warn
5148                  and then Ada_Version >= Ada_2005
5149                  and then (R_Id = No_Asynchronous_Control
5150                             or else
5151                            R_Id = No_Unchecked_Deallocation
5152                             or else
5153                            R_Id = No_Unchecked_Conversion)
5154                then
5155                   Check_Restriction (No_Obsolescent_Features, N);
5156                end if;
5157
5158                --  A very special case that must be processed here: pragma
5159                --  Restrictions (No_Exceptions) turns off all run-time
5160                --  checking. This is a bit dubious in terms of the formal
5161                --  language definition, but it is what is intended by RM
5162                --  H.4(12). Restriction_Warnings never affects generated code
5163                --  so this is done only in the real restriction case.
5164
5165                if R_Id = No_Exceptions and then not Warn then
5166                   Scope_Suppress := (others => True);
5167                end if;
5168
5169             --  Case of No_Dependence => unit-name. Note that the parser
5170             --  already made the necessary entry in the No_Dependence table.
5171
5172             elsif Id = Name_No_Dependence then
5173                Check_Unit_Name (Expr);
5174
5175             --  All other cases of restriction identifier present
5176
5177             else
5178                R_Id := Get_Restriction_Id (Process_Restriction_Synonyms (Arg));
5179                Analyze_And_Resolve (Expr, Any_Integer);
5180
5181                if R_Id not in All_Parameter_Restrictions then
5182                   Error_Pragma_Arg
5183                     ("invalid restriction parameter identifier", Arg);
5184
5185                elsif not Is_OK_Static_Expression (Expr) then
5186                   Flag_Non_Static_Expr
5187                     ("value must be static expression!", Expr);
5188                   raise Pragma_Exit;
5189
5190                elsif not Is_Integer_Type (Etype (Expr))
5191                  or else Expr_Value (Expr) < 0
5192                then
5193                   Error_Pragma_Arg
5194                     ("value must be non-negative integer", Arg);
5195                end if;
5196
5197                --  Restriction pragma is active
5198
5199                Val := Expr_Value (Expr);
5200
5201                if not UI_Is_In_Int_Range (Val) then
5202                   Error_Pragma_Arg
5203                     ("pragma ignored, value too large?", Arg);
5204                end if;
5205
5206                --  Warning case. If the real restriction is active, then we
5207                --  ignore the request, since warning never overrides a real
5208                --  restriction. Otherwise we set the proper warning. Note that
5209                --  this circuit sets the warning again if it is already set,
5210                --  which is what we want, since the constant may have changed.
5211
5212                if Warn then
5213                   if not Restriction_Active (R_Id) then
5214                      Set_Restriction
5215                        (R_Id, N, Integer (UI_To_Int (Val)));
5216                      Restriction_Warnings (R_Id) := True;
5217                   end if;
5218
5219                --  Real restriction case, set restriction and make sure warning
5220                --  flag is off since real restriction always overrides warning.
5221
5222                else
5223                   Set_Restriction (R_Id, N, Integer (UI_To_Int (Val)));
5224                   Restriction_Warnings (R_Id) := False;
5225                end if;
5226             end if;
5227
5228             Next (Arg);
5229          end loop;
5230       end Process_Restrictions_Or_Restriction_Warnings;
5231
5232       ---------------------------------
5233       -- Process_Suppress_Unsuppress --
5234       ---------------------------------
5235
5236       --  Note: this procedure makes entries in the check suppress data
5237       --  structures managed by Sem. See spec of package Sem for full
5238       --  details on how we handle recording of check suppression.
5239
5240       procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean) is
5241          C    : Check_Id;
5242          E_Id : Node_Id;
5243          E    : Entity_Id;
5244
5245          In_Package_Spec : constant Boolean :=
5246                              Is_Package_Or_Generic_Package (Current_Scope)
5247                                and then not In_Package_Body (Current_Scope);
5248
5249          procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id);
5250          --  Used to suppress a single check on the given entity
5251
5252          --------------------------------
5253          -- Suppress_Unsuppress_Echeck --
5254          --------------------------------
5255
5256          procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id) is
5257          begin
5258             Set_Checks_May_Be_Suppressed (E);
5259
5260             if In_Package_Spec then
5261                Push_Global_Suppress_Stack_Entry
5262                  (Entity   => E,
5263                   Check    => C,
5264                   Suppress => Suppress_Case);
5265
5266             else
5267                Push_Local_Suppress_Stack_Entry
5268                  (Entity   => E,
5269                   Check    => C,
5270                   Suppress => Suppress_Case);
5271             end if;
5272
5273             --  If this is a first subtype, and the base type is distinct,
5274             --  then also set the suppress flags on the base type.
5275
5276             if Is_First_Subtype (E)
5277               and then Etype (E) /= E
5278             then
5279                Suppress_Unsuppress_Echeck (Etype (E), C);
5280             end if;
5281          end Suppress_Unsuppress_Echeck;
5282
5283       --  Start of processing for Process_Suppress_Unsuppress
5284
5285       begin
5286          --  Ignore pragma Suppress/Unsuppress in codepeer mode on user code:
5287          --  we want to generate checks for analysis purposes, as set by -gnatC
5288
5289          if CodePeer_Mode and then Comes_From_Source (N) then
5290             return;
5291          end if;
5292
5293          --  Suppress/Unsuppress can appear as a configuration pragma, or in a
5294          --  declarative part or a package spec (RM 11.5(5)).
5295
5296          if not Is_Configuration_Pragma then
5297             Check_Is_In_Decl_Part_Or_Package_Spec;
5298          end if;
5299
5300          Check_At_Least_N_Arguments (1);
5301          Check_At_Most_N_Arguments (2);
5302          Check_No_Identifier (Arg1);
5303          Check_Arg_Is_Identifier (Arg1);
5304
5305          C := Get_Check_Id (Chars (Get_Pragma_Arg (Arg1)));
5306
5307          if C = No_Check_Id then
5308             Error_Pragma_Arg
5309               ("argument of pragma% is not valid check name", Arg1);
5310          end if;
5311
5312          if not Suppress_Case
5313            and then (C = All_Checks or else C = Overflow_Check)
5314          then
5315             Opt.Overflow_Checks_Unsuppressed := True;
5316          end if;
5317
5318          if Arg_Count = 1 then
5319
5320             --  Make an entry in the local scope suppress table. This is the
5321             --  table that directly shows the current value of the scope
5322             --  suppress check for any check id value.
5323
5324             if C = All_Checks then
5325
5326                --  For All_Checks, we set all specific predefined checks with
5327                --  the exception of Elaboration_Check, which is handled
5328                --  specially because of not wanting All_Checks to have the
5329                --  effect of deactivating static elaboration order processing.
5330
5331                for J in Scope_Suppress'Range loop
5332                   if J /= Elaboration_Check then
5333                      Scope_Suppress (J) := Suppress_Case;
5334                   end if;
5335                end loop;
5336
5337             --  If not All_Checks, and predefined check, then set appropriate
5338             --  scope entry. Note that we will set Elaboration_Check if this
5339             --  is explicitly specified.
5340
5341             elsif C in Predefined_Check_Id then
5342                Scope_Suppress (C) := Suppress_Case;
5343             end if;
5344
5345             --  Also make an entry in the Local_Entity_Suppress table
5346
5347             Push_Local_Suppress_Stack_Entry
5348               (Entity   => Empty,
5349                Check    => C,
5350                Suppress => Suppress_Case);
5351
5352          --  Case of two arguments present, where the check is suppressed for
5353          --  a specified entity (given as the second argument of the pragma)
5354
5355          else
5356             --  This is obsolescent in Ada 2005 mode
5357
5358             if Ada_Version >= Ada_2005 then
5359                Check_Restriction (No_Obsolescent_Features, Arg2);
5360             end if;
5361
5362             Check_Optional_Identifier (Arg2, Name_On);
5363             E_Id := Get_Pragma_Arg (Arg2);
5364             Analyze (E_Id);
5365
5366             if not Is_Entity_Name (E_Id) then
5367                Error_Pragma_Arg
5368                  ("second argument of pragma% must be entity name", Arg2);
5369             end if;
5370
5371             E := Entity (E_Id);
5372
5373             if E = Any_Id then
5374                return;
5375             end if;
5376
5377             --  Enforce RM 11.5(7) which requires that for a pragma that
5378             --  appears within a package spec, the named entity must be
5379             --  within the package spec. We allow the package name itself
5380             --  to be mentioned since that makes sense, although it is not
5381             --  strictly allowed by 11.5(7).
5382
5383             if In_Package_Spec
5384               and then E /= Current_Scope
5385               and then Scope (E) /= Current_Scope
5386             then
5387                Error_Pragma_Arg
5388                  ("entity in pragma% is not in package spec (RM 11.5(7))",
5389                   Arg2);
5390             end if;
5391
5392             --  Loop through homonyms. As noted below, in the case of a package
5393             --  spec, only homonyms within the package spec are considered.
5394
5395             loop
5396                Suppress_Unsuppress_Echeck (E, C);
5397
5398                if Is_Generic_Instance (E)
5399                  and then Is_Subprogram (E)
5400                  and then Present (Alias (E))
5401                then
5402                   Suppress_Unsuppress_Echeck (Alias (E), C);
5403                end if;
5404
5405                --  Move to next homonym if not aspect spec case
5406
5407                exit when From_Aspect_Specification (N);
5408                E := Homonym (E);
5409                exit when No (E);
5410
5411                --  If we are within a package specification, the pragma only
5412                --  applies to homonyms in the same scope.
5413
5414                exit when In_Package_Spec
5415                  and then Scope (E) /= Current_Scope;
5416             end loop;
5417          end if;
5418       end Process_Suppress_Unsuppress;
5419
5420       ------------------
5421       -- Set_Exported --
5422       ------------------
5423
5424       procedure Set_Exported (E : Entity_Id; Arg : Node_Id) is
5425       begin
5426          if Is_Imported (E) then
5427             Error_Pragma_Arg
5428               ("cannot export entity& that was previously imported", Arg);
5429
5430          elsif Present (Address_Clause (E)) and then not CodePeer_Mode then
5431             Error_Pragma_Arg
5432               ("cannot export entity& that has an address clause", Arg);
5433          end if;
5434
5435          Set_Is_Exported (E);
5436
5437          --  Generate a reference for entity explicitly, because the
5438          --  identifier may be overloaded and name resolution will not
5439          --  generate one.
5440
5441          Generate_Reference (E, Arg);
5442
5443          --  Deal with exporting non-library level entity
5444
5445          if not Is_Library_Level_Entity (E) then
5446
5447             --  Not allowed at all for subprograms
5448
5449             if Is_Subprogram (E) then
5450                Error_Pragma_Arg ("local subprogram& cannot be exported", Arg);
5451
5452             --  Otherwise set public and statically allocated
5453
5454             else
5455                Set_Is_Public (E);
5456                Set_Is_Statically_Allocated (E);
5457
5458                --  Warn if the corresponding W flag is set and the pragma comes
5459                --  from source. The latter may not be true e.g. on VMS where we
5460                --  expand export pragmas for exception codes associated with
5461                --  imported or exported exceptions. We do not want to generate
5462                --  a warning for something that the user did not write.
5463
5464                if Warn_On_Export_Import
5465                  and then Comes_From_Source (Arg)
5466                then
5467                   Error_Msg_NE
5468                     ("?& has been made static as a result of Export", Arg, E);
5469                   Error_Msg_N
5470                     ("\this usage is non-standard and non-portable", Arg);
5471                end if;
5472             end if;
5473          end if;
5474
5475          if Warn_On_Export_Import and then Is_Type (E) then
5476             Error_Msg_NE ("exporting a type has no effect?", Arg, E);
5477          end if;
5478
5479          if Warn_On_Export_Import and Inside_A_Generic then
5480             Error_Msg_NE
5481               ("all instances of& will have the same external name?", Arg, E);
5482          end if;
5483       end Set_Exported;
5484
5485       ----------------------------------------------
5486       -- Set_Extended_Import_Export_External_Name --
5487       ----------------------------------------------
5488
5489       procedure Set_Extended_Import_Export_External_Name
5490         (Internal_Ent : Entity_Id;
5491          Arg_External : Node_Id)
5492       is
5493          Old_Name : constant Node_Id := Interface_Name (Internal_Ent);
5494          New_Name : Node_Id;
5495
5496       begin
5497          if No (Arg_External) then
5498             return;
5499          end if;
5500
5501          Check_Arg_Is_External_Name (Arg_External);
5502
5503          if Nkind (Arg_External) = N_String_Literal then
5504             if String_Length (Strval (Arg_External)) = 0 then
5505                return;
5506             else
5507                New_Name := Adjust_External_Name_Case (Arg_External);
5508             end if;
5509
5510          elsif Nkind (Arg_External) = N_Identifier then
5511             New_Name := Get_Default_External_Name (Arg_External);
5512
5513          --  Check_Arg_Is_External_Name should let through only identifiers and
5514          --  string literals or static string expressions (which are folded to
5515          --  string literals).
5516
5517          else
5518             raise Program_Error;
5519          end if;
5520
5521          --  If we already have an external name set (by a prior normal Import
5522          --  or Export pragma), then the external names must match
5523
5524          if Present (Interface_Name (Internal_Ent)) then
5525             Check_Matching_Internal_Names : declare
5526                S1 : constant String_Id := Strval (Old_Name);
5527                S2 : constant String_Id := Strval (New_Name);
5528
5529                procedure Mismatch;
5530                --  Called if names do not match
5531
5532                --------------
5533                -- Mismatch --
5534                --------------
5535
5536                procedure Mismatch is
5537                begin
5538                   Error_Msg_Sloc := Sloc (Old_Name);
5539                   Error_Pragma_Arg
5540                     ("external name does not match that given #",
5541                      Arg_External);
5542                end Mismatch;
5543
5544             --  Start of processing for Check_Matching_Internal_Names
5545
5546             begin
5547                if String_Length (S1) /= String_Length (S2) then
5548                   Mismatch;
5549
5550                else
5551                   for J in 1 .. String_Length (S1) loop
5552                      if Get_String_Char (S1, J) /= Get_String_Char (S2, J) then
5553                         Mismatch;
5554                      end if;
5555                   end loop;
5556                end if;
5557             end Check_Matching_Internal_Names;
5558
5559          --  Otherwise set the given name
5560
5561          else
5562             Set_Encoded_Interface_Name (Internal_Ent, New_Name);
5563             Check_Duplicated_Export_Name (New_Name);
5564          end if;
5565       end Set_Extended_Import_Export_External_Name;
5566
5567       ------------------
5568       -- Set_Imported --
5569       ------------------
5570
5571       procedure Set_Imported (E : Entity_Id) is
5572       begin
5573          --  Error message if already imported or exported
5574
5575          if Is_Exported (E) or else Is_Imported (E) then
5576
5577             --  Error if being set Exported twice
5578
5579             if Is_Exported (E) then
5580                Error_Msg_NE ("entity& was previously exported", N, E);
5581
5582             --  OK if Import/Interface case
5583
5584             elsif Import_Interface_Present (N) then
5585                goto OK;
5586
5587             --  Error if being set Imported twice
5588
5589             else
5590                Error_Msg_NE ("entity& was previously imported", N, E);
5591             end if;
5592
5593             Error_Msg_Name_1 := Pname;
5594             Error_Msg_N
5595               ("\(pragma% applies to all previous entities)", N);
5596
5597             Error_Msg_Sloc  := Sloc (E);
5598             Error_Msg_NE ("\import not allowed for& declared#", N, E);
5599
5600          --  Here if not previously imported or exported, OK to import
5601
5602          else
5603             Set_Is_Imported (E);
5604
5605             --  If the entity is an object that is not at the library level,
5606             --  then it is statically allocated. We do not worry about objects
5607             --  with address clauses in this context since they are not really
5608             --  imported in the linker sense.
5609
5610             if Is_Object (E)
5611               and then not Is_Library_Level_Entity (E)
5612               and then No (Address_Clause (E))
5613             then
5614                Set_Is_Statically_Allocated (E);
5615             end if;
5616          end if;
5617
5618          <<OK>> null;
5619       end Set_Imported;
5620
5621       -------------------------
5622       -- Set_Mechanism_Value --
5623       -------------------------
5624
5625       --  Note: the mechanism name has not been analyzed (and cannot indeed be
5626       --  analyzed, since it is semantic nonsense), so we get it in the exact
5627       --  form created by the parser.
5628
5629       procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id) is
5630          Class        : Node_Id;
5631          Param        : Node_Id;
5632          Mech_Name_Id : Name_Id;
5633
5634          procedure Bad_Class;
5635          --  Signal bad descriptor class name
5636
5637          procedure Bad_Mechanism;
5638          --  Signal bad mechanism name
5639
5640          ---------------
5641          -- Bad_Class --
5642          ---------------
5643
5644          procedure Bad_Class is
5645          begin
5646             Error_Pragma_Arg ("unrecognized descriptor class name", Class);
5647          end Bad_Class;
5648
5649          -------------------------
5650          -- Bad_Mechanism_Value --
5651          -------------------------
5652
5653          procedure Bad_Mechanism is
5654          begin
5655             Error_Pragma_Arg ("unrecognized mechanism name", Mech_Name);
5656          end Bad_Mechanism;
5657
5658       --  Start of processing for Set_Mechanism_Value
5659
5660       begin
5661          if Mechanism (Ent) /= Default_Mechanism then
5662             Error_Msg_NE
5663               ("mechanism for & has already been set", Mech_Name, Ent);
5664          end if;
5665
5666          --  MECHANISM_NAME ::= value | reference | descriptor |
5667          --                     short_descriptor
5668
5669          if Nkind (Mech_Name) = N_Identifier then
5670             if Chars (Mech_Name) = Name_Value then
5671                Set_Mechanism (Ent, By_Copy);
5672                return;
5673
5674             elsif Chars (Mech_Name) = Name_Reference then
5675                Set_Mechanism (Ent, By_Reference);
5676                return;
5677
5678             elsif Chars (Mech_Name) = Name_Descriptor then
5679                Check_VMS (Mech_Name);
5680
5681                --  Descriptor => Short_Descriptor if pragma was given
5682
5683                if Short_Descriptors then
5684                   Set_Mechanism (Ent, By_Short_Descriptor);
5685                else
5686                   Set_Mechanism (Ent, By_Descriptor);
5687                end if;
5688
5689                return;
5690
5691             elsif Chars (Mech_Name) = Name_Short_Descriptor then
5692                Check_VMS (Mech_Name);
5693                Set_Mechanism (Ent, By_Short_Descriptor);
5694                return;
5695
5696             elsif Chars (Mech_Name) = Name_Copy then
5697                Error_Pragma_Arg
5698                  ("bad mechanism name, Value assumed", Mech_Name);
5699
5700             else
5701                Bad_Mechanism;
5702             end if;
5703
5704          --  MECHANISM_NAME ::= descriptor (CLASS_NAME) |
5705          --                     short_descriptor (CLASS_NAME)
5706          --  CLASS_NAME     ::= ubs | ubsb | uba | s | sb | a | nca
5707
5708          --  Note: this form is parsed as an indexed component
5709
5710          elsif Nkind (Mech_Name) = N_Indexed_Component then
5711             Class := First (Expressions (Mech_Name));
5712
5713             if Nkind (Prefix (Mech_Name)) /= N_Identifier
5714              or else not (Chars (Prefix (Mech_Name)) = Name_Descriptor or else
5715                           Chars (Prefix (Mech_Name)) = Name_Short_Descriptor)
5716              or else Present (Next (Class))
5717             then
5718                Bad_Mechanism;
5719             else
5720                Mech_Name_Id := Chars (Prefix (Mech_Name));
5721
5722                --  Change Descriptor => Short_Descriptor if pragma was given
5723
5724                if Mech_Name_Id = Name_Descriptor
5725                  and then Short_Descriptors
5726                then
5727                   Mech_Name_Id := Name_Short_Descriptor;
5728                end if;
5729             end if;
5730
5731          --  MECHANISM_NAME ::= descriptor (Class => CLASS_NAME) |
5732          --                     short_descriptor (Class => CLASS_NAME)
5733          --  CLASS_NAME     ::= ubs | ubsb | uba | s | sb | a | nca
5734
5735          --  Note: this form is parsed as a function call
5736
5737          elsif Nkind (Mech_Name) = N_Function_Call then
5738             Param := First (Parameter_Associations (Mech_Name));
5739
5740             if Nkind (Name (Mech_Name)) /= N_Identifier
5741               or else not (Chars (Name (Mech_Name)) = Name_Descriptor or else
5742                            Chars (Name (Mech_Name)) = Name_Short_Descriptor)
5743               or else Present (Next (Param))
5744               or else No (Selector_Name (Param))
5745               or else Chars (Selector_Name (Param)) /= Name_Class
5746             then
5747                Bad_Mechanism;
5748             else
5749                Class := Explicit_Actual_Parameter (Param);
5750                Mech_Name_Id := Chars (Name (Mech_Name));
5751             end if;
5752
5753          else
5754             Bad_Mechanism;
5755          end if;
5756
5757          --  Fall through here with Class set to descriptor class name
5758
5759          Check_VMS (Mech_Name);
5760
5761          if Nkind (Class) /= N_Identifier then
5762             Bad_Class;
5763
5764          elsif Mech_Name_Id = Name_Descriptor
5765            and then Chars (Class) = Name_UBS
5766          then
5767             Set_Mechanism (Ent, By_Descriptor_UBS);
5768
5769          elsif Mech_Name_Id = Name_Descriptor
5770            and then Chars (Class) = Name_UBSB
5771          then
5772             Set_Mechanism (Ent, By_Descriptor_UBSB);
5773
5774          elsif Mech_Name_Id = Name_Descriptor
5775            and then Chars (Class) = Name_UBA
5776          then
5777             Set_Mechanism (Ent, By_Descriptor_UBA);
5778
5779          elsif Mech_Name_Id = Name_Descriptor
5780            and then Chars (Class) = Name_S
5781          then
5782             Set_Mechanism (Ent, By_Descriptor_S);
5783
5784          elsif Mech_Name_Id = Name_Descriptor
5785            and then Chars (Class) = Name_SB
5786          then
5787             Set_Mechanism (Ent, By_Descriptor_SB);
5788
5789          elsif Mech_Name_Id = Name_Descriptor
5790            and then Chars (Class) = Name_A
5791          then
5792             Set_Mechanism (Ent, By_Descriptor_A);
5793
5794          elsif Mech_Name_Id = Name_Descriptor
5795            and then Chars (Class) = Name_NCA
5796          then
5797             Set_Mechanism (Ent, By_Descriptor_NCA);
5798
5799          elsif Mech_Name_Id = Name_Short_Descriptor
5800            and then Chars (Class) = Name_UBS
5801          then
5802             Set_Mechanism (Ent, By_Short_Descriptor_UBS);
5803
5804          elsif Mech_Name_Id = Name_Short_Descriptor
5805            and then Chars (Class) = Name_UBSB
5806          then
5807             Set_Mechanism (Ent, By_Short_Descriptor_UBSB);
5808
5809          elsif Mech_Name_Id = Name_Short_Descriptor
5810            and then Chars (Class) = Name_UBA
5811          then
5812             Set_Mechanism (Ent, By_Short_Descriptor_UBA);
5813
5814          elsif Mech_Name_Id = Name_Short_Descriptor
5815            and then Chars (Class) = Name_S
5816          then
5817             Set_Mechanism (Ent, By_Short_Descriptor_S);
5818
5819          elsif Mech_Name_Id = Name_Short_Descriptor
5820            and then Chars (Class) = Name_SB
5821          then
5822             Set_Mechanism (Ent, By_Short_Descriptor_SB);
5823
5824          elsif Mech_Name_Id = Name_Short_Descriptor
5825            and then Chars (Class) = Name_A
5826          then
5827             Set_Mechanism (Ent, By_Short_Descriptor_A);
5828
5829          elsif Mech_Name_Id = Name_Short_Descriptor
5830            and then Chars (Class) = Name_NCA
5831          then
5832             Set_Mechanism (Ent, By_Short_Descriptor_NCA);
5833
5834          else
5835             Bad_Class;
5836          end if;
5837       end Set_Mechanism_Value;
5838
5839       ---------------------------
5840       -- Set_Ravenscar_Profile --
5841       ---------------------------
5842
5843       --  The tasks to be done here are
5844
5845       --    Set required policies
5846
5847       --      pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
5848       --      pragma Locking_Policy (Ceiling_Locking)
5849
5850       --    Set Detect_Blocking mode
5851
5852       --    Set required restrictions (see System.Rident for detailed list)
5853
5854       --    Set the No_Dependence rules
5855       --      No_Dependence => Ada.Asynchronous_Task_Control
5856       --      No_Dependence => Ada.Calendar
5857       --      No_Dependence => Ada.Execution_Time.Group_Budget
5858       --      No_Dependence => Ada.Execution_Time.Timers
5859       --      No_Dependence => Ada.Task_Attributes
5860       --      No_Dependence => System.Multiprocessors.Dispatching_Domains
5861
5862       procedure Set_Ravenscar_Profile (N : Node_Id) is
5863          Prefix_Entity   : Entity_Id;
5864          Selector_Entity : Entity_Id;
5865          Prefix_Node     : Node_Id;
5866          Node            : Node_Id;
5867
5868       begin
5869          --  pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
5870
5871          if Task_Dispatching_Policy /= ' '
5872            and then Task_Dispatching_Policy /= 'F'
5873          then
5874             Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
5875             Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
5876
5877          --  Set the FIFO_Within_Priorities policy, but always preserve
5878          --  System_Location since we like the error message with the run time
5879          --  name.
5880
5881          else
5882             Task_Dispatching_Policy := 'F';
5883
5884             if Task_Dispatching_Policy_Sloc /= System_Location then
5885                Task_Dispatching_Policy_Sloc := Loc;
5886             end if;
5887          end if;
5888
5889          --  pragma Locking_Policy (Ceiling_Locking)
5890
5891          if Locking_Policy /= ' '
5892            and then Locking_Policy /= 'C'
5893          then
5894             Error_Msg_Sloc := Locking_Policy_Sloc;
5895             Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
5896
5897          --  Set the Ceiling_Locking policy, but preserve System_Location since
5898          --  we like the error message with the run time name.
5899
5900          else
5901             Locking_Policy := 'C';
5902
5903             if Locking_Policy_Sloc /= System_Location then
5904                Locking_Policy_Sloc := Loc;
5905             end if;
5906          end if;
5907
5908          --  pragma Detect_Blocking
5909
5910          Detect_Blocking := True;
5911
5912          --  Set the corresponding restrictions
5913
5914          Set_Profile_Restrictions
5915            (Ravenscar, N, Warn => Treat_Restrictions_As_Warnings);
5916
5917          --  Set the No_Dependence restrictions
5918
5919          --  The following No_Dependence restrictions:
5920          --    No_Dependence => Ada.Asynchronous_Task_Control
5921          --    No_Dependence => Ada.Calendar
5922          --    No_Dependence => Ada.Task_Attributes
5923          --  are already set by previous call to Set_Profile_Restrictions.
5924
5925          --  Set the following restrictions which were added to Ada 2005:
5926          --    No_Dependence => Ada.Execution_Time.Group_Budget
5927          --    No_Dependence => Ada.Execution_Time.Timers
5928
5929          if Ada_Version >= Ada_2005 then
5930             Name_Buffer (1 .. 3) := "ada";
5931             Name_Len := 3;
5932
5933             Prefix_Entity := Make_Identifier (Loc, Name_Find);
5934
5935             Name_Buffer (1 .. 14) := "execution_time";
5936             Name_Len := 14;
5937
5938             Selector_Entity := Make_Identifier (Loc, Name_Find);
5939
5940             Prefix_Node :=
5941               Make_Selected_Component
5942                 (Sloc          => Loc,
5943                  Prefix        => Prefix_Entity,
5944                  Selector_Name => Selector_Entity);
5945
5946             Name_Buffer (1 .. 13) := "group_budgets";
5947             Name_Len := 13;
5948
5949             Selector_Entity := Make_Identifier (Loc, Name_Find);
5950
5951             Node :=
5952               Make_Selected_Component
5953                 (Sloc          => Loc,
5954                  Prefix        => Prefix_Node,
5955                  Selector_Name => Selector_Entity);
5956
5957             Set_Restriction_No_Dependence
5958               (Unit    => Node,
5959                Warn    => Treat_Restrictions_As_Warnings,
5960                Profile => Ravenscar);
5961
5962             Name_Buffer (1 .. 6) := "timers";
5963             Name_Len := 6;
5964
5965             Selector_Entity := Make_Identifier (Loc, Name_Find);
5966
5967             Node :=
5968               Make_Selected_Component
5969                 (Sloc          => Loc,
5970                  Prefix        => Prefix_Node,
5971                  Selector_Name => Selector_Entity);
5972
5973             Set_Restriction_No_Dependence
5974               (Unit    => Node,
5975                Warn    => Treat_Restrictions_As_Warnings,
5976                Profile => Ravenscar);
5977          end if;
5978
5979          --  Set the following restrictions which was added to Ada 2012 (see
5980          --  AI-0171):
5981          --    No_Dependence => System.Multiprocessors.Dispatching_Domains
5982
5983          if Ada_Version >= Ada_2012 then
5984             Name_Buffer (1 .. 6) := "system";
5985             Name_Len := 6;
5986
5987             Prefix_Entity := Make_Identifier (Loc, Name_Find);
5988
5989             Name_Buffer (1 .. 15) := "multiprocessors";
5990             Name_Len := 15;
5991
5992             Selector_Entity := Make_Identifier (Loc, Name_Find);
5993
5994             Prefix_Node :=
5995               Make_Selected_Component
5996                 (Sloc          => Loc,
5997                  Prefix        => Prefix_Entity,
5998                  Selector_Name => Selector_Entity);
5999
6000             Name_Buffer (1 .. 19) := "dispatching_domains";
6001             Name_Len := 19;
6002
6003             Selector_Entity := Make_Identifier (Loc, Name_Find);
6004
6005             Node :=
6006               Make_Selected_Component
6007                 (Sloc          => Loc,
6008                  Prefix        => Prefix_Node,
6009                  Selector_Name => Selector_Entity);
6010
6011             Set_Restriction_No_Dependence
6012               (Unit    => Node,
6013                Warn    => Treat_Restrictions_As_Warnings,
6014                Profile => Ravenscar);
6015          end if;
6016       end Set_Ravenscar_Profile;
6017
6018    --  Start of processing for Analyze_Pragma
6019
6020    begin
6021       --  The following code is a defense against recursion. Not clear that
6022       --  this can happen legitimately, but perhaps some error situations
6023       --  can cause it, and we did see this recursion during testing.
6024
6025       if Analyzed (N) then
6026          return;
6027       else
6028          Set_Analyzed (N, True);
6029       end if;
6030
6031       --  Deal with unrecognized pragma
6032
6033       if not Is_Pragma_Name (Pname) then
6034          if Warn_On_Unrecognized_Pragma then
6035             Error_Msg_Name_1 := Pname;
6036             Error_Msg_N ("?unrecognized pragma%!", Pragma_Identifier (N));
6037
6038             for PN in First_Pragma_Name .. Last_Pragma_Name loop
6039                if Is_Bad_Spelling_Of (Pname, PN) then
6040                   Error_Msg_Name_1 := PN;
6041                   Error_Msg_N -- CODEFIX
6042                     ("\?possible misspelling of %!", Pragma_Identifier (N));
6043                   exit;
6044                end if;
6045             end loop;
6046          end if;
6047
6048          return;
6049       end if;
6050
6051       --  Here to start processing for recognized pragma
6052
6053       Prag_Id := Get_Pragma_Id (Pname);
6054
6055       --  Preset arguments
6056
6057       Arg_Count := 0;
6058       Arg1      := Empty;
6059       Arg2      := Empty;
6060       Arg3      := Empty;
6061       Arg4      := Empty;
6062
6063       if Present (Pragma_Argument_Associations (N)) then
6064          Arg_Count := List_Length (Pragma_Argument_Associations (N));
6065          Arg1 := First (Pragma_Argument_Associations (N));
6066
6067          if Present (Arg1) then
6068             Arg2 := Next (Arg1);
6069
6070             if Present (Arg2) then
6071                Arg3 := Next (Arg2);
6072
6073                if Present (Arg3) then
6074                   Arg4 := Next (Arg3);
6075                end if;
6076             end if;
6077          end if;
6078       end if;
6079
6080       --  An enumeration type defines the pragmas that are supported by the
6081       --  implementation. Get_Pragma_Id (in package Prag) transforms a name
6082       --  into the corresponding enumeration value for the following case.
6083
6084       case Prag_Id is
6085
6086          -----------------
6087          -- Abort_Defer --
6088          -----------------
6089
6090          --  pragma Abort_Defer;
6091
6092          when Pragma_Abort_Defer =>
6093             GNAT_Pragma;
6094             Check_Arg_Count (0);
6095
6096             --  The only required semantic processing is to check the
6097             --  placement. This pragma must appear at the start of the
6098             --  statement sequence of a handled sequence of statements.
6099
6100             if Nkind (Parent (N)) /= N_Handled_Sequence_Of_Statements
6101               or else N /= First (Statements (Parent (N)))
6102             then
6103                Pragma_Misplaced;
6104             end if;
6105
6106          ------------
6107          -- Ada_83 --
6108          ------------
6109
6110          --  pragma Ada_83;
6111
6112          --  Note: this pragma also has some specific processing in Par.Prag
6113          --  because we want to set the Ada version mode during parsing.
6114
6115          when Pragma_Ada_83 =>
6116             GNAT_Pragma;
6117             Check_Arg_Count (0);
6118
6119             --  We really should check unconditionally for proper configuration
6120             --  pragma placement, since we really don't want mixed Ada modes
6121             --  within a single unit, and the GNAT reference manual has always
6122             --  said this was a configuration pragma, but we did not check and
6123             --  are hesitant to add the check now.
6124
6125             --  However, we really cannot tolerate mixing Ada 2005 or Ada 2012
6126             --  with Ada 83 or Ada 95, so we must check if we are in Ada 2005
6127             --  or Ada 2012 mode.
6128
6129             if Ada_Version >= Ada_2005 then
6130                Check_Valid_Configuration_Pragma;
6131             end if;
6132
6133             --  Now set Ada 83 mode
6134
6135             Ada_Version := Ada_83;
6136             Ada_Version_Explicit := Ada_Version;
6137
6138          ------------
6139          -- Ada_95 --
6140          ------------
6141
6142          --  pragma Ada_95;
6143
6144          --  Note: this pragma also has some specific processing in Par.Prag
6145          --  because we want to set the Ada 83 version mode during parsing.
6146
6147          when Pragma_Ada_95 =>
6148             GNAT_Pragma;
6149             Check_Arg_Count (0);
6150
6151             --  We really should check unconditionally for proper configuration
6152             --  pragma placement, since we really don't want mixed Ada modes
6153             --  within a single unit, and the GNAT reference manual has always
6154             --  said this was a configuration pragma, but we did not check and
6155             --  are hesitant to add the check now.
6156
6157             --  However, we really cannot tolerate mixing Ada 2005 with Ada 83
6158             --  or Ada 95, so we must check if we are in Ada 2005 mode.
6159
6160             if Ada_Version >= Ada_2005 then
6161                Check_Valid_Configuration_Pragma;
6162             end if;
6163
6164             --  Now set Ada 95 mode
6165
6166             Ada_Version := Ada_95;
6167             Ada_Version_Explicit := Ada_Version;
6168
6169          ---------------------
6170          -- Ada_05/Ada_2005 --
6171          ---------------------
6172
6173          --  pragma Ada_05;
6174          --  pragma Ada_05 (LOCAL_NAME);
6175
6176          --  pragma Ada_2005;
6177          --  pragma Ada_2005 (LOCAL_NAME):
6178
6179          --  Note: these pragmas also have some specific processing in Par.Prag
6180          --  because we want to set the Ada 2005 version mode during parsing.
6181
6182          when Pragma_Ada_05 | Pragma_Ada_2005 => declare
6183             E_Id : Node_Id;
6184
6185          begin
6186             GNAT_Pragma;
6187
6188             if Arg_Count = 1 then
6189                Check_Arg_Is_Local_Name (Arg1);
6190                E_Id := Get_Pragma_Arg (Arg1);
6191
6192                if Etype (E_Id) = Any_Type then
6193                   return;
6194                end if;
6195
6196                Set_Is_Ada_2005_Only (Entity (E_Id));
6197
6198             else
6199                Check_Arg_Count (0);
6200
6201                --  For Ada_2005 we unconditionally enforce the documented
6202                --  configuration pragma placement, since we do not want to
6203                --  tolerate mixed modes in a unit involving Ada 2005. That
6204                --  would cause real difficulties for those cases where there
6205                --  are incompatibilities between Ada 95 and Ada 2005.
6206
6207                Check_Valid_Configuration_Pragma;
6208
6209                --  Now set appropriate Ada mode
6210
6211                Ada_Version          := Ada_2005;
6212                Ada_Version_Explicit := Ada_2005;
6213             end if;
6214          end;
6215
6216          ---------------------
6217          -- Ada_12/Ada_2012 --
6218          ---------------------
6219
6220          --  pragma Ada_12;
6221          --  pragma Ada_12 (LOCAL_NAME);
6222
6223          --  pragma Ada_2012;
6224          --  pragma Ada_2012 (LOCAL_NAME):
6225
6226          --  Note: these pragmas also have some specific processing in Par.Prag
6227          --  because we want to set the Ada 2012 version mode during parsing.
6228
6229          when Pragma_Ada_12 | Pragma_Ada_2012 => declare
6230             E_Id : Node_Id;
6231
6232          begin
6233             GNAT_Pragma;
6234
6235             if Arg_Count = 1 then
6236                Check_Arg_Is_Local_Name (Arg1);
6237                E_Id := Get_Pragma_Arg (Arg1);
6238
6239                if Etype (E_Id) = Any_Type then
6240                   return;
6241                end if;
6242
6243                Set_Is_Ada_2012_Only (Entity (E_Id));
6244
6245             else
6246                Check_Arg_Count (0);
6247
6248                --  For Ada_2012 we unconditionally enforce the documented
6249                --  configuration pragma placement, since we do not want to
6250                --  tolerate mixed modes in a unit involving Ada 2012. That
6251                --  would cause real difficulties for those cases where there
6252                --  are incompatibilities between Ada 95 and Ada 2012. We could
6253                --  allow mixing of Ada 2005 and Ada 2012 but it's not worth it.
6254
6255                Check_Valid_Configuration_Pragma;
6256
6257                --  Now set appropriate Ada mode
6258
6259                Ada_Version          := Ada_2012;
6260                Ada_Version_Explicit := Ada_2012;
6261             end if;
6262          end;
6263
6264          ----------------------
6265          -- All_Calls_Remote --
6266          ----------------------
6267
6268          --  pragma All_Calls_Remote [(library_package_NAME)];
6269
6270          when Pragma_All_Calls_Remote => All_Calls_Remote : declare
6271             Lib_Entity : Entity_Id;
6272
6273          begin
6274             Check_Ada_83_Warning;
6275             Check_Valid_Library_Unit_Pragma;
6276
6277             if Nkind (N) = N_Null_Statement then
6278                return;
6279             end if;
6280
6281             Lib_Entity := Find_Lib_Unit_Name;
6282
6283             --  This pragma should only apply to a RCI unit (RM E.2.3(23))
6284
6285             if Present (Lib_Entity)
6286               and then not Debug_Flag_U
6287             then
6288                if not Is_Remote_Call_Interface (Lib_Entity) then
6289                   Error_Pragma ("pragma% only apply to rci unit");
6290
6291                --  Set flag for entity of the library unit
6292
6293                else
6294                   Set_Has_All_Calls_Remote (Lib_Entity);
6295                end if;
6296
6297             end if;
6298          end All_Calls_Remote;
6299
6300          --------------
6301          -- Annotate --
6302          --------------
6303
6304          --  pragma Annotate (IDENTIFIER [, IDENTIFIER {, ARG}]);
6305          --  ARG ::= NAME | EXPRESSION
6306
6307          --  The first two arguments are by convention intended to refer to an
6308          --  external tool and a tool-specific function. These arguments are
6309          --  not analyzed.
6310
6311          when Pragma_Annotate => Annotate : declare
6312             Arg : Node_Id;
6313             Exp : Node_Id;
6314
6315          begin
6316             GNAT_Pragma;
6317             Check_At_Least_N_Arguments (1);
6318             Check_Arg_Is_Identifier (Arg1);
6319             Check_No_Identifiers;
6320             Store_Note (N);
6321
6322             --  Second parameter is optional, it is never analyzed
6323
6324             if No (Arg2) then
6325                null;
6326
6327             --  Here if we have a second parameter
6328
6329             else
6330                --  Second parameter must be identifier
6331
6332                Check_Arg_Is_Identifier (Arg2);
6333
6334                --  Process remaining parameters if any
6335
6336                Arg := Next (Arg2);
6337                while Present (Arg) loop
6338                   Exp := Get_Pragma_Arg (Arg);
6339                   Analyze (Exp);
6340
6341                   if Is_Entity_Name (Exp) then
6342                      null;
6343
6344                   --  For string literals, we assume Standard_String as the
6345                   --  type, unless the string contains wide or wide_wide
6346                   --  characters.
6347
6348                   elsif Nkind (Exp) = N_String_Literal then
6349                      if Has_Wide_Wide_Character (Exp) then
6350                         Resolve (Exp, Standard_Wide_Wide_String);
6351                      elsif Has_Wide_Character (Exp) then
6352                         Resolve (Exp, Standard_Wide_String);
6353                      else
6354                         Resolve (Exp, Standard_String);
6355                      end if;
6356
6357                   elsif Is_Overloaded (Exp) then
6358                         Error_Pragma_Arg
6359                           ("ambiguous argument for pragma%", Exp);
6360
6361                   else
6362                      Resolve (Exp);
6363                   end if;
6364
6365                   Next (Arg);
6366                end loop;
6367             end if;
6368          end Annotate;
6369
6370          ------------
6371          -- Assert --
6372          ------------
6373
6374          --  pragma Assert ([Check =>] Boolean_EXPRESSION
6375          --                 [, [Message =>] Static_String_EXPRESSION]);
6376
6377          when Pragma_Assert => Assert : declare
6378             Expr : Node_Id;
6379             Newa : List_Id;
6380
6381          begin
6382             Ada_2005_Pragma;
6383             Check_At_Least_N_Arguments (1);
6384             Check_At_Most_N_Arguments (2);
6385             Check_Arg_Order ((Name_Check, Name_Message));
6386             Check_Optional_Identifier (Arg1, Name_Check);
6387
6388             --  We treat pragma Assert as equivalent to:
6389
6390             --    pragma Check (Assertion, condition [, msg]);
6391
6392             --  So rewrite pragma in this manner, and analyze the result
6393
6394             Expr := Get_Pragma_Arg (Arg1);
6395             Newa := New_List (
6396               Make_Pragma_Argument_Association (Loc,
6397                 Expression => Make_Identifier (Loc, Name_Assertion)),
6398
6399               Make_Pragma_Argument_Association (Sloc (Expr),
6400                 Expression => Expr));
6401
6402             if Arg_Count > 1 then
6403                Check_Optional_Identifier (Arg2, Name_Message);
6404                Analyze_And_Resolve (Get_Pragma_Arg (Arg2), Standard_String);
6405                Append_To (Newa, Relocate_Node (Arg2));
6406             end if;
6407
6408             Rewrite (N,
6409               Make_Pragma (Loc,
6410                 Chars => Name_Check,
6411                 Pragma_Argument_Associations => Newa));
6412             Analyze (N);
6413          end Assert;
6414
6415          ----------------------
6416          -- Assertion_Policy --
6417          ----------------------
6418
6419          --  pragma Assertion_Policy (Check | Ignore)
6420
6421          when Pragma_Assertion_Policy => Assertion_Policy : declare
6422             Policy : Node_Id;
6423
6424          begin
6425             Ada_2005_Pragma;
6426             Check_Valid_Configuration_Pragma;
6427             Check_Arg_Count (1);
6428             Check_No_Identifiers;
6429             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Ignore);
6430
6431             --  We treat pragma Assertion_Policy as equivalent to:
6432
6433             --    pragma Check_Policy (Assertion, policy)
6434
6435             --  So rewrite the pragma in that manner and link on to the chain
6436             --  of Check_Policy pragmas, marking the pragma as analyzed.
6437
6438             Policy := Get_Pragma_Arg (Arg1);
6439
6440             Rewrite (N,
6441               Make_Pragma (Loc,
6442                 Chars => Name_Check_Policy,
6443
6444                 Pragma_Argument_Associations => New_List (
6445                   Make_Pragma_Argument_Association (Loc,
6446                     Expression => Make_Identifier (Loc, Name_Assertion)),
6447
6448                   Make_Pragma_Argument_Association (Loc,
6449                     Expression =>
6450                       Make_Identifier (Sloc (Policy), Chars (Policy))))));
6451
6452             Set_Analyzed (N);
6453             Set_Next_Pragma (N, Opt.Check_Policy_List);
6454             Opt.Check_Policy_List := N;
6455          end Assertion_Policy;
6456
6457          ------------------------------
6458          -- Assume_No_Invalid_Values --
6459          ------------------------------
6460
6461          --  pragma Assume_No_Invalid_Values (On | Off);
6462
6463          when Pragma_Assume_No_Invalid_Values =>
6464             GNAT_Pragma;
6465             Check_Valid_Configuration_Pragma;
6466             Check_Arg_Count (1);
6467             Check_No_Identifiers;
6468             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
6469
6470             if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
6471                Assume_No_Invalid_Values := True;
6472             else
6473                Assume_No_Invalid_Values := False;
6474             end if;
6475
6476          ---------------
6477          -- AST_Entry --
6478          ---------------
6479
6480          --  pragma AST_Entry (entry_IDENTIFIER);
6481
6482          when Pragma_AST_Entry => AST_Entry : declare
6483             Ent : Node_Id;
6484
6485          begin
6486             GNAT_Pragma;
6487             Check_VMS (N);
6488             Check_Arg_Count (1);
6489             Check_No_Identifiers;
6490             Check_Arg_Is_Local_Name (Arg1);
6491             Ent := Entity (Get_Pragma_Arg (Arg1));
6492
6493             --  Note: the implementation of the AST_Entry pragma could handle
6494             --  the entry family case fine, but for now we are consistent with
6495             --  the DEC rules, and do not allow the pragma, which of course
6496             --  has the effect of also forbidding the attribute.
6497
6498             if Ekind (Ent) /= E_Entry then
6499                Error_Pragma_Arg
6500                  ("pragma% argument must be simple entry name", Arg1);
6501
6502             elsif Is_AST_Entry (Ent) then
6503                Error_Pragma_Arg
6504                  ("duplicate % pragma for entry", Arg1);
6505
6506             elsif Has_Homonym (Ent) then
6507                Error_Pragma_Arg
6508                  ("pragma% argument cannot specify overloaded entry", Arg1);
6509
6510             else
6511                declare
6512                   FF : constant Entity_Id := First_Formal (Ent);
6513
6514                begin
6515                   if Present (FF) then
6516                      if Present (Next_Formal (FF)) then
6517                         Error_Pragma_Arg
6518                           ("entry for pragma% can have only one argument",
6519                            Arg1);
6520
6521                      elsif Parameter_Mode (FF) /= E_In_Parameter then
6522                         Error_Pragma_Arg
6523                           ("entry parameter for pragma% must have mode IN",
6524                            Arg1);
6525                      end if;
6526                   end if;
6527                end;
6528
6529                Set_Is_AST_Entry (Ent);
6530             end if;
6531          end AST_Entry;
6532
6533          ------------------
6534          -- Asynchronous --
6535          ------------------
6536
6537          --  pragma Asynchronous (LOCAL_NAME);
6538
6539          when Pragma_Asynchronous => Asynchronous : declare
6540             Nm     : Entity_Id;
6541             C_Ent  : Entity_Id;
6542             L      : List_Id;
6543             S      : Node_Id;
6544             N      : Node_Id;
6545             Formal : Entity_Id;
6546
6547             procedure Process_Async_Pragma;
6548             --  Common processing for procedure and access-to-procedure case
6549
6550             --------------------------
6551             -- Process_Async_Pragma --
6552             --------------------------
6553
6554             procedure Process_Async_Pragma is
6555             begin
6556                if No (L) then
6557                   Set_Is_Asynchronous (Nm);
6558                   return;
6559                end if;
6560
6561                --  The formals should be of mode IN (RM E.4.1(6))
6562
6563                S := First (L);
6564                while Present (S) loop
6565                   Formal := Defining_Identifier (S);
6566
6567                   if Nkind (Formal) = N_Defining_Identifier
6568                     and then Ekind (Formal) /= E_In_Parameter
6569                   then
6570                      Error_Pragma_Arg
6571                        ("pragma% procedure can only have IN parameter",
6572                         Arg1);
6573                   end if;
6574
6575                   Next (S);
6576                end loop;
6577
6578                Set_Is_Asynchronous (Nm);
6579             end Process_Async_Pragma;
6580
6581          --  Start of processing for pragma Asynchronous
6582
6583          begin
6584             Check_Ada_83_Warning;
6585             Check_No_Identifiers;
6586             Check_Arg_Count (1);
6587             Check_Arg_Is_Local_Name (Arg1);
6588
6589             if Debug_Flag_U then
6590                return;
6591             end if;
6592
6593             C_Ent := Cunit_Entity (Current_Sem_Unit);
6594             Analyze (Get_Pragma_Arg (Arg1));
6595             Nm := Entity (Get_Pragma_Arg (Arg1));
6596
6597             if not Is_Remote_Call_Interface (C_Ent)
6598               and then not Is_Remote_Types (C_Ent)
6599             then
6600                --  This pragma should only appear in an RCI or Remote Types
6601                --  unit (RM E.4.1(4)).
6602
6603                Error_Pragma
6604                  ("pragma% not in Remote_Call_Interface or " &
6605                   "Remote_Types unit");
6606             end if;
6607
6608             if Ekind (Nm) = E_Procedure
6609               and then Nkind (Parent (Nm)) = N_Procedure_Specification
6610             then
6611                if not Is_Remote_Call_Interface (Nm) then
6612                   Error_Pragma_Arg
6613                     ("pragma% cannot be applied on non-remote procedure",
6614                      Arg1);
6615                end if;
6616
6617                L := Parameter_Specifications (Parent (Nm));
6618                Process_Async_Pragma;
6619                return;
6620
6621             elsif Ekind (Nm) = E_Function then
6622                Error_Pragma_Arg
6623                  ("pragma% cannot be applied to function", Arg1);
6624
6625             elsif Is_Remote_Access_To_Subprogram_Type (Nm) then
6626                   if Is_Record_Type (Nm) then
6627
6628                   --  A record type that is the Equivalent_Type for a remote
6629                   --  access-to-subprogram type.
6630
6631                      N := Declaration_Node (Corresponding_Remote_Type (Nm));
6632
6633                   else
6634                      --  A non-expanded RAS type (distribution is not enabled)
6635
6636                      N := Declaration_Node (Nm);
6637                   end if;
6638
6639                if Nkind (N) = N_Full_Type_Declaration
6640                  and then Nkind (Type_Definition (N)) =
6641                                      N_Access_Procedure_Definition
6642                then
6643                   L := Parameter_Specifications (Type_Definition (N));
6644                   Process_Async_Pragma;
6645
6646                   if Is_Asynchronous (Nm)
6647                     and then Expander_Active
6648                     and then Get_PCS_Name /= Name_No_DSA
6649                   then
6650                      RACW_Type_Is_Asynchronous (Underlying_RACW_Type (Nm));
6651                   end if;
6652
6653                else
6654                   Error_Pragma_Arg
6655                     ("pragma% cannot reference access-to-function type",
6656                     Arg1);
6657                end if;
6658
6659             --  Only other possibility is Access-to-class-wide type
6660
6661             elsif Is_Access_Type (Nm)
6662               and then Is_Class_Wide_Type (Designated_Type (Nm))
6663             then
6664                Check_First_Subtype (Arg1);
6665                Set_Is_Asynchronous (Nm);
6666                if Expander_Active then
6667                   RACW_Type_Is_Asynchronous (Nm);
6668                end if;
6669
6670             else
6671                Error_Pragma_Arg ("inappropriate argument for pragma%", Arg1);
6672             end if;
6673          end Asynchronous;
6674
6675          ------------
6676          -- Atomic --
6677          ------------
6678
6679          --  pragma Atomic (LOCAL_NAME);
6680
6681          when Pragma_Atomic =>
6682             Process_Atomic_Shared_Volatile;
6683
6684          -----------------------
6685          -- Atomic_Components --
6686          -----------------------
6687
6688          --  pragma Atomic_Components (array_LOCAL_NAME);
6689
6690          --  This processing is shared by Volatile_Components
6691
6692          when Pragma_Atomic_Components   |
6693               Pragma_Volatile_Components =>
6694
6695          Atomic_Components : declare
6696             E_Id : Node_Id;
6697             E    : Entity_Id;
6698             D    : Node_Id;
6699             K    : Node_Kind;
6700
6701          begin
6702             Check_Ada_83_Warning;
6703             Check_No_Identifiers;
6704             Check_Arg_Count (1);
6705             Check_Arg_Is_Local_Name (Arg1);
6706             E_Id := Get_Pragma_Arg (Arg1);
6707
6708             if Etype (E_Id) = Any_Type then
6709                return;
6710             end if;
6711
6712             E := Entity (E_Id);
6713
6714             Check_Duplicate_Pragma (E);
6715
6716             if Rep_Item_Too_Early (E, N)
6717                  or else
6718                Rep_Item_Too_Late (E, N)
6719             then
6720                return;
6721             end if;
6722
6723             D := Declaration_Node (E);
6724             K := Nkind (D);
6725
6726             if (K = N_Full_Type_Declaration and then Is_Array_Type (E))
6727               or else
6728                 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
6729                    and then Nkind (D) = N_Object_Declaration
6730                    and then Nkind (Object_Definition (D)) =
6731                                        N_Constrained_Array_Definition)
6732             then
6733                --  The flag is set on the object, or on the base type
6734
6735                if Nkind (D) /= N_Object_Declaration then
6736                   E := Base_Type (E);
6737                end if;
6738
6739                Set_Has_Volatile_Components (E);
6740
6741                if Prag_Id = Pragma_Atomic_Components then
6742                   Set_Has_Atomic_Components (E);
6743                end if;
6744
6745             else
6746                Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
6747             end if;
6748          end Atomic_Components;
6749
6750          --------------------
6751          -- Attach_Handler --
6752          --------------------
6753
6754          --  pragma Attach_Handler (handler_NAME, EXPRESSION);
6755
6756          when Pragma_Attach_Handler =>
6757             Check_Ada_83_Warning;
6758             Check_No_Identifiers;
6759             Check_Arg_Count (2);
6760
6761             if No_Run_Time_Mode then
6762                Error_Msg_CRT ("Attach_Handler pragma", N);
6763             else
6764                Check_Interrupt_Or_Attach_Handler;
6765
6766                --  The expression that designates the attribute may depend on a
6767                --  discriminant, and is therefore a per- object expression, to
6768                --  be expanded in the init proc. If expansion is enabled, then
6769                --  perform semantic checks on a copy only.
6770
6771                if Expander_Active then
6772                   declare
6773                      Temp : constant Node_Id :=
6774                               New_Copy_Tree (Get_Pragma_Arg (Arg2));
6775                   begin
6776                      Set_Parent (Temp, N);
6777                      Preanalyze_And_Resolve (Temp, RTE (RE_Interrupt_ID));
6778                   end;
6779
6780                else
6781                   Analyze (Get_Pragma_Arg (Arg2));
6782                   Resolve (Get_Pragma_Arg (Arg2), RTE (RE_Interrupt_ID));
6783                end if;
6784
6785                Process_Interrupt_Or_Attach_Handler;
6786             end if;
6787
6788          --------------------
6789          -- C_Pass_By_Copy --
6790          --------------------
6791
6792          --  pragma C_Pass_By_Copy ([Max_Size =>] static_integer_EXPRESSION);
6793
6794          when Pragma_C_Pass_By_Copy => C_Pass_By_Copy : declare
6795             Arg : Node_Id;
6796             Val : Uint;
6797
6798          begin
6799             GNAT_Pragma;
6800             Check_Valid_Configuration_Pragma;
6801             Check_Arg_Count (1);
6802             Check_Optional_Identifier (Arg1, "max_size");
6803
6804             Arg := Get_Pragma_Arg (Arg1);
6805             Check_Arg_Is_Static_Expression (Arg, Any_Integer);
6806
6807             Val := Expr_Value (Arg);
6808
6809             if Val <= 0 then
6810                Error_Pragma_Arg
6811                  ("maximum size for pragma% must be positive", Arg1);
6812
6813             elsif UI_Is_In_Int_Range (Val) then
6814                Default_C_Record_Mechanism := UI_To_Int (Val);
6815
6816             --  If a giant value is given, Int'Last will do well enough.
6817             --  If sometime someone complains that a record larger than
6818             --  two gigabytes is not copied, we will worry about it then!
6819
6820             else
6821                Default_C_Record_Mechanism := Mechanism_Type'Last;
6822             end if;
6823          end C_Pass_By_Copy;
6824
6825          -----------
6826          -- Check --
6827          -----------
6828
6829          --  pragma Check ([Name    =>] IDENTIFIER,
6830          --                [Check   =>] Boolean_EXPRESSION
6831          --              [,[Message =>] String_EXPRESSION]);
6832
6833          when Pragma_Check => Check : declare
6834             Expr : Node_Id;
6835             Eloc : Source_Ptr;
6836
6837             Check_On : Boolean;
6838             --  Set True if category of assertions referenced by Name enabled
6839
6840          begin
6841             GNAT_Pragma;
6842             Check_At_Least_N_Arguments (2);
6843             Check_At_Most_N_Arguments (3);
6844             Check_Optional_Identifier (Arg1, Name_Name);
6845             Check_Optional_Identifier (Arg2, Name_Check);
6846
6847             if Arg_Count = 3 then
6848                Check_Optional_Identifier (Arg3, Name_Message);
6849                Analyze_And_Resolve (Get_Pragma_Arg (Arg3), Standard_String);
6850             end if;
6851
6852             Check_Arg_Is_Identifier (Arg1);
6853
6854             --  Indicate if pragma is enabled. The Original_Node reference here
6855             --  is to deal with pragma Assert rewritten as a Check pragma.
6856
6857             Check_On := Check_Enabled (Chars (Get_Pragma_Arg (Arg1)));
6858
6859             if Check_On then
6860                Set_SCO_Pragma_Enabled (Loc);
6861             end if;
6862
6863             --  If expansion is active and the check is not enabled then we
6864             --  rewrite the Check as:
6865
6866             --    if False and then condition then
6867             --       null;
6868             --    end if;
6869
6870             --  The reason we do this rewriting during semantic analysis rather
6871             --  than as part of normal expansion is that we cannot analyze and
6872             --  expand the code for the boolean expression directly, or it may
6873             --  cause insertion of actions that would escape the attempt to
6874             --  suppress the check code.
6875
6876             --  Note that the Sloc for the if statement corresponds to the
6877             --  argument condition, not the pragma itself. The reason for this
6878             --  is that we may generate a warning if the condition is False at
6879             --  compile time, and we do not want to delete this warning when we
6880             --  delete the if statement.
6881
6882             Expr := Get_Pragma_Arg (Arg2);
6883
6884             if Expander_Active and then not Check_On then
6885                Eloc := Sloc (Expr);
6886
6887                Rewrite (N,
6888                  Make_If_Statement (Eloc,
6889                    Condition =>
6890                      Make_And_Then (Eloc,
6891                        Left_Opnd  => New_Occurrence_Of (Standard_False, Eloc),
6892                        Right_Opnd => Expr),
6893                    Then_Statements => New_List (
6894                      Make_Null_Statement (Eloc))));
6895
6896                Analyze (N);
6897
6898             --  Check is active
6899
6900             else
6901                Analyze_And_Resolve (Expr, Any_Boolean);
6902             end if;
6903          end Check;
6904
6905          ----------------
6906          -- Check_Name --
6907          ----------------
6908
6909          --  pragma Check_Name (check_IDENTIFIER);
6910
6911          when Pragma_Check_Name =>
6912             Check_No_Identifiers;
6913             GNAT_Pragma;
6914             Check_Valid_Configuration_Pragma;
6915             Check_Arg_Count (1);
6916             Check_Arg_Is_Identifier (Arg1);
6917
6918             declare
6919                Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
6920
6921             begin
6922                for J in Check_Names.First .. Check_Names.Last loop
6923                   if Check_Names.Table (J) = Nam then
6924                      return;
6925                   end if;
6926                end loop;
6927
6928                Check_Names.Append (Nam);
6929             end;
6930
6931          ------------------
6932          -- Check_Policy --
6933          ------------------
6934
6935          --  pragma Check_Policy (
6936          --    [Name   =>] IDENTIFIER,
6937          --    [Policy =>] POLICY_IDENTIFIER);
6938
6939          --  POLICY_IDENTIFIER ::= ON | OFF | CHECK | IGNORE
6940
6941          --  Note: this is a configuration pragma, but it is allowed to appear
6942          --  anywhere else.
6943
6944          when Pragma_Check_Policy =>
6945             GNAT_Pragma;
6946             Check_Arg_Count (2);
6947             Check_Optional_Identifier (Arg1, Name_Name);
6948             Check_Optional_Identifier (Arg2, Name_Policy);
6949             Check_Arg_Is_One_Of
6950               (Arg2, Name_On, Name_Off, Name_Check, Name_Ignore);
6951
6952             --  A Check_Policy pragma can appear either as a configuration
6953             --  pragma, or in a declarative part or a package spec (see RM
6954             --  11.5(5) for rules for Suppress/Unsuppress which are also
6955             --  followed for Check_Policy).
6956
6957             if not Is_Configuration_Pragma then
6958                Check_Is_In_Decl_Part_Or_Package_Spec;
6959             end if;
6960
6961             Set_Next_Pragma (N, Opt.Check_Policy_List);
6962             Opt.Check_Policy_List := N;
6963
6964          ---------------------
6965          -- CIL_Constructor --
6966          ---------------------
6967
6968          --  pragma CIL_Constructor ([Entity =>] LOCAL_NAME);
6969
6970          --  Processing for this pragma is shared with Java_Constructor
6971
6972          -------------
6973          -- Comment --
6974          -------------
6975
6976          --  pragma Comment (static_string_EXPRESSION)
6977
6978          --  Processing for pragma Comment shares the circuitry for pragma
6979          --  Ident. The only differences are that Ident enforces a limit of 31
6980          --  characters on its argument, and also enforces limitations on
6981          --  placement for DEC compatibility. Pragma Comment shares neither of
6982          --  these restrictions.
6983
6984          -------------------
6985          -- Common_Object --
6986          -------------------
6987
6988          --  pragma Common_Object (
6989          --        [Internal =>] LOCAL_NAME
6990          --     [, [External =>] EXTERNAL_SYMBOL]
6991          --     [, [Size     =>] EXTERNAL_SYMBOL]);
6992
6993          --  Processing for this pragma is shared with Psect_Object
6994
6995          ------------------------
6996          -- Compile_Time_Error --
6997          ------------------------
6998
6999          --  pragma Compile_Time_Error
7000          --    (boolean_EXPRESSION, static_string_EXPRESSION);
7001
7002          when Pragma_Compile_Time_Error =>
7003             GNAT_Pragma;
7004             Process_Compile_Time_Warning_Or_Error;
7005
7006          --------------------------
7007          -- Compile_Time_Warning --
7008          --------------------------
7009
7010          --  pragma Compile_Time_Warning
7011          --    (boolean_EXPRESSION, static_string_EXPRESSION);
7012
7013          when Pragma_Compile_Time_Warning =>
7014             GNAT_Pragma;
7015             Process_Compile_Time_Warning_Or_Error;
7016
7017          -------------------
7018          -- Compiler_Unit --
7019          -------------------
7020
7021          when Pragma_Compiler_Unit =>
7022             GNAT_Pragma;
7023             Check_Arg_Count (0);
7024             Set_Is_Compiler_Unit (Get_Source_Unit (N));
7025
7026          -----------------------------
7027          -- Complete_Representation --
7028          -----------------------------
7029
7030          --  pragma Complete_Representation;
7031
7032          when Pragma_Complete_Representation =>
7033             GNAT_Pragma;
7034             Check_Arg_Count (0);
7035
7036             if Nkind (Parent (N)) /= N_Record_Representation_Clause then
7037                Error_Pragma
7038                  ("pragma & must appear within record representation clause");
7039             end if;
7040
7041          ----------------------------
7042          -- Complex_Representation --
7043          ----------------------------
7044
7045          --  pragma Complex_Representation ([Entity =>] LOCAL_NAME);
7046
7047          when Pragma_Complex_Representation => Complex_Representation : declare
7048             E_Id : Entity_Id;
7049             E    : Entity_Id;
7050             Ent  : Entity_Id;
7051
7052          begin
7053             GNAT_Pragma;
7054             Check_Arg_Count (1);
7055             Check_Optional_Identifier (Arg1, Name_Entity);
7056             Check_Arg_Is_Local_Name (Arg1);
7057             E_Id := Get_Pragma_Arg (Arg1);
7058
7059             if Etype (E_Id) = Any_Type then
7060                return;
7061             end if;
7062
7063             E := Entity (E_Id);
7064
7065             if not Is_Record_Type (E) then
7066                Error_Pragma_Arg
7067                  ("argument for pragma% must be record type", Arg1);
7068             end if;
7069
7070             Ent := First_Entity (E);
7071
7072             if No (Ent)
7073               or else No (Next_Entity (Ent))
7074               or else Present (Next_Entity (Next_Entity (Ent)))
7075               or else not Is_Floating_Point_Type (Etype (Ent))
7076               or else Etype (Ent) /= Etype (Next_Entity (Ent))
7077             then
7078                Error_Pragma_Arg
7079                  ("record for pragma% must have two fields of the same "
7080                   & "floating-point type", Arg1);
7081
7082             else
7083                Set_Has_Complex_Representation (Base_Type (E));
7084
7085                --  We need to treat the type has having a non-standard
7086                --  representation, for back-end purposes, even though in
7087                --  general a complex will have the default representation
7088                --  of a record with two real components.
7089
7090                Set_Has_Non_Standard_Rep (Base_Type (E));
7091             end if;
7092          end Complex_Representation;
7093
7094          -------------------------
7095          -- Component_Alignment --
7096          -------------------------
7097
7098          --  pragma Component_Alignment (
7099          --        [Form =>] ALIGNMENT_CHOICE
7100          --     [, [Name =>] type_LOCAL_NAME]);
7101          --
7102          --   ALIGNMENT_CHOICE ::=
7103          --     Component_Size
7104          --   | Component_Size_4
7105          --   | Storage_Unit
7106          --   | Default
7107
7108          when Pragma_Component_Alignment => Component_AlignmentP : declare
7109             Args  : Args_List (1 .. 2);
7110             Names : constant Name_List (1 .. 2) := (
7111                       Name_Form,
7112                       Name_Name);
7113
7114             Form  : Node_Id renames Args (1);
7115             Name  : Node_Id renames Args (2);
7116
7117             Atype : Component_Alignment_Kind;
7118             Typ   : Entity_Id;
7119
7120          begin
7121             GNAT_Pragma;
7122             Gather_Associations (Names, Args);
7123
7124             if No (Form) then
7125                Error_Pragma ("missing Form argument for pragma%");
7126             end if;
7127
7128             Check_Arg_Is_Identifier (Form);
7129
7130             --  Get proper alignment, note that Default = Component_Size on all
7131             --  machines we have so far, and we want to set this value rather
7132             --  than the default value to indicate that it has been explicitly
7133             --  set (and thus will not get overridden by the default component
7134             --  alignment for the current scope)
7135
7136             if Chars (Form) = Name_Component_Size then
7137                Atype := Calign_Component_Size;
7138
7139             elsif Chars (Form) = Name_Component_Size_4 then
7140                Atype := Calign_Component_Size_4;
7141
7142             elsif Chars (Form) = Name_Default then
7143                Atype := Calign_Component_Size;
7144
7145             elsif Chars (Form) = Name_Storage_Unit then
7146                Atype := Calign_Storage_Unit;
7147
7148             else
7149                Error_Pragma_Arg
7150                  ("invalid Form parameter for pragma%", Form);
7151             end if;
7152
7153             --  Case with no name, supplied, affects scope table entry
7154
7155             if No (Name) then
7156                Scope_Stack.Table
7157                  (Scope_Stack.Last).Component_Alignment_Default := Atype;
7158
7159             --  Case of name supplied
7160
7161             else
7162                Check_Arg_Is_Local_Name (Name);
7163                Find_Type (Name);
7164                Typ := Entity (Name);
7165
7166                if Typ = Any_Type
7167                  or else Rep_Item_Too_Early (Typ, N)
7168                then
7169                   return;
7170                else
7171                   Typ := Underlying_Type (Typ);
7172                end if;
7173
7174                if not Is_Record_Type (Typ)
7175                  and then not Is_Array_Type (Typ)
7176                then
7177                   Error_Pragma_Arg
7178                     ("Name parameter of pragma% must identify record or " &
7179                      "array type", Name);
7180                end if;
7181
7182                --  An explicit Component_Alignment pragma overrides an
7183                --  implicit pragma Pack, but not an explicit one.
7184
7185                if not Has_Pragma_Pack (Base_Type (Typ)) then
7186                   Set_Is_Packed (Base_Type (Typ), False);
7187                   Set_Component_Alignment (Base_Type (Typ), Atype);
7188                end if;
7189             end if;
7190          end Component_AlignmentP;
7191
7192          ----------------
7193          -- Controlled --
7194          ----------------
7195
7196          --  pragma Controlled (first_subtype_LOCAL_NAME);
7197
7198          when Pragma_Controlled => Controlled : declare
7199             Arg : Node_Id;
7200
7201          begin
7202             Check_No_Identifiers;
7203             Check_Arg_Count (1);
7204             Check_Arg_Is_Local_Name (Arg1);
7205             Arg := Get_Pragma_Arg (Arg1);
7206
7207             if not Is_Entity_Name (Arg)
7208               or else not Is_Access_Type (Entity (Arg))
7209             then
7210                Error_Pragma_Arg ("pragma% requires access type", Arg1);
7211             else
7212                Set_Has_Pragma_Controlled (Base_Type (Entity (Arg)));
7213             end if;
7214          end Controlled;
7215
7216          ----------------
7217          -- Convention --
7218          ----------------
7219
7220          --  pragma Convention ([Convention =>] convention_IDENTIFIER,
7221          --    [Entity =>] LOCAL_NAME);
7222
7223          when Pragma_Convention => Convention : declare
7224             C : Convention_Id;
7225             E : Entity_Id;
7226             pragma Warnings (Off, C);
7227             pragma Warnings (Off, E);
7228          begin
7229             Check_Arg_Order ((Name_Convention, Name_Entity));
7230             Check_Ada_83_Warning;
7231             Check_Arg_Count (2);
7232             Process_Convention (C, E);
7233          end Convention;
7234
7235          ---------------------------
7236          -- Convention_Identifier --
7237          ---------------------------
7238
7239          --  pragma Convention_Identifier ([Name =>] IDENTIFIER,
7240          --    [Convention =>] convention_IDENTIFIER);
7241
7242          when Pragma_Convention_Identifier => Convention_Identifier : declare
7243             Idnam : Name_Id;
7244             Cname : Name_Id;
7245
7246          begin
7247             GNAT_Pragma;
7248             Check_Arg_Order ((Name_Name, Name_Convention));
7249             Check_Arg_Count (2);
7250             Check_Optional_Identifier (Arg1, Name_Name);
7251             Check_Optional_Identifier (Arg2, Name_Convention);
7252             Check_Arg_Is_Identifier (Arg1);
7253             Check_Arg_Is_Identifier (Arg2);
7254             Idnam := Chars (Get_Pragma_Arg (Arg1));
7255             Cname := Chars (Get_Pragma_Arg (Arg2));
7256
7257             if Is_Convention_Name (Cname) then
7258                Record_Convention_Identifier
7259                  (Idnam, Get_Convention_Id (Cname));
7260             else
7261                Error_Pragma_Arg
7262                  ("second arg for % pragma must be convention", Arg2);
7263             end if;
7264          end Convention_Identifier;
7265
7266          ---------------
7267          -- CPP_Class --
7268          ---------------
7269
7270          --  pragma CPP_Class ([Entity =>] local_NAME)
7271
7272          when Pragma_CPP_Class => CPP_Class : declare
7273             Arg : Node_Id;
7274             Typ : Entity_Id;
7275
7276          begin
7277             if Warn_On_Obsolescent_Feature then
7278                Error_Msg_N
7279                  ("'G'N'A'T pragma cpp'_class is now obsolete; replace it" &
7280                   " by pragma import?", N);
7281             end if;
7282
7283             GNAT_Pragma;
7284             Check_Arg_Count (1);
7285             Check_Optional_Identifier (Arg1, Name_Entity);
7286             Check_Arg_Is_Local_Name (Arg1);
7287
7288             Arg := Get_Pragma_Arg (Arg1);
7289             Analyze (Arg);
7290
7291             if Etype (Arg) = Any_Type then
7292                return;
7293             end if;
7294
7295             if not Is_Entity_Name (Arg)
7296               or else not Is_Type (Entity (Arg))
7297             then
7298                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
7299             end if;
7300
7301             Typ := Entity (Arg);
7302
7303             if not Is_Tagged_Type (Typ) then
7304                Error_Pragma_Arg ("pragma% applicable to tagged types ", Arg1);
7305             end if;
7306
7307             --  Types treated as CPP classes must be declared limited (note:
7308             --  this used to be a warning but there is no real benefit to it
7309             --  since we did effectively intend to treat the type as limited
7310             --  anyway).
7311
7312             if not Is_Limited_Type (Typ) then
7313                Error_Msg_N
7314                  ("imported 'C'P'P type must be limited",
7315                   Get_Pragma_Arg (Arg1));
7316             end if;
7317
7318             Set_Is_CPP_Class      (Typ);
7319             Set_Convention        (Typ, Convention_CPP);
7320
7321             --  Imported CPP types must not have discriminants (because C++
7322             --  classes do not have discriminants).
7323
7324             if Has_Discriminants (Typ) then
7325                Error_Msg_N
7326                  ("imported 'C'P'P type cannot have discriminants",
7327                   First (Discriminant_Specifications
7328                           (Declaration_Node (Typ))));
7329             end if;
7330
7331             --  Components of imported CPP types must not have default
7332             --  expressions because the constructor (if any) is in the
7333             --  C++ side.
7334
7335             if Is_Incomplete_Or_Private_Type (Typ)
7336               and then No (Underlying_Type (Typ))
7337             then
7338                --  It should be an error to apply pragma CPP to a private
7339                --  type if the underlying type is not visible (as it is
7340                --  for any representation item). For now, for backward
7341                --  compatibility we do nothing but we cannot check components
7342                --  because they are not available at this stage. All this code
7343                --  will be removed when we cleanup this obsolete GNAT pragma???
7344
7345                null;
7346
7347             else
7348                declare
7349                   Tdef  : constant Node_Id :=
7350                             Type_Definition (Declaration_Node (Typ));
7351                   Clist : Node_Id;
7352                   Comp  : Node_Id;
7353
7354                begin
7355                   if Nkind (Tdef) = N_Record_Definition then
7356                      Clist := Component_List (Tdef);
7357                   else
7358                      pragma Assert (Nkind (Tdef) = N_Derived_Type_Definition);
7359                      Clist := Component_List (Record_Extension_Part (Tdef));
7360                   end if;
7361
7362                   if Present (Clist) then
7363                      Comp := First (Component_Items (Clist));
7364                      while Present (Comp) loop
7365                         if Present (Expression (Comp)) then
7366                            Error_Msg_N
7367                              ("component of imported 'C'P'P type cannot have" &
7368                               " default expression", Expression (Comp));
7369                         end if;
7370
7371                         Next (Comp);
7372                      end loop;
7373                   end if;
7374                end;
7375             end if;
7376          end CPP_Class;
7377
7378          ---------------------
7379          -- CPP_Constructor --
7380          ---------------------
7381
7382          --  pragma CPP_Constructor ([Entity =>] LOCAL_NAME
7383          --    [, [External_Name =>] static_string_EXPRESSION ]
7384          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
7385
7386          when Pragma_CPP_Constructor => CPP_Constructor : declare
7387             Elmt    : Elmt_Id;
7388             Id      : Entity_Id;
7389             Def_Id  : Entity_Id;
7390             Tag_Typ : Entity_Id;
7391
7392          begin
7393             GNAT_Pragma;
7394             Check_At_Least_N_Arguments (1);
7395             Check_At_Most_N_Arguments (3);
7396             Check_Optional_Identifier (Arg1, Name_Entity);
7397             Check_Arg_Is_Local_Name (Arg1);
7398
7399             Id := Get_Pragma_Arg (Arg1);
7400             Find_Program_Unit_Name (Id);
7401
7402             --  If we did not find the name, we are done
7403
7404             if Etype (Id) = Any_Type then
7405                return;
7406             end if;
7407
7408             Def_Id := Entity (Id);
7409
7410             --  Check if already defined as constructor
7411
7412             if Is_Constructor (Def_Id) then
7413                Error_Msg_N
7414                  ("?duplicate argument for pragma 'C'P'P_Constructor", Arg1);
7415                return;
7416             end if;
7417
7418             if Ekind (Def_Id) = E_Function
7419               and then (Is_CPP_Class (Etype (Def_Id))
7420                          or else (Is_Class_Wide_Type (Etype (Def_Id))
7421                                    and then
7422                                   Is_CPP_Class (Root_Type (Etype (Def_Id)))))
7423             then
7424                if Arg_Count >= 2 then
7425                   Set_Imported (Def_Id);
7426                   Set_Is_Public (Def_Id);
7427                   Process_Interface_Name (Def_Id, Arg2, Arg3);
7428                end if;
7429
7430                Set_Has_Completion (Def_Id);
7431                Set_Is_Constructor (Def_Id);
7432
7433                --  Imported C++ constructors are not dispatching primitives
7434                --  because in C++ they don't have a dispatch table slot.
7435                --  However, in Ada the constructor has the profile of a
7436                --  function that returns a tagged type and therefore it has
7437                --  been treated as a primitive operation during semantic
7438                --  analysis. We now remove it from the list of primitive
7439                --  operations of the type.
7440
7441                if Is_Tagged_Type (Etype (Def_Id))
7442                  and then not Is_Class_Wide_Type (Etype (Def_Id))
7443                then
7444                   pragma Assert (Is_Dispatching_Operation (Def_Id));
7445                   Tag_Typ := Etype (Def_Id);
7446
7447                   Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
7448                   while Present (Elmt) and then Node (Elmt) /= Def_Id loop
7449                      Next_Elmt (Elmt);
7450                   end loop;
7451
7452                   Remove_Elmt (Primitive_Operations (Tag_Typ), Elmt);
7453                   Set_Is_Dispatching_Operation (Def_Id, False);
7454                end if;
7455
7456                --  For backward compatibility, if the constructor returns a
7457                --  class wide type, and we internally change the return type to
7458                --  the corresponding root type.
7459
7460                if Is_Class_Wide_Type (Etype (Def_Id)) then
7461                   Set_Etype (Def_Id, Root_Type (Etype (Def_Id)));
7462                end if;
7463             else
7464                Error_Pragma_Arg
7465                  ("pragma% requires function returning a 'C'P'P_Class type",
7466                    Arg1);
7467             end if;
7468          end CPP_Constructor;
7469
7470          -----------------
7471          -- CPP_Virtual --
7472          -----------------
7473
7474          when Pragma_CPP_Virtual => CPP_Virtual : declare
7475          begin
7476             GNAT_Pragma;
7477
7478             if Warn_On_Obsolescent_Feature then
7479                Error_Msg_N
7480                  ("'G'N'A'T pragma cpp'_virtual is now obsolete and has " &
7481                   "no effect?", N);
7482             end if;
7483          end CPP_Virtual;
7484
7485          ----------------
7486          -- CPP_Vtable --
7487          ----------------
7488
7489          when Pragma_CPP_Vtable => CPP_Vtable : declare
7490          begin
7491             GNAT_Pragma;
7492
7493             if Warn_On_Obsolescent_Feature then
7494                Error_Msg_N
7495                  ("'G'N'A'T pragma cpp'_vtable is now obsolete and has " &
7496                   "no effect?", N);
7497             end if;
7498          end CPP_Vtable;
7499
7500          ---------
7501          -- CPU --
7502          ---------
7503
7504          --  pragma CPU (EXPRESSION);
7505
7506          when Pragma_CPU => CPU : declare
7507             P   : constant Node_Id := Parent (N);
7508             Arg : Node_Id;
7509
7510          begin
7511             Ada_2012_Pragma;
7512             Check_No_Identifiers;
7513             Check_Arg_Count (1);
7514
7515             --  Subprogram case
7516
7517             if Nkind (P) = N_Subprogram_Body then
7518                Check_In_Main_Program;
7519
7520                Arg := Get_Pragma_Arg (Arg1);
7521                Analyze_And_Resolve (Arg, Any_Integer);
7522
7523                --  Must be static
7524
7525                if not Is_Static_Expression (Arg) then
7526                   Flag_Non_Static_Expr
7527                     ("main subprogram affinity is not static!", Arg);
7528                   raise Pragma_Exit;
7529
7530                --  If constraint error, then we already signalled an error
7531
7532                elsif Raises_Constraint_Error (Arg) then
7533                   null;
7534
7535                --  Otherwise check in range
7536
7537                else
7538                   declare
7539                      CPU_Id : constant Entity_Id := RTE (RE_CPU_Range);
7540                      --  This is the entity System.Multiprocessors.CPU_Range;
7541
7542                      Val : constant Uint := Expr_Value (Arg);
7543
7544                   begin
7545                      if Val < Expr_Value (Type_Low_Bound (CPU_Id))
7546                           or else
7547                         Val > Expr_Value (Type_High_Bound (CPU_Id))
7548                      then
7549                         Error_Pragma_Arg
7550                           ("main subprogram CPU is out of range", Arg1);
7551                      end if;
7552                   end;
7553                end if;
7554
7555                Set_Main_CPU
7556                     (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
7557
7558             --  Task case
7559
7560             elsif Nkind (P) = N_Task_Definition then
7561                Arg := Get_Pragma_Arg (Arg1);
7562
7563                --  The expression must be analyzed in the special manner
7564                --  described in "Handling of Default and Per-Object
7565                --  Expressions" in sem.ads.
7566
7567                Preanalyze_Spec_Expression (Arg, RTE (RE_CPU_Range));
7568
7569             --  Anything else is incorrect
7570
7571             else
7572                Pragma_Misplaced;
7573             end if;
7574
7575             if Has_Pragma_CPU (P) then
7576                Error_Pragma ("duplicate pragma% not allowed");
7577             else
7578                Set_Has_Pragma_CPU (P, True);
7579
7580                if Nkind (P) = N_Task_Definition then
7581                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
7582                end if;
7583             end if;
7584          end CPU;
7585
7586          -----------
7587          -- Debug --
7588          -----------
7589
7590          --  pragma Debug ([boolean_EXPRESSION,] PROCEDURE_CALL_STATEMENT);
7591
7592          when Pragma_Debug => Debug : declare
7593             Cond : Node_Id;
7594             Call : Node_Id;
7595
7596          begin
7597             GNAT_Pragma;
7598
7599             Cond :=
7600               New_Occurrence_Of
7601                 (Boolean_Literals (Debug_Pragmas_Enabled and Expander_Active),
7602                  Loc);
7603
7604             if Arg_Count = 2 then
7605                Cond :=
7606                  Make_And_Then (Loc,
7607                    Left_Opnd  => Relocate_Node (Cond),
7608                    Right_Opnd => Get_Pragma_Arg (Arg1));
7609                Call := Get_Pragma_Arg (Arg2);
7610             else
7611                Call := Get_Pragma_Arg (Arg1);
7612             end if;
7613
7614             if Nkind_In (Call,
7615                  N_Indexed_Component,
7616                  N_Function_Call,
7617                  N_Identifier,
7618                  N_Selected_Component)
7619             then
7620                --  If this pragma Debug comes from source, its argument was
7621                --  parsed as a name form (which is syntactically identical).
7622                --  Change it to a procedure call statement now.
7623
7624                Change_Name_To_Procedure_Call_Statement (Call);
7625
7626             elsif Nkind (Call) = N_Procedure_Call_Statement then
7627
7628                --  Already in the form of a procedure call statement: nothing
7629                --  to do (could happen in case of an internally generated
7630                --  pragma Debug).
7631
7632                null;
7633
7634             else
7635                --  All other cases: diagnose error
7636
7637                Error_Msg
7638                  ("argument of pragma% is not procedure call", Sloc (Call));
7639                return;
7640             end if;
7641
7642             --  Rewrite into a conditional with an appropriate condition. We
7643             --  wrap the procedure call in a block so that overhead from e.g.
7644             --  use of the secondary stack does not generate execution overhead
7645             --  for suppressed conditions.
7646
7647             Rewrite (N, Make_Implicit_If_Statement (N,
7648               Condition => Cond,
7649                  Then_Statements => New_List (
7650                    Make_Block_Statement (Loc,
7651                      Handled_Statement_Sequence =>
7652                        Make_Handled_Sequence_Of_Statements (Loc,
7653                          Statements => New_List (Relocate_Node (Call)))))));
7654             Analyze (N);
7655          end Debug;
7656
7657          ------------------
7658          -- Debug_Policy --
7659          ------------------
7660
7661          --  pragma Debug_Policy (Check | Ignore)
7662
7663          when Pragma_Debug_Policy =>
7664             GNAT_Pragma;
7665             Check_Arg_Count (1);
7666             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Ignore);
7667             Debug_Pragmas_Enabled :=
7668               Chars (Get_Pragma_Arg (Arg1)) = Name_Check;
7669
7670          ---------------------
7671          -- Detect_Blocking --
7672          ---------------------
7673
7674          --  pragma Detect_Blocking;
7675
7676          when Pragma_Detect_Blocking =>
7677             Ada_2005_Pragma;
7678             Check_Arg_Count (0);
7679             Check_Valid_Configuration_Pragma;
7680             Detect_Blocking := True;
7681
7682          --------------------------
7683          -- Default_Storage_Pool --
7684          --------------------------
7685
7686          --  pragma Default_Storage_Pool (storage_pool_NAME | null);
7687
7688          when Pragma_Default_Storage_Pool =>
7689             Ada_2012_Pragma;
7690             Check_Arg_Count (1);
7691
7692             --  Default_Storage_Pool can appear as a configuration pragma, or
7693             --  in a declarative part or a package spec.
7694
7695             if not Is_Configuration_Pragma then
7696                Check_Is_In_Decl_Part_Or_Package_Spec;
7697             end if;
7698
7699             --  Case of Default_Storage_Pool (null);
7700
7701             if Nkind (Expression (Arg1)) = N_Null then
7702                Analyze (Expression (Arg1));
7703
7704                --  This is an odd case, this is not really an expression, so
7705                --  we don't have a type for it. So just set the type to Empty.
7706
7707                Set_Etype (Expression (Arg1), Empty);
7708
7709             --  Case of Default_Storage_Pool (storage_pool_NAME);
7710
7711             else
7712                --  If it's a configuration pragma, then the only allowed
7713                --  argument is "null".
7714
7715                if Is_Configuration_Pragma then
7716                   Error_Pragma_Arg ("NULL expected", Arg1);
7717                end if;
7718
7719                --  The expected type for a non-"null" argument is
7720                --  Root_Storage_Pool'Class.
7721
7722                Analyze_And_Resolve
7723                  (Get_Pragma_Arg (Arg1),
7724                   Typ => Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
7725             end if;
7726
7727             --  Finally, record the pool name (or null). Freeze.Freeze_Entity
7728             --  for an access type will use this information to set the
7729             --  appropriate attributes of the access type.
7730
7731             Default_Pool := Expression (Arg1);
7732
7733          ---------------
7734          -- Dimension --
7735          ---------------
7736
7737          when Pragma_Dimension =>
7738             GNAT_Pragma;
7739             Check_Arg_Count (4);
7740             Check_No_Identifiers;
7741             Check_Arg_Is_Local_Name (Arg1);
7742
7743             if not Is_Type (Arg1) then
7744                Error_Pragma ("first argument for pragma% must be subtype");
7745             end if;
7746
7747             Check_Arg_Is_Static_Expression (Arg2, Standard_Integer);
7748             Check_Arg_Is_Static_Expression (Arg3, Standard_Integer);
7749             Check_Arg_Is_Static_Expression (Arg4, Standard_Integer);
7750
7751          -------------------
7752          -- Discard_Names --
7753          -------------------
7754
7755          --  pragma Discard_Names [([On =>] LOCAL_NAME)];
7756
7757          when Pragma_Discard_Names => Discard_Names : declare
7758             E    : Entity_Id;
7759             E_Id : Entity_Id;
7760
7761          begin
7762             Check_Ada_83_Warning;
7763
7764             --  Deal with configuration pragma case
7765
7766             if Arg_Count = 0 and then Is_Configuration_Pragma then
7767                Global_Discard_Names := True;
7768                return;
7769
7770             --  Otherwise, check correct appropriate context
7771
7772             else
7773                Check_Is_In_Decl_Part_Or_Package_Spec;
7774
7775                if Arg_Count = 0 then
7776
7777                   --  If there is no parameter, then from now on this pragma
7778                   --  applies to any enumeration, exception or tagged type
7779                   --  defined in the current declarative part, and recursively
7780                   --  to any nested scope.
7781
7782                   Set_Discard_Names (Current_Scope);
7783                   return;
7784
7785                else
7786                   Check_Arg_Count (1);
7787                   Check_Optional_Identifier (Arg1, Name_On);
7788                   Check_Arg_Is_Local_Name (Arg1);
7789
7790                   E_Id := Get_Pragma_Arg (Arg1);
7791
7792                   if Etype (E_Id) = Any_Type then
7793                      return;
7794                   else
7795                      E := Entity (E_Id);
7796                   end if;
7797
7798                   if (Is_First_Subtype (E)
7799                       and then
7800                         (Is_Enumeration_Type (E) or else Is_Tagged_Type (E)))
7801                     or else Ekind (E) = E_Exception
7802                   then
7803                      Set_Discard_Names (E);
7804                   else
7805                      Error_Pragma_Arg
7806                        ("inappropriate entity for pragma%", Arg1);
7807                   end if;
7808
7809                end if;
7810             end if;
7811          end Discard_Names;
7812
7813          ---------------
7814          -- Elaborate --
7815          ---------------
7816
7817          --  pragma Elaborate (library_unit_NAME {, library_unit_NAME});
7818
7819          when Pragma_Elaborate => Elaborate : declare
7820             Arg   : Node_Id;
7821             Citem : Node_Id;
7822
7823          begin
7824             --  Pragma must be in context items list of a compilation unit
7825
7826             if not Is_In_Context_Clause then
7827                Pragma_Misplaced;
7828             end if;
7829
7830             --  Must be at least one argument
7831
7832             if Arg_Count = 0 then
7833                Error_Pragma ("pragma% requires at least one argument");
7834             end if;
7835
7836             --  In Ada 83 mode, there can be no items following it in the
7837             --  context list except other pragmas and implicit with clauses
7838             --  (e.g. those added by use of Rtsfind). In Ada 95 mode, this
7839             --  placement rule does not apply.
7840
7841             if Ada_Version = Ada_83 and then Comes_From_Source (N) then
7842                Citem := Next (N);
7843                while Present (Citem) loop
7844                   if Nkind (Citem) = N_Pragma
7845                     or else (Nkind (Citem) = N_With_Clause
7846                               and then Implicit_With (Citem))
7847                   then
7848                      null;
7849                   else
7850                      Error_Pragma
7851                        ("(Ada 83) pragma% must be at end of context clause");
7852                   end if;
7853
7854                   Next (Citem);
7855                end loop;
7856             end if;
7857
7858             --  Finally, the arguments must all be units mentioned in a with
7859             --  clause in the same context clause. Note we already checked (in
7860             --  Par.Prag) that the arguments are all identifiers or selected
7861             --  components.
7862
7863             Arg := Arg1;
7864             Outer : while Present (Arg) loop
7865                Citem := First (List_Containing (N));
7866                Inner : while Citem /= N loop
7867                   if Nkind (Citem) = N_With_Clause
7868                     and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
7869                   then
7870                      Set_Elaborate_Present (Citem, True);
7871                      Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
7872                      Generate_Reference (Entity (Name (Citem)), Citem);
7873
7874                      --  With the pragma present, elaboration calls on
7875                      --  subprograms from the named unit need no further
7876                      --  checks, as long as the pragma appears in the current
7877                      --  compilation unit. If the pragma appears in some unit
7878                      --  in the context, there might still be a need for an
7879                      --  Elaborate_All_Desirable from the current compilation
7880                      --  to the named unit, so we keep the check enabled.
7881
7882                      if In_Extended_Main_Source_Unit (N) then
7883                         Set_Suppress_Elaboration_Warnings
7884                           (Entity (Name (Citem)));
7885                      end if;
7886
7887                      exit Inner;
7888                   end if;
7889
7890                   Next (Citem);
7891                end loop Inner;
7892
7893                if Citem = N then
7894                   Error_Pragma_Arg
7895                     ("argument of pragma% is not with'ed unit", Arg);
7896                end if;
7897
7898                Next (Arg);
7899             end loop Outer;
7900
7901             --  Give a warning if operating in static mode with -gnatwl
7902             --  (elaboration warnings enabled) switch set.
7903
7904             if Elab_Warnings and not Dynamic_Elaboration_Checks then
7905                Error_Msg_N
7906                  ("?use of pragma Elaborate may not be safe", N);
7907                Error_Msg_N
7908                  ("?use pragma Elaborate_All instead if possible", N);
7909             end if;
7910          end Elaborate;
7911
7912          -------------------
7913          -- Elaborate_All --
7914          -------------------
7915
7916          --  pragma Elaborate_All (library_unit_NAME {, library_unit_NAME});
7917
7918          when Pragma_Elaborate_All => Elaborate_All : declare
7919             Arg   : Node_Id;
7920             Citem : Node_Id;
7921
7922          begin
7923             Check_Ada_83_Warning;
7924
7925             --  Pragma must be in context items list of a compilation unit
7926
7927             if not Is_In_Context_Clause then
7928                Pragma_Misplaced;
7929             end if;
7930
7931             --  Must be at least one argument
7932
7933             if Arg_Count = 0 then
7934                Error_Pragma ("pragma% requires at least one argument");
7935             end if;
7936
7937             --  Note: unlike pragma Elaborate, pragma Elaborate_All does not
7938             --  have to appear at the end of the context clause, but may
7939             --  appear mixed in with other items, even in Ada 83 mode.
7940
7941             --  Final check: the arguments must all be units mentioned in
7942             --  a with clause in the same context clause. Note that we
7943             --  already checked (in Par.Prag) that all the arguments are
7944             --  either identifiers or selected components.
7945
7946             Arg := Arg1;
7947             Outr : while Present (Arg) loop
7948                Citem := First (List_Containing (N));
7949                Innr : while Citem /= N loop
7950                   if Nkind (Citem) = N_With_Clause
7951                     and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
7952                   then
7953                      Set_Elaborate_All_Present (Citem, True);
7954                      Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
7955
7956                      --  Suppress warnings and elaboration checks on the named
7957                      --  unit if the pragma is in the current compilation, as
7958                      --  for pragma Elaborate.
7959
7960                      if In_Extended_Main_Source_Unit (N) then
7961                         Set_Suppress_Elaboration_Warnings
7962                           (Entity (Name (Citem)));
7963                      end if;
7964                      exit Innr;
7965                   end if;
7966
7967                   Next (Citem);
7968                end loop Innr;
7969
7970                if Citem = N then
7971                   Set_Error_Posted (N);
7972                   Error_Pragma_Arg
7973                     ("argument of pragma% is not with'ed unit", Arg);
7974                end if;
7975
7976                Next (Arg);
7977             end loop Outr;
7978          end Elaborate_All;
7979
7980          --------------------
7981          -- Elaborate_Body --
7982          --------------------
7983
7984          --  pragma Elaborate_Body [( library_unit_NAME )];
7985
7986          when Pragma_Elaborate_Body => Elaborate_Body : declare
7987             Cunit_Node : Node_Id;
7988             Cunit_Ent  : Entity_Id;
7989
7990          begin
7991             Check_Ada_83_Warning;
7992             Check_Valid_Library_Unit_Pragma;
7993
7994             if Nkind (N) = N_Null_Statement then
7995                return;
7996             end if;
7997
7998             Cunit_Node := Cunit (Current_Sem_Unit);
7999             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
8000
8001             if Nkind_In (Unit (Cunit_Node), N_Package_Body,
8002                                             N_Subprogram_Body)
8003             then
8004                Error_Pragma ("pragma% must refer to a spec, not a body");
8005             else
8006                Set_Body_Required (Cunit_Node, True);
8007                Set_Has_Pragma_Elaborate_Body (Cunit_Ent);
8008
8009                --  If we are in dynamic elaboration mode, then we suppress
8010                --  elaboration warnings for the unit, since it is definitely
8011                --  fine NOT to do dynamic checks at the first level (and such
8012                --  checks will be suppressed because no elaboration boolean
8013                --  is created for Elaborate_Body packages).
8014
8015                --  But in the static model of elaboration, Elaborate_Body is
8016                --  definitely NOT good enough to ensure elaboration safety on
8017                --  its own, since the body may WITH other units that are not
8018                --  safe from an elaboration point of view, so a client must
8019                --  still do an Elaborate_All on such units.
8020
8021                --  Debug flag -gnatdD restores the old behavior of 3.13, where
8022                --  Elaborate_Body always suppressed elab warnings.
8023
8024                if Dynamic_Elaboration_Checks or Debug_Flag_DD then
8025                   Set_Suppress_Elaboration_Warnings (Cunit_Ent);
8026                end if;
8027             end if;
8028          end Elaborate_Body;
8029
8030          ------------------------
8031          -- Elaboration_Checks --
8032          ------------------------
8033
8034          --  pragma Elaboration_Checks (Static | Dynamic);
8035
8036          when Pragma_Elaboration_Checks =>
8037             GNAT_Pragma;
8038             Check_Arg_Count (1);
8039             Check_Arg_Is_One_Of (Arg1, Name_Static, Name_Dynamic);
8040             Dynamic_Elaboration_Checks :=
8041               (Chars (Get_Pragma_Arg (Arg1)) = Name_Dynamic);
8042
8043          ---------------
8044          -- Eliminate --
8045          ---------------
8046
8047          --  pragma Eliminate (
8048          --      [Unit_Name  =>] IDENTIFIER | SELECTED_COMPONENT,
8049          --    [,[Entity     =>] IDENTIFIER |
8050          --                      SELECTED_COMPONENT |
8051          --                      STRING_LITERAL]
8052          --    [,                OVERLOADING_RESOLUTION]);
8053
8054          --  OVERLOADING_RESOLUTION ::= PARAMETER_AND_RESULT_TYPE_PROFILE |
8055          --                             SOURCE_LOCATION
8056
8057          --  PARAMETER_AND_RESULT_TYPE_PROFILE ::= PROCEDURE_PROFILE |
8058          --                                        FUNCTION_PROFILE
8059
8060          --  PROCEDURE_PROFILE ::= Parameter_Types => PARAMETER_TYPES
8061
8062          --  FUNCTION_PROFILE ::= [Parameter_Types => PARAMETER_TYPES,]
8063          --                       Result_Type => result_SUBTYPE_NAME]
8064
8065          --  PARAMETER_TYPES ::= (SUBTYPE_NAME {, SUBTYPE_NAME})
8066          --  SUBTYPE_NAME    ::= STRING_LITERAL
8067
8068          --  SOURCE_LOCATION ::= Source_Location => SOURCE_TRACE
8069          --  SOURCE_TRACE    ::= STRING_LITERAL
8070
8071          when Pragma_Eliminate => Eliminate : declare
8072             Args  : Args_List (1 .. 5);
8073             Names : constant Name_List (1 .. 5) := (
8074                       Name_Unit_Name,
8075                       Name_Entity,
8076                       Name_Parameter_Types,
8077                       Name_Result_Type,
8078                       Name_Source_Location);
8079
8080             Unit_Name       : Node_Id renames Args (1);
8081             Entity          : Node_Id renames Args (2);
8082             Parameter_Types : Node_Id renames Args (3);
8083             Result_Type     : Node_Id renames Args (4);
8084             Source_Location : Node_Id renames Args (5);
8085
8086          begin
8087             GNAT_Pragma;
8088             Check_Valid_Configuration_Pragma;
8089             Gather_Associations (Names, Args);
8090
8091             if No (Unit_Name) then
8092                Error_Pragma ("missing Unit_Name argument for pragma%");
8093             end if;
8094
8095             if No (Entity)
8096               and then (Present (Parameter_Types)
8097                           or else
8098                         Present (Result_Type)
8099                           or else
8100                         Present (Source_Location))
8101             then
8102                Error_Pragma ("missing Entity argument for pragma%");
8103             end if;
8104
8105             if (Present (Parameter_Types)
8106                   or else
8107                 Present (Result_Type))
8108               and then
8109                 Present (Source_Location)
8110             then
8111                Error_Pragma
8112                  ("parameter profile and source location cannot " &
8113                   "be used together in pragma%");
8114             end if;
8115
8116             Process_Eliminate_Pragma
8117               (N,
8118                Unit_Name,
8119                Entity,
8120                Parameter_Types,
8121                Result_Type,
8122                Source_Location);
8123          end Eliminate;
8124
8125          ------------
8126          -- Export --
8127          ------------
8128
8129          --  pragma Export (
8130          --    [   Convention    =>] convention_IDENTIFIER,
8131          --    [   Entity        =>] local_NAME
8132          --    [, [External_Name =>] static_string_EXPRESSION ]
8133          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
8134
8135          when Pragma_Export => Export : declare
8136             C      : Convention_Id;
8137             Def_Id : Entity_Id;
8138
8139             pragma Warnings (Off, C);
8140
8141          begin
8142             Check_Ada_83_Warning;
8143             Check_Arg_Order
8144               ((Name_Convention,
8145                 Name_Entity,
8146                 Name_External_Name,
8147                 Name_Link_Name));
8148             Check_At_Least_N_Arguments (2);
8149             Check_At_Most_N_Arguments  (4);
8150             Process_Convention (C, Def_Id);
8151
8152             if Ekind (Def_Id) /= E_Constant then
8153                Note_Possible_Modification
8154                  (Get_Pragma_Arg (Arg2), Sure => False);
8155             end if;
8156
8157             Process_Interface_Name (Def_Id, Arg3, Arg4);
8158             Set_Exported (Def_Id, Arg2);
8159
8160             --  If the entity is a deferred constant, propagate the information
8161             --  to the full view, because gigi elaborates the full view only.
8162
8163             if Ekind (Def_Id) = E_Constant
8164               and then Present (Full_View (Def_Id))
8165             then
8166                declare
8167                   Id2 : constant Entity_Id := Full_View (Def_Id);
8168                begin
8169                   Set_Is_Exported    (Id2, Is_Exported          (Def_Id));
8170                   Set_First_Rep_Item (Id2, First_Rep_Item       (Def_Id));
8171                   Set_Interface_Name (Id2, Einfo.Interface_Name (Def_Id));
8172                end;
8173             end if;
8174          end Export;
8175
8176          ----------------------
8177          -- Export_Exception --
8178          ----------------------
8179
8180          --  pragma Export_Exception (
8181          --        [Internal         =>] LOCAL_NAME
8182          --     [, [External         =>] EXTERNAL_SYMBOL]
8183          --     [, [Form     =>] Ada | VMS]
8184          --     [, [Code     =>] static_integer_EXPRESSION]);
8185
8186          when Pragma_Export_Exception => Export_Exception : declare
8187             Args  : Args_List (1 .. 4);
8188             Names : constant Name_List (1 .. 4) := (
8189                       Name_Internal,
8190                       Name_External,
8191                       Name_Form,
8192                       Name_Code);
8193
8194             Internal : Node_Id renames Args (1);
8195             External : Node_Id renames Args (2);
8196             Form     : Node_Id renames Args (3);
8197             Code     : Node_Id renames Args (4);
8198
8199          begin
8200             GNAT_Pragma;
8201
8202             if Inside_A_Generic then
8203                Error_Pragma ("pragma% cannot be used for generic entities");
8204             end if;
8205
8206             Gather_Associations (Names, Args);
8207             Process_Extended_Import_Export_Exception_Pragma (
8208               Arg_Internal => Internal,
8209               Arg_External => External,
8210               Arg_Form     => Form,
8211               Arg_Code     => Code);
8212
8213             if not Is_VMS_Exception (Entity (Internal)) then
8214                Set_Exported (Entity (Internal), Internal);
8215             end if;
8216          end Export_Exception;
8217
8218          ---------------------
8219          -- Export_Function --
8220          ---------------------
8221
8222          --  pragma Export_Function (
8223          --        [Internal         =>] LOCAL_NAME
8224          --     [, [External         =>] EXTERNAL_SYMBOL]
8225          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8226          --     [, [Result_Type      =>] TYPE_DESIGNATOR]
8227          --     [, [Mechanism        =>] MECHANISM]
8228          --     [, [Result_Mechanism =>] MECHANISM_NAME]);
8229
8230          --  EXTERNAL_SYMBOL ::=
8231          --    IDENTIFIER
8232          --  | static_string_EXPRESSION
8233
8234          --  PARAMETER_TYPES ::=
8235          --    null
8236          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8237
8238          --  TYPE_DESIGNATOR ::=
8239          --    subtype_NAME
8240          --  | subtype_Name ' Access
8241
8242          --  MECHANISM ::=
8243          --    MECHANISM_NAME
8244          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8245
8246          --  MECHANISM_ASSOCIATION ::=
8247          --    [formal_parameter_NAME =>] MECHANISM_NAME
8248
8249          --  MECHANISM_NAME ::=
8250          --    Value
8251          --  | Reference
8252          --  | Descriptor [([Class =>] CLASS_NAME)]
8253
8254          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8255
8256          when Pragma_Export_Function => Export_Function : declare
8257             Args  : Args_List (1 .. 6);
8258             Names : constant Name_List (1 .. 6) := (
8259                       Name_Internal,
8260                       Name_External,
8261                       Name_Parameter_Types,
8262                       Name_Result_Type,
8263                       Name_Mechanism,
8264                       Name_Result_Mechanism);
8265
8266             Internal         : Node_Id renames Args (1);
8267             External         : Node_Id renames Args (2);
8268             Parameter_Types  : Node_Id renames Args (3);
8269             Result_Type      : Node_Id renames Args (4);
8270             Mechanism        : Node_Id renames Args (5);
8271             Result_Mechanism : Node_Id renames Args (6);
8272
8273          begin
8274             GNAT_Pragma;
8275             Gather_Associations (Names, Args);
8276             Process_Extended_Import_Export_Subprogram_Pragma (
8277               Arg_Internal         => Internal,
8278               Arg_External         => External,
8279               Arg_Parameter_Types  => Parameter_Types,
8280               Arg_Result_Type      => Result_Type,
8281               Arg_Mechanism        => Mechanism,
8282               Arg_Result_Mechanism => Result_Mechanism);
8283          end Export_Function;
8284
8285          -------------------
8286          -- Export_Object --
8287          -------------------
8288
8289          --  pragma Export_Object (
8290          --        [Internal =>] LOCAL_NAME
8291          --     [, [External =>] EXTERNAL_SYMBOL]
8292          --     [, [Size     =>] EXTERNAL_SYMBOL]);
8293
8294          --  EXTERNAL_SYMBOL ::=
8295          --    IDENTIFIER
8296          --  | static_string_EXPRESSION
8297
8298          --  PARAMETER_TYPES ::=
8299          --    null
8300          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8301
8302          --  TYPE_DESIGNATOR ::=
8303          --    subtype_NAME
8304          --  | subtype_Name ' Access
8305
8306          --  MECHANISM ::=
8307          --    MECHANISM_NAME
8308          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8309
8310          --  MECHANISM_ASSOCIATION ::=
8311          --    [formal_parameter_NAME =>] MECHANISM_NAME
8312
8313          --  MECHANISM_NAME ::=
8314          --    Value
8315          --  | Reference
8316          --  | Descriptor [([Class =>] CLASS_NAME)]
8317
8318          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8319
8320          when Pragma_Export_Object => Export_Object : declare
8321             Args  : Args_List (1 .. 3);
8322             Names : constant Name_List (1 .. 3) := (
8323                       Name_Internal,
8324                       Name_External,
8325                       Name_Size);
8326
8327             Internal : Node_Id renames Args (1);
8328             External : Node_Id renames Args (2);
8329             Size     : Node_Id renames Args (3);
8330
8331          begin
8332             GNAT_Pragma;
8333             Gather_Associations (Names, Args);
8334             Process_Extended_Import_Export_Object_Pragma (
8335               Arg_Internal => Internal,
8336               Arg_External => External,
8337               Arg_Size     => Size);
8338          end Export_Object;
8339
8340          ----------------------
8341          -- Export_Procedure --
8342          ----------------------
8343
8344          --  pragma Export_Procedure (
8345          --        [Internal         =>] LOCAL_NAME
8346          --     [, [External         =>] EXTERNAL_SYMBOL]
8347          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8348          --     [, [Mechanism        =>] MECHANISM]);
8349
8350          --  EXTERNAL_SYMBOL ::=
8351          --    IDENTIFIER
8352          --  | static_string_EXPRESSION
8353
8354          --  PARAMETER_TYPES ::=
8355          --    null
8356          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8357
8358          --  TYPE_DESIGNATOR ::=
8359          --    subtype_NAME
8360          --  | subtype_Name ' Access
8361
8362          --  MECHANISM ::=
8363          --    MECHANISM_NAME
8364          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8365
8366          --  MECHANISM_ASSOCIATION ::=
8367          --    [formal_parameter_NAME =>] MECHANISM_NAME
8368
8369          --  MECHANISM_NAME ::=
8370          --    Value
8371          --  | Reference
8372          --  | Descriptor [([Class =>] CLASS_NAME)]
8373
8374          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8375
8376          when Pragma_Export_Procedure => Export_Procedure : declare
8377             Args  : Args_List (1 .. 4);
8378             Names : constant Name_List (1 .. 4) := (
8379                       Name_Internal,
8380                       Name_External,
8381                       Name_Parameter_Types,
8382                       Name_Mechanism);
8383
8384             Internal        : Node_Id renames Args (1);
8385             External        : Node_Id renames Args (2);
8386             Parameter_Types : Node_Id renames Args (3);
8387             Mechanism       : Node_Id renames Args (4);
8388
8389          begin
8390             GNAT_Pragma;
8391             Gather_Associations (Names, Args);
8392             Process_Extended_Import_Export_Subprogram_Pragma (
8393               Arg_Internal        => Internal,
8394               Arg_External        => External,
8395               Arg_Parameter_Types => Parameter_Types,
8396               Arg_Mechanism       => Mechanism);
8397          end Export_Procedure;
8398
8399          ------------------
8400          -- Export_Value --
8401          ------------------
8402
8403          --  pragma Export_Value (
8404          --     [Value     =>] static_integer_EXPRESSION,
8405          --     [Link_Name =>] static_string_EXPRESSION);
8406
8407          when Pragma_Export_Value =>
8408             GNAT_Pragma;
8409             Check_Arg_Order ((Name_Value, Name_Link_Name));
8410             Check_Arg_Count (2);
8411
8412             Check_Optional_Identifier (Arg1, Name_Value);
8413             Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
8414
8415             Check_Optional_Identifier (Arg2, Name_Link_Name);
8416             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
8417
8418          -----------------------------
8419          -- Export_Valued_Procedure --
8420          -----------------------------
8421
8422          --  pragma Export_Valued_Procedure (
8423          --        [Internal         =>] LOCAL_NAME
8424          --     [, [External         =>] EXTERNAL_SYMBOL,]
8425          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8426          --     [, [Mechanism        =>] MECHANISM]);
8427
8428          --  EXTERNAL_SYMBOL ::=
8429          --    IDENTIFIER
8430          --  | static_string_EXPRESSION
8431
8432          --  PARAMETER_TYPES ::=
8433          --    null
8434          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8435
8436          --  TYPE_DESIGNATOR ::=
8437          --    subtype_NAME
8438          --  | subtype_Name ' Access
8439
8440          --  MECHANISM ::=
8441          --    MECHANISM_NAME
8442          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8443
8444          --  MECHANISM_ASSOCIATION ::=
8445          --    [formal_parameter_NAME =>] MECHANISM_NAME
8446
8447          --  MECHANISM_NAME ::=
8448          --    Value
8449          --  | Reference
8450          --  | Descriptor [([Class =>] CLASS_NAME)]
8451
8452          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8453
8454          when Pragma_Export_Valued_Procedure =>
8455          Export_Valued_Procedure : declare
8456             Args  : Args_List (1 .. 4);
8457             Names : constant Name_List (1 .. 4) := (
8458                       Name_Internal,
8459                       Name_External,
8460                       Name_Parameter_Types,
8461                       Name_Mechanism);
8462
8463             Internal        : Node_Id renames Args (1);
8464             External        : Node_Id renames Args (2);
8465             Parameter_Types : Node_Id renames Args (3);
8466             Mechanism       : Node_Id renames Args (4);
8467
8468          begin
8469             GNAT_Pragma;
8470             Gather_Associations (Names, Args);
8471             Process_Extended_Import_Export_Subprogram_Pragma (
8472               Arg_Internal        => Internal,
8473               Arg_External        => External,
8474               Arg_Parameter_Types => Parameter_Types,
8475               Arg_Mechanism       => Mechanism);
8476          end Export_Valued_Procedure;
8477
8478          -------------------
8479          -- Extend_System --
8480          -------------------
8481
8482          --  pragma Extend_System ([Name =>] Identifier);
8483
8484          when Pragma_Extend_System => Extend_System : declare
8485          begin
8486             GNAT_Pragma;
8487             Check_Valid_Configuration_Pragma;
8488             Check_Arg_Count (1);
8489             Check_Optional_Identifier (Arg1, Name_Name);
8490             Check_Arg_Is_Identifier (Arg1);
8491
8492             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
8493
8494             if Name_Len > 4
8495               and then Name_Buffer (1 .. 4) = "aux_"
8496             then
8497                if Present (System_Extend_Pragma_Arg) then
8498                   if Chars (Get_Pragma_Arg (Arg1)) =
8499                      Chars (Expression (System_Extend_Pragma_Arg))
8500                   then
8501                      null;
8502                   else
8503                      Error_Msg_Sloc := Sloc (System_Extend_Pragma_Arg);
8504                      Error_Pragma ("pragma% conflicts with that #");
8505                   end if;
8506
8507                else
8508                   System_Extend_Pragma_Arg := Arg1;
8509
8510                   if not GNAT_Mode then
8511                      System_Extend_Unit := Arg1;
8512                   end if;
8513                end if;
8514             else
8515                Error_Pragma ("incorrect name for pragma%, must be Aux_xxx");
8516             end if;
8517          end Extend_System;
8518
8519          ------------------------
8520          -- Extensions_Allowed --
8521          ------------------------
8522
8523          --  pragma Extensions_Allowed (ON | OFF);
8524
8525          when Pragma_Extensions_Allowed =>
8526             GNAT_Pragma;
8527             Check_Arg_Count (1);
8528             Check_No_Identifiers;
8529             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
8530
8531             if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
8532                Extensions_Allowed := True;
8533                Ada_Version := Ada_Version_Type'Last;
8534
8535             else
8536                Extensions_Allowed := False;
8537                Ada_Version := Ada_Version_Explicit;
8538             end if;
8539
8540          --------------
8541          -- External --
8542          --------------
8543
8544          --  pragma External (
8545          --    [   Convention    =>] convention_IDENTIFIER,
8546          --    [   Entity        =>] local_NAME
8547          --    [, [External_Name =>] static_string_EXPRESSION ]
8548          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
8549
8550          when Pragma_External => External : declare
8551                Def_Id : Entity_Id;
8552
8553                C : Convention_Id;
8554                pragma Warnings (Off, C);
8555
8556          begin
8557             GNAT_Pragma;
8558             Check_Arg_Order
8559               ((Name_Convention,
8560                 Name_Entity,
8561                 Name_External_Name,
8562                 Name_Link_Name));
8563             Check_At_Least_N_Arguments (2);
8564             Check_At_Most_N_Arguments  (4);
8565             Process_Convention (C, Def_Id);
8566             Note_Possible_Modification
8567               (Get_Pragma_Arg (Arg2), Sure => False);
8568             Process_Interface_Name (Def_Id, Arg3, Arg4);
8569             Set_Exported (Def_Id, Arg2);
8570          end External;
8571
8572          --------------------------
8573          -- External_Name_Casing --
8574          --------------------------
8575
8576          --  pragma External_Name_Casing (
8577          --    UPPERCASE | LOWERCASE
8578          --    [, AS_IS | UPPERCASE | LOWERCASE]);
8579
8580          when Pragma_External_Name_Casing => External_Name_Casing : declare
8581          begin
8582             GNAT_Pragma;
8583             Check_No_Identifiers;
8584
8585             if Arg_Count = 2 then
8586                Check_Arg_Is_One_Of
8587                  (Arg2, Name_As_Is, Name_Uppercase, Name_Lowercase);
8588
8589                case Chars (Get_Pragma_Arg (Arg2)) is
8590                   when Name_As_Is     =>
8591                      Opt.External_Name_Exp_Casing := As_Is;
8592
8593                   when Name_Uppercase =>
8594                      Opt.External_Name_Exp_Casing := Uppercase;
8595
8596                   when Name_Lowercase =>
8597                      Opt.External_Name_Exp_Casing := Lowercase;
8598
8599                   when others =>
8600                      null;
8601                end case;
8602
8603             else
8604                Check_Arg_Count (1);
8605             end if;
8606
8607             Check_Arg_Is_One_Of (Arg1, Name_Uppercase, Name_Lowercase);
8608
8609             case Chars (Get_Pragma_Arg (Arg1)) is
8610                when Name_Uppercase =>
8611                   Opt.External_Name_Imp_Casing := Uppercase;
8612
8613                when Name_Lowercase =>
8614                   Opt.External_Name_Imp_Casing := Lowercase;
8615
8616                when others =>
8617                   null;
8618             end case;
8619          end External_Name_Casing;
8620
8621          --------------------------
8622          -- Favor_Top_Level --
8623          --------------------------
8624
8625          --  pragma Favor_Top_Level (type_NAME);
8626
8627          when Pragma_Favor_Top_Level => Favor_Top_Level : declare
8628                Named_Entity : Entity_Id;
8629
8630          begin
8631             GNAT_Pragma;
8632             Check_No_Identifiers;
8633             Check_Arg_Count (1);
8634             Check_Arg_Is_Local_Name (Arg1);
8635             Named_Entity := Entity (Get_Pragma_Arg (Arg1));
8636
8637             --  If it's an access-to-subprogram type (in particular, not a
8638             --  subtype), set the flag on that type.
8639
8640             if Is_Access_Subprogram_Type (Named_Entity) then
8641                Set_Can_Use_Internal_Rep (Named_Entity, False);
8642
8643             --  Otherwise it's an error (name denotes the wrong sort of entity)
8644
8645             else
8646                Error_Pragma_Arg
8647                  ("access-to-subprogram type expected",
8648                   Get_Pragma_Arg (Arg1));
8649             end if;
8650          end Favor_Top_Level;
8651
8652          ---------------
8653          -- Fast_Math --
8654          ---------------
8655
8656          --  pragma Fast_Math;
8657
8658          when Pragma_Fast_Math =>
8659             GNAT_Pragma;
8660             Check_No_Identifiers;
8661             Check_Valid_Configuration_Pragma;
8662             Fast_Math := True;
8663
8664          ---------------------------
8665          -- Finalize_Storage_Only --
8666          ---------------------------
8667
8668          --  pragma Finalize_Storage_Only (first_subtype_LOCAL_NAME);
8669
8670          when Pragma_Finalize_Storage_Only => Finalize_Storage : declare
8671             Assoc   : constant Node_Id := Arg1;
8672             Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
8673             Typ     : Entity_Id;
8674
8675          begin
8676             GNAT_Pragma;
8677             Check_No_Identifiers;
8678             Check_Arg_Count (1);
8679             Check_Arg_Is_Local_Name (Arg1);
8680
8681             Find_Type (Type_Id);
8682             Typ := Entity (Type_Id);
8683
8684             if Typ = Any_Type
8685               or else Rep_Item_Too_Early (Typ, N)
8686             then
8687                return;
8688             else
8689                Typ := Underlying_Type (Typ);
8690             end if;
8691
8692             if not Is_Controlled (Typ) then
8693                Error_Pragma ("pragma% must specify controlled type");
8694             end if;
8695
8696             Check_First_Subtype (Arg1);
8697
8698             if Finalize_Storage_Only (Typ) then
8699                Error_Pragma ("duplicate pragma%, only one allowed");
8700
8701             elsif not Rep_Item_Too_Late (Typ, N) then
8702                Set_Finalize_Storage_Only (Base_Type (Typ), True);
8703             end if;
8704          end Finalize_Storage;
8705
8706          --------------------------
8707          -- Float_Representation --
8708          --------------------------
8709
8710          --  pragma Float_Representation (FLOAT_REP[, float_type_LOCAL_NAME]);
8711
8712          --  FLOAT_REP ::= VAX_Float | IEEE_Float
8713
8714          when Pragma_Float_Representation => Float_Representation : declare
8715             Argx : Node_Id;
8716             Digs : Nat;
8717             Ent  : Entity_Id;
8718
8719          begin
8720             GNAT_Pragma;
8721
8722             if Arg_Count = 1 then
8723                Check_Valid_Configuration_Pragma;
8724             else
8725                Check_Arg_Count (2);
8726                Check_Optional_Identifier (Arg2, Name_Entity);
8727                Check_Arg_Is_Local_Name (Arg2);
8728             end if;
8729
8730             Check_No_Identifier (Arg1);
8731             Check_Arg_Is_One_Of (Arg1, Name_VAX_Float, Name_IEEE_Float);
8732
8733             if not OpenVMS_On_Target then
8734                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
8735                   Error_Pragma
8736                     ("?pragma% ignored (applies only to Open'V'M'S)");
8737                end if;
8738
8739                return;
8740             end if;
8741
8742             --  One argument case
8743
8744             if Arg_Count = 1 then
8745                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
8746                   if Opt.Float_Format = 'I' then
8747                      Error_Pragma ("'I'E'E'E format previously specified");
8748                   end if;
8749
8750                   Opt.Float_Format := 'V';
8751
8752                else
8753                   if Opt.Float_Format = 'V' then
8754                      Error_Pragma ("'V'A'X format previously specified");
8755                   end if;
8756
8757                   Opt.Float_Format := 'I';
8758                end if;
8759
8760                Set_Standard_Fpt_Formats;
8761
8762             --  Two argument case
8763
8764             else
8765                Argx := Get_Pragma_Arg (Arg2);
8766
8767                if not Is_Entity_Name (Argx)
8768                  or else not Is_Floating_Point_Type (Entity (Argx))
8769                then
8770                   Error_Pragma_Arg
8771                     ("second argument of% pragma must be floating-point type",
8772                      Arg2);
8773                end if;
8774
8775                Ent  := Entity (Argx);
8776                Digs := UI_To_Int (Digits_Value (Ent));
8777
8778                --  Two arguments, VAX_Float case
8779
8780                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
8781                   case Digs is
8782                      when  6 => Set_F_Float (Ent);
8783                      when  9 => Set_D_Float (Ent);
8784                      when 15 => Set_G_Float (Ent);
8785
8786                      when others =>
8787                         Error_Pragma_Arg
8788                           ("wrong digits value, must be 6,9 or 15", Arg2);
8789                   end case;
8790
8791                --  Two arguments, IEEE_Float case
8792
8793                else
8794                   case Digs is
8795                      when  6 => Set_IEEE_Short (Ent);
8796                      when 15 => Set_IEEE_Long  (Ent);
8797
8798                      when others =>
8799                         Error_Pragma_Arg
8800                           ("wrong digits value, must be 6 or 15", Arg2);
8801                   end case;
8802                end if;
8803             end if;
8804          end Float_Representation;
8805
8806          -----------
8807          -- Ident --
8808          -----------
8809
8810          --  pragma Ident (static_string_EXPRESSION)
8811
8812          --  Note: pragma Comment shares this processing. Pragma Comment is
8813          --  identical to Ident, except that the restriction of the argument to
8814          --  31 characters and the placement restrictions are not enforced for
8815          --  pragma Comment.
8816
8817          when Pragma_Ident | Pragma_Comment => Ident : declare
8818             Str : Node_Id;
8819
8820          begin
8821             GNAT_Pragma;
8822             Check_Arg_Count (1);
8823             Check_No_Identifiers;
8824             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
8825             Store_Note (N);
8826
8827             --  For pragma Ident, preserve DEC compatibility by requiring the
8828             --  pragma to appear in a declarative part or package spec.
8829
8830             if Prag_Id = Pragma_Ident then
8831                Check_Is_In_Decl_Part_Or_Package_Spec;
8832             end if;
8833
8834             Str := Expr_Value_S (Get_Pragma_Arg (Arg1));
8835
8836             declare
8837                CS : Node_Id;
8838                GP : Node_Id;
8839
8840             begin
8841                GP := Parent (Parent (N));
8842
8843                if Nkind_In (GP, N_Package_Declaration,
8844                                 N_Generic_Package_Declaration)
8845                then
8846                   GP := Parent (GP);
8847                end if;
8848
8849                --  If we have a compilation unit, then record the ident value,
8850                --  checking for improper duplication.
8851
8852                if Nkind (GP) = N_Compilation_Unit then
8853                   CS := Ident_String (Current_Sem_Unit);
8854
8855                   if Present (CS) then
8856
8857                      --  For Ident, we do not permit multiple instances
8858
8859                      if Prag_Id = Pragma_Ident then
8860                         Error_Pragma ("duplicate% pragma not permitted");
8861
8862                      --  For Comment, we concatenate the string, unless we want
8863                      --  to preserve the tree structure for ASIS.
8864
8865                      elsif not ASIS_Mode then
8866                         Start_String (Strval (CS));
8867                         Store_String_Char (' ');
8868                         Store_String_Chars (Strval (Str));
8869                         Set_Strval (CS, End_String);
8870                      end if;
8871
8872                   else
8873                      --  In VMS, the effect of IDENT is achieved by passing
8874                      --  --identification=name as a --for-linker switch.
8875
8876                      if OpenVMS_On_Target then
8877                         Start_String;
8878                         Store_String_Chars
8879                           ("--for-linker=--identification=");
8880                         String_To_Name_Buffer (Strval (Str));
8881                         Store_String_Chars (Name_Buffer (1 .. Name_Len));
8882
8883                         --  Only the last processed IDENT is saved. The main
8884                         --  purpose is so an IDENT associated with a main
8885                         --  procedure will be used in preference to an IDENT
8886                         --  associated with a with'd package.
8887
8888                         Replace_Linker_Option_String
8889                           (End_String, "--for-linker=--identification=");
8890                      end if;
8891
8892                      Set_Ident_String (Current_Sem_Unit, Str);
8893                   end if;
8894
8895                --  For subunits, we just ignore the Ident, since in GNAT these
8896                --  are not separate object files, and hence not separate units
8897                --  in the unit table.
8898
8899                elsif Nkind (GP) = N_Subunit then
8900                   null;
8901
8902                --  Otherwise we have a misplaced pragma Ident, but we ignore
8903                --  this if we are in an instantiation, since it comes from
8904                --  a generic, and has no relevance to the instantiation.
8905
8906                elsif Prag_Id = Pragma_Ident then
8907                   if Instantiation_Location (Loc) = No_Location then
8908                      Error_Pragma ("pragma% only allowed at outer level");
8909                   end if;
8910                end if;
8911             end;
8912          end Ident;
8913
8914          -----------------
8915          -- Implemented --
8916          -----------------
8917
8918          --  pragma Implemented (procedure_LOCAL_NAME, implementation_kind);
8919          --  implementation_kind ::= By_Entry | By_Protected_Procedure | By_Any
8920
8921          when Pragma_Implemented => Implemented : declare
8922             Proc_Id : Entity_Id;
8923             Typ     : Entity_Id;
8924
8925          begin
8926             Ada_2012_Pragma;
8927             Check_Arg_Count (2);
8928             Check_No_Identifiers;
8929             Check_Arg_Is_Identifier (Arg1);
8930             Check_Arg_Is_Local_Name (Arg1);
8931             Check_Arg_Is_One_Of
8932               (Arg2, Name_By_Any, Name_By_Entry, Name_By_Protected_Procedure);
8933
8934             --  Extract the name of the local procedure
8935
8936             Proc_Id := Entity (Get_Pragma_Arg (Arg1));
8937
8938             --  Ada 2012 (AI05-0030): The procedure_LOCAL_NAME must denote a
8939             --  primitive procedure of a synchronized tagged type.
8940
8941             if Ekind (Proc_Id) = E_Procedure
8942               and then Is_Primitive (Proc_Id)
8943               and then Present (First_Formal (Proc_Id))
8944             then
8945                Typ := Etype (First_Formal (Proc_Id));
8946
8947                if Is_Tagged_Type (Typ)
8948                  and then
8949
8950                   --  Check for a protected, a synchronized or a task interface
8951
8952                    ((Is_Interface (Typ)
8953                        and then Is_Synchronized_Interface (Typ))
8954
8955                   --  Check for a protected type or a task type that implements
8956                   --  an interface.
8957
8958                    or else
8959                     (Is_Concurrent_Record_Type (Typ)
8960                        and then Present (Interfaces (Typ)))
8961
8962                   --  Check for a private record extension with keyword
8963                   --  "synchronized".
8964
8965                    or else
8966                     (Ekind_In (Typ, E_Record_Type_With_Private,
8967                                     E_Record_Subtype_With_Private)
8968                        and then Synchronized_Present (Parent (Typ))))
8969                then
8970                   null;
8971                else
8972                   Error_Pragma_Arg
8973                     ("controlling formal must be of synchronized " &
8974                      "tagged type", Arg1);
8975                   return;
8976                end if;
8977
8978             --  Procedures declared inside a protected type must be accepted
8979
8980             elsif Ekind (Proc_Id) = E_Procedure
8981               and then Is_Protected_Type (Scope (Proc_Id))
8982             then
8983                null;
8984
8985             --  The first argument is not a primitive procedure
8986
8987             else
8988                Error_Pragma_Arg
8989                  ("pragma % must be applied to a primitive procedure", Arg1);
8990                return;
8991             end if;
8992
8993             --  Ada 2012 (AI05-0030): Cannot apply the implementation_kind
8994             --  By_Protected_Procedure to the primitive procedure of a task
8995             --  interface.
8996
8997             if Chars (Arg2) = Name_By_Protected_Procedure
8998               and then Is_Interface (Typ)
8999               and then Is_Task_Interface (Typ)
9000             then
9001                Error_Pragma_Arg
9002                  ("implementation kind By_Protected_Procedure cannot be " &
9003                   "applied to a task interface primitive", Arg2);
9004                return;
9005             end if;
9006
9007             Record_Rep_Item (Proc_Id, N);
9008          end Implemented;
9009
9010          ----------------------
9011          -- Implicit_Packing --
9012          ----------------------
9013
9014          --  pragma Implicit_Packing;
9015
9016          when Pragma_Implicit_Packing =>
9017             GNAT_Pragma;
9018             Check_Arg_Count (0);
9019             Implicit_Packing := True;
9020
9021          ------------
9022          -- Import --
9023          ------------
9024
9025          --  pragma Import (
9026          --       [Convention    =>] convention_IDENTIFIER,
9027          --       [Entity        =>] local_NAME
9028          --    [, [External_Name =>] static_string_EXPRESSION ]
9029          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
9030
9031          when Pragma_Import =>
9032             Check_Ada_83_Warning;
9033             Check_Arg_Order
9034               ((Name_Convention,
9035                 Name_Entity,
9036                 Name_External_Name,
9037                 Name_Link_Name));
9038             Check_At_Least_N_Arguments (2);
9039             Check_At_Most_N_Arguments  (4);
9040             Process_Import_Or_Interface;
9041
9042          ----------------------
9043          -- Import_Exception --
9044          ----------------------
9045
9046          --  pragma Import_Exception (
9047          --        [Internal         =>] LOCAL_NAME
9048          --     [, [External         =>] EXTERNAL_SYMBOL]
9049          --     [, [Form     =>] Ada | VMS]
9050          --     [, [Code     =>] static_integer_EXPRESSION]);
9051
9052          when Pragma_Import_Exception => Import_Exception : declare
9053             Args  : Args_List (1 .. 4);
9054             Names : constant Name_List (1 .. 4) := (
9055                       Name_Internal,
9056                       Name_External,
9057                       Name_Form,
9058                       Name_Code);
9059
9060             Internal : Node_Id renames Args (1);
9061             External : Node_Id renames Args (2);
9062             Form     : Node_Id renames Args (3);
9063             Code     : Node_Id renames Args (4);
9064
9065          begin
9066             GNAT_Pragma;
9067             Gather_Associations (Names, Args);
9068
9069             if Present (External) and then Present (Code) then
9070                Error_Pragma
9071                  ("cannot give both External and Code options for pragma%");
9072             end if;
9073
9074             Process_Extended_Import_Export_Exception_Pragma (
9075               Arg_Internal => Internal,
9076               Arg_External => External,
9077               Arg_Form     => Form,
9078               Arg_Code     => Code);
9079
9080             if not Is_VMS_Exception (Entity (Internal)) then
9081                Set_Imported (Entity (Internal));
9082             end if;
9083          end Import_Exception;
9084
9085          ---------------------
9086          -- Import_Function --
9087          ---------------------
9088
9089          --  pragma Import_Function (
9090          --        [Internal                 =>] LOCAL_NAME,
9091          --     [, [External                 =>] EXTERNAL_SYMBOL]
9092          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9093          --     [, [Result_Type              =>] SUBTYPE_MARK]
9094          --     [, [Mechanism                =>] MECHANISM]
9095          --     [, [Result_Mechanism         =>] MECHANISM_NAME]
9096          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9097
9098          --  EXTERNAL_SYMBOL ::=
9099          --    IDENTIFIER
9100          --  | static_string_EXPRESSION
9101
9102          --  PARAMETER_TYPES ::=
9103          --    null
9104          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9105
9106          --  TYPE_DESIGNATOR ::=
9107          --    subtype_NAME
9108          --  | subtype_Name ' Access
9109
9110          --  MECHANISM ::=
9111          --    MECHANISM_NAME
9112          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9113
9114          --  MECHANISM_ASSOCIATION ::=
9115          --    [formal_parameter_NAME =>] MECHANISM_NAME
9116
9117          --  MECHANISM_NAME ::=
9118          --    Value
9119          --  | Reference
9120          --  | Descriptor [([Class =>] CLASS_NAME)]
9121
9122          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9123
9124          when Pragma_Import_Function => Import_Function : declare
9125             Args  : Args_List (1 .. 7);
9126             Names : constant Name_List (1 .. 7) := (
9127                       Name_Internal,
9128                       Name_External,
9129                       Name_Parameter_Types,
9130                       Name_Result_Type,
9131                       Name_Mechanism,
9132                       Name_Result_Mechanism,
9133                       Name_First_Optional_Parameter);
9134
9135             Internal                 : Node_Id renames Args (1);
9136             External                 : Node_Id renames Args (2);
9137             Parameter_Types          : Node_Id renames Args (3);
9138             Result_Type              : Node_Id renames Args (4);
9139             Mechanism                : Node_Id renames Args (5);
9140             Result_Mechanism         : Node_Id renames Args (6);
9141             First_Optional_Parameter : Node_Id renames Args (7);
9142
9143          begin
9144             GNAT_Pragma;
9145             Gather_Associations (Names, Args);
9146             Process_Extended_Import_Export_Subprogram_Pragma (
9147               Arg_Internal                 => Internal,
9148               Arg_External                 => External,
9149               Arg_Parameter_Types          => Parameter_Types,
9150               Arg_Result_Type              => Result_Type,
9151               Arg_Mechanism                => Mechanism,
9152               Arg_Result_Mechanism         => Result_Mechanism,
9153               Arg_First_Optional_Parameter => First_Optional_Parameter);
9154          end Import_Function;
9155
9156          -------------------
9157          -- Import_Object --
9158          -------------------
9159
9160          --  pragma Import_Object (
9161          --        [Internal =>] LOCAL_NAME
9162          --     [, [External =>] EXTERNAL_SYMBOL]
9163          --     [, [Size     =>] EXTERNAL_SYMBOL]);
9164
9165          --  EXTERNAL_SYMBOL ::=
9166          --    IDENTIFIER
9167          --  | static_string_EXPRESSION
9168
9169          when Pragma_Import_Object => Import_Object : declare
9170             Args  : Args_List (1 .. 3);
9171             Names : constant Name_List (1 .. 3) := (
9172                       Name_Internal,
9173                       Name_External,
9174                       Name_Size);
9175
9176             Internal : Node_Id renames Args (1);
9177             External : Node_Id renames Args (2);
9178             Size     : Node_Id renames Args (3);
9179
9180          begin
9181             GNAT_Pragma;
9182             Gather_Associations (Names, Args);
9183             Process_Extended_Import_Export_Object_Pragma (
9184               Arg_Internal => Internal,
9185               Arg_External => External,
9186               Arg_Size     => Size);
9187          end Import_Object;
9188
9189          ----------------------
9190          -- Import_Procedure --
9191          ----------------------
9192
9193          --  pragma Import_Procedure (
9194          --        [Internal                 =>] LOCAL_NAME
9195          --     [, [External                 =>] EXTERNAL_SYMBOL]
9196          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9197          --     [, [Mechanism                =>] MECHANISM]
9198          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9199
9200          --  EXTERNAL_SYMBOL ::=
9201          --    IDENTIFIER
9202          --  | static_string_EXPRESSION
9203
9204          --  PARAMETER_TYPES ::=
9205          --    null
9206          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9207
9208          --  TYPE_DESIGNATOR ::=
9209          --    subtype_NAME
9210          --  | subtype_Name ' Access
9211
9212          --  MECHANISM ::=
9213          --    MECHANISM_NAME
9214          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9215
9216          --  MECHANISM_ASSOCIATION ::=
9217          --    [formal_parameter_NAME =>] MECHANISM_NAME
9218
9219          --  MECHANISM_NAME ::=
9220          --    Value
9221          --  | Reference
9222          --  | Descriptor [([Class =>] CLASS_NAME)]
9223
9224          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9225
9226          when Pragma_Import_Procedure => Import_Procedure : declare
9227             Args  : Args_List (1 .. 5);
9228             Names : constant Name_List (1 .. 5) := (
9229                       Name_Internal,
9230                       Name_External,
9231                       Name_Parameter_Types,
9232                       Name_Mechanism,
9233                       Name_First_Optional_Parameter);
9234
9235             Internal                 : Node_Id renames Args (1);
9236             External                 : Node_Id renames Args (2);
9237             Parameter_Types          : Node_Id renames Args (3);
9238             Mechanism                : Node_Id renames Args (4);
9239             First_Optional_Parameter : Node_Id renames Args (5);
9240
9241          begin
9242             GNAT_Pragma;
9243             Gather_Associations (Names, Args);
9244             Process_Extended_Import_Export_Subprogram_Pragma (
9245               Arg_Internal                 => Internal,
9246               Arg_External                 => External,
9247               Arg_Parameter_Types          => Parameter_Types,
9248               Arg_Mechanism                => Mechanism,
9249               Arg_First_Optional_Parameter => First_Optional_Parameter);
9250          end Import_Procedure;
9251
9252          -----------------------------
9253          -- Import_Valued_Procedure --
9254          -----------------------------
9255
9256          --  pragma Import_Valued_Procedure (
9257          --        [Internal                 =>] LOCAL_NAME
9258          --     [, [External                 =>] EXTERNAL_SYMBOL]
9259          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9260          --     [, [Mechanism                =>] MECHANISM]
9261          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9262
9263          --  EXTERNAL_SYMBOL ::=
9264          --    IDENTIFIER
9265          --  | static_string_EXPRESSION
9266
9267          --  PARAMETER_TYPES ::=
9268          --    null
9269          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9270
9271          --  TYPE_DESIGNATOR ::=
9272          --    subtype_NAME
9273          --  | subtype_Name ' Access
9274
9275          --  MECHANISM ::=
9276          --    MECHANISM_NAME
9277          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9278
9279          --  MECHANISM_ASSOCIATION ::=
9280          --    [formal_parameter_NAME =>] MECHANISM_NAME
9281
9282          --  MECHANISM_NAME ::=
9283          --    Value
9284          --  | Reference
9285          --  | Descriptor [([Class =>] CLASS_NAME)]
9286
9287          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9288
9289          when Pragma_Import_Valued_Procedure =>
9290          Import_Valued_Procedure : declare
9291             Args  : Args_List (1 .. 5);
9292             Names : constant Name_List (1 .. 5) := (
9293                       Name_Internal,
9294                       Name_External,
9295                       Name_Parameter_Types,
9296                       Name_Mechanism,
9297                       Name_First_Optional_Parameter);
9298
9299             Internal                 : Node_Id renames Args (1);
9300             External                 : Node_Id renames Args (2);
9301             Parameter_Types          : Node_Id renames Args (3);
9302             Mechanism                : Node_Id renames Args (4);
9303             First_Optional_Parameter : Node_Id renames Args (5);
9304
9305          begin
9306             GNAT_Pragma;
9307             Gather_Associations (Names, Args);
9308             Process_Extended_Import_Export_Subprogram_Pragma (
9309               Arg_Internal                 => Internal,
9310               Arg_External                 => External,
9311               Arg_Parameter_Types          => Parameter_Types,
9312               Arg_Mechanism                => Mechanism,
9313               Arg_First_Optional_Parameter => First_Optional_Parameter);
9314          end Import_Valued_Procedure;
9315
9316          -----------------
9317          -- Independent --
9318          -----------------
9319
9320          --  pragma Independent (LOCAL_NAME);
9321
9322          when Pragma_Independent => Independent : declare
9323             E_Id : Node_Id;
9324             E    : Entity_Id;
9325             D    : Node_Id;
9326             K    : Node_Kind;
9327
9328          begin
9329             Check_Ada_83_Warning;
9330             Ada_2012_Pragma;
9331             Check_No_Identifiers;
9332             Check_Arg_Count (1);
9333             Check_Arg_Is_Local_Name (Arg1);
9334             E_Id := Get_Pragma_Arg (Arg1);
9335
9336             if Etype (E_Id) = Any_Type then
9337                return;
9338             end if;
9339
9340             E := Entity (E_Id);
9341             D := Declaration_Node (E);
9342             K := Nkind (D);
9343
9344             --  Check duplicate before we chain ourselves!
9345
9346             Check_Duplicate_Pragma (E);
9347
9348             --  Check appropriate entity
9349
9350             if Is_Type (E) then
9351                if Rep_Item_Too_Early (E, N)
9352                     or else
9353                   Rep_Item_Too_Late (E, N)
9354                then
9355                   return;
9356                else
9357                   Check_First_Subtype (Arg1);
9358                end if;
9359
9360             elsif K = N_Object_Declaration
9361               or else (K = N_Component_Declaration
9362                        and then Original_Record_Component (E) = E)
9363             then
9364                if Rep_Item_Too_Late (E, N) then
9365                   return;
9366                end if;
9367
9368             else
9369                Error_Pragma_Arg
9370                  ("inappropriate entity for pragma%", Arg1);
9371             end if;
9372
9373             Independence_Checks.Append ((N, E));
9374          end Independent;
9375
9376          ----------------------------
9377          -- Independent_Components --
9378          ----------------------------
9379
9380          --  pragma Atomic_Components (array_LOCAL_NAME);
9381
9382          --  This processing is shared by Volatile_Components
9383
9384          when Pragma_Independent_Components => Independent_Components : declare
9385             E_Id : Node_Id;
9386             E    : Entity_Id;
9387             D    : Node_Id;
9388             K    : Node_Kind;
9389
9390          begin
9391             Check_Ada_83_Warning;
9392             Ada_2012_Pragma;
9393             Check_No_Identifiers;
9394             Check_Arg_Count (1);
9395             Check_Arg_Is_Local_Name (Arg1);
9396             E_Id := Get_Pragma_Arg (Arg1);
9397
9398             if Etype (E_Id) = Any_Type then
9399                return;
9400             end if;
9401
9402             E := Entity (E_Id);
9403
9404             --  Check duplicate before we chain ourselves!
9405
9406             Check_Duplicate_Pragma (E);
9407
9408             --  Check appropriate entity
9409
9410             if Rep_Item_Too_Early (E, N)
9411                  or else
9412                Rep_Item_Too_Late (E, N)
9413             then
9414                return;
9415             end if;
9416
9417             D := Declaration_Node (E);
9418             K := Nkind (D);
9419
9420             if (K = N_Full_Type_Declaration
9421                  and then (Is_Array_Type (E) or else Is_Record_Type (E)))
9422               or else
9423                 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
9424                    and then Nkind (D) = N_Object_Declaration
9425                    and then Nkind (Object_Definition (D)) =
9426                                        N_Constrained_Array_Definition)
9427             then
9428                Independence_Checks.Append ((N, E));
9429
9430             else
9431                Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
9432             end if;
9433          end Independent_Components;
9434
9435          ------------------------
9436          -- Initialize_Scalars --
9437          ------------------------
9438
9439          --  pragma Initialize_Scalars;
9440
9441          when Pragma_Initialize_Scalars =>
9442             GNAT_Pragma;
9443             Check_Arg_Count (0);
9444             Check_Valid_Configuration_Pragma;
9445             Check_Restriction (No_Initialize_Scalars, N);
9446
9447             --  Initialize_Scalars creates false positives in CodePeer,
9448             --  so ignore this pragma in this mode.
9449
9450             if not Restriction_Active (No_Initialize_Scalars)
9451               and then not CodePeer_Mode
9452             then
9453                Init_Or_Norm_Scalars := True;
9454                Initialize_Scalars := True;
9455             end if;
9456
9457          ------------
9458          -- Inline --
9459          ------------
9460
9461          --  pragma Inline ( NAME {, NAME} );
9462
9463          when Pragma_Inline =>
9464
9465             --  Pragma is active if inlining option is active
9466
9467             Process_Inline (Inline_Active);
9468
9469          -------------------
9470          -- Inline_Always --
9471          -------------------
9472
9473          --  pragma Inline_Always ( NAME {, NAME} );
9474
9475          when Pragma_Inline_Always =>
9476             GNAT_Pragma;
9477
9478             --  Pragma always active unless in CodePeer mode, since this causes
9479             --  walk order issues.
9480
9481             if not CodePeer_Mode then
9482                Process_Inline (True);
9483             end if;
9484
9485          --------------------
9486          -- Inline_Generic --
9487          --------------------
9488
9489          --  pragma Inline_Generic (NAME {, NAME});
9490
9491          when Pragma_Inline_Generic =>
9492             GNAT_Pragma;
9493             Process_Generic_List;
9494
9495          ----------------------
9496          -- Inspection_Point --
9497          ----------------------
9498
9499          --  pragma Inspection_Point [(object_NAME {, object_NAME})];
9500
9501          when Pragma_Inspection_Point => Inspection_Point : declare
9502             Arg : Node_Id;
9503             Exp : Node_Id;
9504
9505          begin
9506             if Arg_Count > 0 then
9507                Arg := Arg1;
9508                loop
9509                   Exp := Get_Pragma_Arg (Arg);
9510                   Analyze (Exp);
9511
9512                   if not Is_Entity_Name (Exp)
9513                     or else not Is_Object (Entity (Exp))
9514                   then
9515                      Error_Pragma_Arg ("object name required", Arg);
9516                   end if;
9517
9518                   Next (Arg);
9519                   exit when No (Arg);
9520                end loop;
9521             end if;
9522          end Inspection_Point;
9523
9524          ---------------
9525          -- Interface --
9526          ---------------
9527
9528          --  pragma Interface (
9529          --    [   Convention    =>] convention_IDENTIFIER,
9530          --    [   Entity        =>] local_NAME
9531          --    [, [External_Name =>] static_string_EXPRESSION ]
9532          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
9533
9534          when Pragma_Interface =>
9535             GNAT_Pragma;
9536             Check_Arg_Order
9537               ((Name_Convention,
9538                 Name_Entity,
9539                 Name_External_Name,
9540                 Name_Link_Name));
9541             Check_At_Least_N_Arguments (2);
9542             Check_At_Most_N_Arguments  (4);
9543             Process_Import_Or_Interface;
9544
9545             --  In Ada 2005, the permission to use Interface (a reserved word)
9546             --  as a pragma name is considered an obsolescent feature.
9547
9548             if Ada_Version >= Ada_2005 then
9549                Check_Restriction
9550                  (No_Obsolescent_Features, Pragma_Identifier (N));
9551             end if;
9552
9553          --------------------
9554          -- Interface_Name --
9555          --------------------
9556
9557          --  pragma Interface_Name (
9558          --    [  Entity        =>] local_NAME
9559          --    [,[External_Name =>] static_string_EXPRESSION ]
9560          --    [,[Link_Name     =>] static_string_EXPRESSION ]);
9561
9562          when Pragma_Interface_Name => Interface_Name : declare
9563             Id     : Node_Id;
9564             Def_Id : Entity_Id;
9565             Hom_Id : Entity_Id;
9566             Found  : Boolean;
9567
9568          begin
9569             GNAT_Pragma;
9570             Check_Arg_Order
9571               ((Name_Entity, Name_External_Name, Name_Link_Name));
9572             Check_At_Least_N_Arguments (2);
9573             Check_At_Most_N_Arguments  (3);
9574             Id := Get_Pragma_Arg (Arg1);
9575             Analyze (Id);
9576
9577             if not Is_Entity_Name (Id) then
9578                Error_Pragma_Arg
9579                  ("first argument for pragma% must be entity name", Arg1);
9580             elsif Etype (Id) = Any_Type then
9581                return;
9582             else
9583                Def_Id := Entity (Id);
9584             end if;
9585
9586             --  Special DEC-compatible processing for the object case, forces
9587             --  object to be imported.
9588
9589             if Ekind (Def_Id) = E_Variable then
9590                Kill_Size_Check_Code (Def_Id);
9591                Note_Possible_Modification (Id, Sure => False);
9592
9593                --  Initialization is not allowed for imported variable
9594
9595                if Present (Expression (Parent (Def_Id)))
9596                  and then Comes_From_Source (Expression (Parent (Def_Id)))
9597                then
9598                   Error_Msg_Sloc := Sloc (Def_Id);
9599                   Error_Pragma_Arg
9600                     ("no initialization allowed for declaration of& #",
9601                      Arg2);
9602
9603                else
9604                   --  For compatibility, support VADS usage of providing both
9605                   --  pragmas Interface and Interface_Name to obtain the effect
9606                   --  of a single Import pragma.
9607
9608                   if Is_Imported (Def_Id)
9609                     and then Present (First_Rep_Item (Def_Id))
9610                     and then Nkind (First_Rep_Item (Def_Id)) = N_Pragma
9611                     and then
9612                       Pragma_Name (First_Rep_Item (Def_Id)) = Name_Interface
9613                   then
9614                      null;
9615                   else
9616                      Set_Imported (Def_Id);
9617                   end if;
9618
9619                   Set_Is_Public (Def_Id);
9620                   Process_Interface_Name (Def_Id, Arg2, Arg3);
9621                end if;
9622
9623             --  Otherwise must be subprogram
9624
9625             elsif not Is_Subprogram (Def_Id) then
9626                Error_Pragma_Arg
9627                  ("argument of pragma% is not subprogram", Arg1);
9628
9629             else
9630                Check_At_Most_N_Arguments (3);
9631                Hom_Id := Def_Id;
9632                Found := False;
9633
9634                --  Loop through homonyms
9635
9636                loop
9637                   Def_Id := Get_Base_Subprogram (Hom_Id);
9638
9639                   if Is_Imported (Def_Id) then
9640                      Process_Interface_Name (Def_Id, Arg2, Arg3);
9641                      Found := True;
9642                   end if;
9643
9644                   exit when From_Aspect_Specification (N);
9645                   Hom_Id := Homonym (Hom_Id);
9646
9647                   exit when No (Hom_Id)
9648                     or else Scope (Hom_Id) /= Current_Scope;
9649                end loop;
9650
9651                if not Found then
9652                   Error_Pragma_Arg
9653                     ("argument of pragma% is not imported subprogram",
9654                      Arg1);
9655                end if;
9656             end if;
9657          end Interface_Name;
9658
9659          -----------------------
9660          -- Interrupt_Handler --
9661          -----------------------
9662
9663          --  pragma Interrupt_Handler (handler_NAME);
9664
9665          when Pragma_Interrupt_Handler =>
9666             Check_Ada_83_Warning;
9667             Check_Arg_Count (1);
9668             Check_No_Identifiers;
9669
9670             if No_Run_Time_Mode then
9671                Error_Msg_CRT ("Interrupt_Handler pragma", N);
9672             else
9673                Check_Interrupt_Or_Attach_Handler;
9674                Process_Interrupt_Or_Attach_Handler;
9675             end if;
9676
9677          ------------------------
9678          -- Interrupt_Priority --
9679          ------------------------
9680
9681          --  pragma Interrupt_Priority [(EXPRESSION)];
9682
9683          when Pragma_Interrupt_Priority => Interrupt_Priority : declare
9684             P   : constant Node_Id := Parent (N);
9685             Arg : Node_Id;
9686
9687          begin
9688             Check_Ada_83_Warning;
9689
9690             if Arg_Count /= 0 then
9691                Arg := Get_Pragma_Arg (Arg1);
9692                Check_Arg_Count (1);
9693                Check_No_Identifiers;
9694
9695                --  The expression must be analyzed in the special manner
9696                --  described in "Handling of Default and Per-Object
9697                --  Expressions" in sem.ads.
9698
9699                Preanalyze_Spec_Expression (Arg, RTE (RE_Interrupt_Priority));
9700             end if;
9701
9702             if not Nkind_In (P, N_Task_Definition, N_Protected_Definition) then
9703                Pragma_Misplaced;
9704                return;
9705
9706             elsif Has_Pragma_Priority (P) then
9707                Error_Pragma ("duplicate pragma% not allowed");
9708
9709             else
9710                Set_Has_Pragma_Priority (P, True);
9711                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
9712             end if;
9713          end Interrupt_Priority;
9714
9715          ---------------------
9716          -- Interrupt_State --
9717          ---------------------
9718
9719          --  pragma Interrupt_State (
9720          --    [Name  =>] INTERRUPT_ID,
9721          --    [State =>] INTERRUPT_STATE);
9722
9723          --  INTERRUPT_ID => IDENTIFIER | static_integer_EXPRESSION
9724          --  INTERRUPT_STATE => System | Runtime | User
9725
9726          --  Note: if the interrupt id is given as an identifier, then it must
9727          --  be one of the identifiers in Ada.Interrupts.Names. Otherwise it is
9728          --  given as a static integer expression which must be in the range of
9729          --  Ada.Interrupts.Interrupt_ID.
9730
9731          when Pragma_Interrupt_State => Interrupt_State : declare
9732
9733             Int_Id : constant Entity_Id := RTE (RE_Interrupt_ID);
9734             --  This is the entity Ada.Interrupts.Interrupt_ID;
9735
9736             State_Type : Character;
9737             --  Set to 's'/'r'/'u' for System/Runtime/User
9738
9739             IST_Num : Pos;
9740             --  Index to entry in Interrupt_States table
9741
9742             Int_Val : Uint;
9743             --  Value of interrupt
9744
9745             Arg1X : constant Node_Id := Get_Pragma_Arg (Arg1);
9746             --  The first argument to the pragma
9747
9748             Int_Ent : Entity_Id;
9749             --  Interrupt entity in Ada.Interrupts.Names
9750
9751          begin
9752             GNAT_Pragma;
9753             Check_Arg_Order ((Name_Name, Name_State));
9754             Check_Arg_Count (2);
9755
9756             Check_Optional_Identifier (Arg1, Name_Name);
9757             Check_Optional_Identifier (Arg2, Name_State);
9758             Check_Arg_Is_Identifier (Arg2);
9759
9760             --  First argument is identifier
9761
9762             if Nkind (Arg1X) = N_Identifier then
9763
9764                --  Search list of names in Ada.Interrupts.Names
9765
9766                Int_Ent := First_Entity (RTE (RE_Names));
9767                loop
9768                   if No (Int_Ent) then
9769                      Error_Pragma_Arg ("invalid interrupt name", Arg1);
9770
9771                   elsif Chars (Int_Ent) = Chars (Arg1X) then
9772                      Int_Val := Expr_Value (Constant_Value (Int_Ent));
9773                      exit;
9774                   end if;
9775
9776                   Next_Entity (Int_Ent);
9777                end loop;
9778
9779             --  First argument is not an identifier, so it must be a static
9780             --  expression of type Ada.Interrupts.Interrupt_ID.
9781
9782             else
9783                Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
9784                Int_Val := Expr_Value (Arg1X);
9785
9786                if Int_Val < Expr_Value (Type_Low_Bound (Int_Id))
9787                     or else
9788                   Int_Val > Expr_Value (Type_High_Bound (Int_Id))
9789                then
9790                   Error_Pragma_Arg
9791                     ("value not in range of type " &
9792                      """Ada.Interrupts.Interrupt_'I'D""", Arg1);
9793                end if;
9794             end if;
9795
9796             --  Check OK state
9797
9798             case Chars (Get_Pragma_Arg (Arg2)) is
9799                when Name_Runtime => State_Type := 'r';
9800                when Name_System  => State_Type := 's';
9801                when Name_User    => State_Type := 'u';
9802
9803                when others =>
9804                   Error_Pragma_Arg ("invalid interrupt state", Arg2);
9805             end case;
9806
9807             --  Check if entry is already stored
9808
9809             IST_Num := Interrupt_States.First;
9810             loop
9811                --  If entry not found, add it
9812
9813                if IST_Num > Interrupt_States.Last then
9814                   Interrupt_States.Append
9815                     ((Interrupt_Number => UI_To_Int (Int_Val),
9816                       Interrupt_State  => State_Type,
9817                       Pragma_Loc       => Loc));
9818                   exit;
9819
9820                --  Case of entry for the same entry
9821
9822                elsif Int_Val = Interrupt_States.Table (IST_Num).
9823                                                            Interrupt_Number
9824                then
9825                   --  If state matches, done, no need to make redundant entry
9826
9827                   exit when
9828                     State_Type = Interrupt_States.Table (IST_Num).
9829                                                            Interrupt_State;
9830
9831                   --  Otherwise if state does not match, error
9832
9833                   Error_Msg_Sloc :=
9834                     Interrupt_States.Table (IST_Num).Pragma_Loc;
9835                   Error_Pragma_Arg
9836                     ("state conflicts with that given #", Arg2);
9837                   exit;
9838                end if;
9839
9840                IST_Num := IST_Num + 1;
9841             end loop;
9842          end Interrupt_State;
9843
9844          ---------------
9845          -- Invariant --
9846          ---------------
9847
9848          --  pragma Invariant
9849          --    ([Entity =>]    type_LOCAL_NAME,
9850          --     [Check  =>]    EXPRESSION
9851          --     [,[Message =>] String_Expression]);
9852
9853          when Pragma_Invariant => Invariant : declare
9854             Type_Id : Node_Id;
9855             Typ     : Entity_Id;
9856
9857             Discard : Boolean;
9858             pragma Unreferenced (Discard);
9859
9860          begin
9861             GNAT_Pragma;
9862             Check_At_Least_N_Arguments (2);
9863             Check_At_Most_N_Arguments (3);
9864             Check_Optional_Identifier (Arg1, Name_Entity);
9865             Check_Optional_Identifier (Arg2, Name_Check);
9866
9867             if Arg_Count = 3 then
9868                Check_Optional_Identifier (Arg3, Name_Message);
9869                Check_Arg_Is_Static_Expression (Arg3, Standard_String);
9870             end if;
9871
9872             Check_Arg_Is_Local_Name (Arg1);
9873
9874             Type_Id := Get_Pragma_Arg (Arg1);
9875             Find_Type (Type_Id);
9876             Typ := Entity (Type_Id);
9877
9878             if Typ = Any_Type then
9879                return;
9880
9881             elsif not Ekind_In (Typ, E_Private_Type,
9882                                      E_Record_Type_With_Private,
9883                                      E_Limited_Private_Type)
9884             then
9885                Error_Pragma_Arg
9886                  ("pragma% only allowed for private type", Arg1);
9887             end if;
9888
9889             --  Note that the type has at least one invariant, and also that
9890             --  it has inheritable invariants if we have Invariant'Class.
9891
9892             Set_Has_Invariants (Typ);
9893
9894             if Class_Present (N) then
9895                Set_Has_Inheritable_Invariants (Typ);
9896             end if;
9897
9898             --  The remaining processing is simply to link the pragma on to
9899             --  the rep item chain, for processing when the type is frozen.
9900             --  This is accomplished by a call to Rep_Item_Too_Late.
9901
9902             Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
9903          end Invariant;
9904
9905          ----------------------
9906          -- Java_Constructor --
9907          ----------------------
9908
9909          --  pragma Java_Constructor ([Entity =>] LOCAL_NAME);
9910
9911          --  Also handles pragma CIL_Constructor
9912
9913          when Pragma_CIL_Constructor | Pragma_Java_Constructor =>
9914          Java_Constructor : declare
9915             Convention  : Convention_Id;
9916             Def_Id      : Entity_Id;
9917             Hom_Id      : Entity_Id;
9918             Id          : Entity_Id;
9919             This_Formal : Entity_Id;
9920
9921          begin
9922             GNAT_Pragma;
9923             Check_Arg_Count (1);
9924             Check_Optional_Identifier (Arg1, Name_Entity);
9925             Check_Arg_Is_Local_Name (Arg1);
9926
9927             Id := Get_Pragma_Arg (Arg1);
9928             Find_Program_Unit_Name (Id);
9929
9930             --  If we did not find the name, we are done
9931
9932             if Etype (Id) = Any_Type then
9933                return;
9934             end if;
9935
9936             --  Check wrong use of pragma in wrong VM target
9937
9938             if VM_Target = No_VM then
9939                return;
9940
9941             elsif VM_Target = CLI_Target
9942               and then Prag_Id = Pragma_Java_Constructor
9943             then
9944                Error_Pragma ("must use pragma 'C'I'L_'Constructor");
9945
9946             elsif VM_Target = JVM_Target
9947               and then Prag_Id = Pragma_CIL_Constructor
9948             then
9949                Error_Pragma ("must use pragma 'Java_'Constructor");
9950             end if;
9951
9952             case Prag_Id is
9953                when Pragma_CIL_Constructor  => Convention := Convention_CIL;
9954                when Pragma_Java_Constructor => Convention := Convention_Java;
9955                when others                  => null;
9956             end case;
9957
9958             Hom_Id := Entity (Id);
9959
9960             --  Loop through homonyms
9961
9962             loop
9963                Def_Id := Get_Base_Subprogram (Hom_Id);
9964
9965                --  The constructor is required to be a function
9966
9967                if Ekind (Def_Id) /= E_Function then
9968                   if VM_Target = JVM_Target then
9969                      Error_Pragma_Arg
9970                        ("pragma% requires function returning a " &
9971                         "'Java access type", Def_Id);
9972                   else
9973                      Error_Pragma_Arg
9974                        ("pragma% requires function returning a " &
9975                         "'C'I'L access type", Def_Id);
9976                   end if;
9977                end if;
9978
9979                --  Check arguments: For tagged type the first formal must be
9980                --  named "this" and its type must be a named access type
9981                --  designating a class-wide tagged type that has convention
9982                --  CIL/Java. The first formal must also have a null default
9983                --  value. For example:
9984
9985                --      type Typ is tagged ...
9986                --      type Ref is access all Typ;
9987                --      pragma Convention (CIL, Typ);
9988
9989                --      function New_Typ (This : Ref) return Ref;
9990                --      function New_Typ (This : Ref; I : Integer) return Ref;
9991                --      pragma Cil_Constructor (New_Typ);
9992
9993                --  Reason: The first formal must NOT be a primitive of the
9994                --  tagged type.
9995
9996                --  This rule also applies to constructors of delegates used
9997                --  to interface with standard target libraries. For example:
9998
9999                --      type Delegate is access procedure ...
10000                --      pragma Import (CIL, Delegate, ...);
10001
10002                --      function new_Delegate
10003                --        (This : Delegate := null; ... ) return Delegate;
10004
10005                --  For value-types this rule does not apply.
10006
10007                if not Is_Value_Type (Etype (Def_Id)) then
10008                   if No (First_Formal (Def_Id)) then
10009                      Error_Msg_Name_1 := Pname;
10010                      Error_Msg_N ("% function must have parameters", Def_Id);
10011                      return;
10012                   end if;
10013
10014                   --  In the JRE library we have several occurrences in which
10015                   --  the "this" parameter is not the first formal.
10016
10017                   This_Formal := First_Formal (Def_Id);
10018
10019                   --  In the JRE library we have several occurrences in which
10020                   --  the "this" parameter is not the first formal. Search for
10021                   --  it.
10022
10023                   if VM_Target = JVM_Target then
10024                      while Present (This_Formal)
10025                        and then Get_Name_String (Chars (This_Formal)) /= "this"
10026                      loop
10027                         Next_Formal (This_Formal);
10028                      end loop;
10029
10030                      if No (This_Formal) then
10031                         This_Formal := First_Formal (Def_Id);
10032                      end if;
10033                   end if;
10034
10035                   --  Warning: The first parameter should be named "this".
10036                   --  We temporarily allow it because we have the following
10037                   --  case in the Java runtime (file s-osinte.ads) ???
10038
10039                   --    function new_Thread
10040                   --      (Self_Id : System.Address) return Thread_Id;
10041                   --    pragma Java_Constructor (new_Thread);
10042
10043                   if VM_Target = JVM_Target
10044                     and then Get_Name_String (Chars (First_Formal (Def_Id)))
10045                                = "self_id"
10046                     and then Etype (First_Formal (Def_Id)) = RTE (RE_Address)
10047                   then
10048                      null;
10049
10050                   elsif Get_Name_String (Chars (This_Formal)) /= "this" then
10051                      Error_Msg_Name_1 := Pname;
10052                      Error_Msg_N
10053                        ("first formal of % function must be named `this`",
10054                         Parent (This_Formal));
10055
10056                   elsif not Is_Access_Type (Etype (This_Formal)) then
10057                      Error_Msg_Name_1 := Pname;
10058                      Error_Msg_N
10059                        ("first formal of % function must be an access type",
10060                         Parameter_Type (Parent (This_Formal)));
10061
10062                   --  For delegates the type of the first formal must be a
10063                   --  named access-to-subprogram type (see previous example)
10064
10065                   elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type
10066                     and then Ekind (Etype (This_Formal))
10067                                /= E_Access_Subprogram_Type
10068                   then
10069                      Error_Msg_Name_1 := Pname;
10070                      Error_Msg_N
10071                        ("first formal of % function must be a named access" &
10072                         " to subprogram type",
10073                         Parameter_Type (Parent (This_Formal)));
10074
10075                   --  Warning: We should reject anonymous access types because
10076                   --  the constructor must not be handled as a primitive of the
10077                   --  tagged type. We temporarily allow it because this profile
10078                   --  is currently generated by cil2ada???
10079
10080                   elsif Ekind (Etype (Def_Id)) /= E_Access_Subprogram_Type
10081                     and then not Ekind_In (Etype (This_Formal),
10082                                              E_Access_Type,
10083                                              E_General_Access_Type,
10084                                              E_Anonymous_Access_Type)
10085                   then
10086                      Error_Msg_Name_1 := Pname;
10087                      Error_Msg_N
10088                        ("first formal of % function must be a named access" &
10089                         " type",
10090                         Parameter_Type (Parent (This_Formal)));
10091
10092                   elsif Atree.Convention
10093                          (Designated_Type (Etype (This_Formal))) /= Convention
10094                   then
10095                      Error_Msg_Name_1 := Pname;
10096
10097                      if Convention = Convention_Java then
10098                         Error_Msg_N
10099                           ("pragma% requires convention 'Cil in designated" &
10100                            " type",
10101                            Parameter_Type (Parent (This_Formal)));
10102                      else
10103                         Error_Msg_N
10104                           ("pragma% requires convention 'Java in designated" &
10105                            " type",
10106                            Parameter_Type (Parent (This_Formal)));
10107                      end if;
10108
10109                   elsif No (Expression (Parent (This_Formal)))
10110                     or else Nkind (Expression (Parent (This_Formal))) /= N_Null
10111                   then
10112                      Error_Msg_Name_1 := Pname;
10113                      Error_Msg_N
10114                        ("pragma% requires first formal with default `null`",
10115                         Parameter_Type (Parent (This_Formal)));
10116                   end if;
10117                end if;
10118
10119                --  Check result type: the constructor must be a function
10120                --  returning:
10121                --   * a value type (only allowed in the CIL compiler)
10122                --   * an access-to-subprogram type with convention Java/CIL
10123                --   * an access-type designating a type that has convention
10124                --     Java/CIL.
10125
10126                if Is_Value_Type (Etype (Def_Id)) then
10127                   null;
10128
10129                --  Access-to-subprogram type with convention Java/CIL
10130
10131                elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type then
10132                   if Atree.Convention (Etype (Def_Id)) /= Convention then
10133                      if Convention = Convention_Java then
10134                         Error_Pragma_Arg
10135                           ("pragma% requires function returning a " &
10136                            "'Java access type", Arg1);
10137                      else
10138                         pragma Assert (Convention = Convention_CIL);
10139                         Error_Pragma_Arg
10140                           ("pragma% requires function returning a " &
10141                            "'C'I'L access type", Arg1);
10142                      end if;
10143                   end if;
10144
10145                elsif Ekind (Etype (Def_Id)) in Access_Kind then
10146                   if not Ekind_In (Etype (Def_Id), E_Access_Type,
10147                                                    E_General_Access_Type)
10148                     or else
10149                       Atree.Convention
10150                         (Designated_Type (Etype (Def_Id))) /= Convention
10151                   then
10152                      Error_Msg_Name_1 := Pname;
10153
10154                      if Convention = Convention_Java then
10155                         Error_Pragma_Arg
10156                           ("pragma% requires function returning a named" &
10157                            "'Java access type", Arg1);
10158                      else
10159                         Error_Pragma_Arg
10160                           ("pragma% requires function returning a named" &
10161                            "'C'I'L access type", Arg1);
10162                      end if;
10163                   end if;
10164                end if;
10165
10166                Set_Is_Constructor (Def_Id);
10167                Set_Convention     (Def_Id, Convention);
10168                Set_Is_Imported    (Def_Id);
10169
10170                exit when From_Aspect_Specification (N);
10171                Hom_Id := Homonym (Hom_Id);
10172
10173                exit when No (Hom_Id) or else Scope (Hom_Id) /= Current_Scope;
10174             end loop;
10175          end Java_Constructor;
10176
10177          ----------------------
10178          -- Java_Interface --
10179          ----------------------
10180
10181          --  pragma Java_Interface ([Entity =>] LOCAL_NAME);
10182
10183          when Pragma_Java_Interface => Java_Interface : declare
10184             Arg : Node_Id;
10185             Typ : Entity_Id;
10186
10187          begin
10188             GNAT_Pragma;
10189             Check_Arg_Count (1);
10190             Check_Optional_Identifier (Arg1, Name_Entity);
10191             Check_Arg_Is_Local_Name (Arg1);
10192
10193             Arg := Get_Pragma_Arg (Arg1);
10194             Analyze (Arg);
10195
10196             if Etype (Arg) = Any_Type then
10197                return;
10198             end if;
10199
10200             if not Is_Entity_Name (Arg)
10201               or else not Is_Type (Entity (Arg))
10202             then
10203                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
10204             end if;
10205
10206             Typ := Underlying_Type (Entity (Arg));
10207
10208             --  For now simply check some of the semantic constraints on the
10209             --  type. This currently leaves out some restrictions on interface
10210             --  types, namely that the parent type must be java.lang.Object.Typ
10211             --  and that all primitives of the type should be declared
10212             --  abstract. ???
10213
10214             if not Is_Tagged_Type (Typ) or else not Is_Abstract_Type (Typ) then
10215                Error_Pragma_Arg ("pragma% requires an abstract "
10216                  & "tagged type", Arg1);
10217
10218             elsif not Has_Discriminants (Typ)
10219               or else Ekind (Etype (First_Discriminant (Typ)))
10220                         /= E_Anonymous_Access_Type
10221               or else
10222                 not Is_Class_Wide_Type
10223                       (Designated_Type (Etype (First_Discriminant (Typ))))
10224             then
10225                Error_Pragma_Arg
10226                  ("type must have a class-wide access discriminant", Arg1);
10227             end if;
10228          end Java_Interface;
10229
10230          ----------------
10231          -- Keep_Names --
10232          ----------------
10233
10234          --  pragma Keep_Names ([On => ] local_NAME);
10235
10236          when Pragma_Keep_Names => Keep_Names : declare
10237             Arg : Node_Id;
10238
10239          begin
10240             GNAT_Pragma;
10241             Check_Arg_Count (1);
10242             Check_Optional_Identifier (Arg1, Name_On);
10243             Check_Arg_Is_Local_Name (Arg1);
10244
10245             Arg := Get_Pragma_Arg (Arg1);
10246             Analyze (Arg);
10247
10248             if Etype (Arg) = Any_Type then
10249                return;
10250             end if;
10251
10252             if not Is_Entity_Name (Arg)
10253               or else Ekind (Entity (Arg)) /= E_Enumeration_Type
10254             then
10255                Error_Pragma_Arg
10256                  ("pragma% requires a local enumeration type", Arg1);
10257             end if;
10258
10259             Set_Discard_Names (Entity (Arg), False);
10260          end Keep_Names;
10261
10262          -------------
10263          -- License --
10264          -------------
10265
10266          --  pragma License (RESTRICTED | UNRESTRICTED | GPL | MODIFIED_GPL);
10267
10268          when Pragma_License =>
10269             GNAT_Pragma;
10270             Check_Arg_Count (1);
10271             Check_No_Identifiers;
10272             Check_Valid_Configuration_Pragma;
10273             Check_Arg_Is_Identifier (Arg1);
10274
10275             declare
10276                Sind : constant Source_File_Index :=
10277                         Source_Index (Current_Sem_Unit);
10278
10279             begin
10280                case Chars (Get_Pragma_Arg (Arg1)) is
10281                   when Name_GPL =>
10282                      Set_License (Sind, GPL);
10283
10284                   when Name_Modified_GPL =>
10285                      Set_License (Sind, Modified_GPL);
10286
10287                   when Name_Restricted =>
10288                      Set_License (Sind, Restricted);
10289
10290                   when Name_Unrestricted =>
10291                      Set_License (Sind, Unrestricted);
10292
10293                   when others =>
10294                      Error_Pragma_Arg ("invalid license name", Arg1);
10295                end case;
10296             end;
10297
10298          ---------------
10299          -- Link_With --
10300          ---------------
10301
10302          --  pragma Link_With (string_EXPRESSION {, string_EXPRESSION});
10303
10304          when Pragma_Link_With => Link_With : declare
10305             Arg : Node_Id;
10306
10307          begin
10308             GNAT_Pragma;
10309
10310             if Operating_Mode = Generate_Code
10311               and then In_Extended_Main_Source_Unit (N)
10312             then
10313                Check_At_Least_N_Arguments (1);
10314                Check_No_Identifiers;
10315                Check_Is_In_Decl_Part_Or_Package_Spec;
10316                Check_Arg_Is_Static_Expression (Arg1, Standard_String);
10317                Start_String;
10318
10319                Arg := Arg1;
10320                while Present (Arg) loop
10321                   Check_Arg_Is_Static_Expression (Arg, Standard_String);
10322
10323                   --  Store argument, converting sequences of spaces to a
10324                   --  single null character (this is one of the differences
10325                   --  in processing between Link_With and Linker_Options).
10326
10327                   Arg_Store : declare
10328                      C : constant Char_Code := Get_Char_Code (' ');
10329                      S : constant String_Id :=
10330                            Strval (Expr_Value_S (Get_Pragma_Arg (Arg)));
10331                      L : constant Nat := String_Length (S);
10332                      F : Nat := 1;
10333
10334                      procedure Skip_Spaces;
10335                      --  Advance F past any spaces
10336
10337                      -----------------
10338                      -- Skip_Spaces --
10339                      -----------------
10340
10341                      procedure Skip_Spaces is
10342                      begin
10343                         while F <= L and then Get_String_Char (S, F) = C loop
10344                            F := F + 1;
10345                         end loop;
10346                      end Skip_Spaces;
10347
10348                   --  Start of processing for Arg_Store
10349
10350                   begin
10351                      Skip_Spaces; -- skip leading spaces
10352
10353                      --  Loop through characters, changing any embedded
10354                      --  sequence of spaces to a single null character (this
10355                      --  is how Link_With/Linker_Options differ)
10356
10357                      while F <= L loop
10358                         if Get_String_Char (S, F) = C then
10359                            Skip_Spaces;
10360                            exit when F > L;
10361                            Store_String_Char (ASCII.NUL);
10362
10363                         else
10364                            Store_String_Char (Get_String_Char (S, F));
10365                            F := F + 1;
10366                         end if;
10367                      end loop;
10368                   end Arg_Store;
10369
10370                   Arg := Next (Arg);
10371
10372                   if Present (Arg) then
10373                      Store_String_Char (ASCII.NUL);
10374                   end if;
10375                end loop;
10376
10377                Store_Linker_Option_String (End_String);
10378             end if;
10379          end Link_With;
10380
10381          ------------------
10382          -- Linker_Alias --
10383          ------------------
10384
10385          --  pragma Linker_Alias (
10386          --      [Entity =>]  LOCAL_NAME
10387          --      [Target =>]  static_string_EXPRESSION);
10388
10389          when Pragma_Linker_Alias =>
10390             GNAT_Pragma;
10391             Check_Arg_Order ((Name_Entity, Name_Target));
10392             Check_Arg_Count (2);
10393             Check_Optional_Identifier (Arg1, Name_Entity);
10394             Check_Optional_Identifier (Arg2, Name_Target);
10395             Check_Arg_Is_Library_Level_Local_Name (Arg1);
10396             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10397
10398             --  The only processing required is to link this item on to the
10399             --  list of rep items for the given entity. This is accomplished
10400             --  by the call to Rep_Item_Too_Late (when no error is detected
10401             --  and False is returned).
10402
10403             if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
10404                return;
10405             else
10406                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10407             end if;
10408
10409          ------------------------
10410          -- Linker_Constructor --
10411          ------------------------
10412
10413          --  pragma Linker_Constructor (procedure_LOCAL_NAME);
10414
10415          --  Code is shared with Linker_Destructor
10416
10417          -----------------------
10418          -- Linker_Destructor --
10419          -----------------------
10420
10421          --  pragma Linker_Destructor (procedure_LOCAL_NAME);
10422
10423          when Pragma_Linker_Constructor |
10424               Pragma_Linker_Destructor =>
10425          Linker_Constructor : declare
10426             Arg1_X : Node_Id;
10427             Proc   : Entity_Id;
10428
10429          begin
10430             GNAT_Pragma;
10431             Check_Arg_Count (1);
10432             Check_No_Identifiers;
10433             Check_Arg_Is_Local_Name (Arg1);
10434             Arg1_X := Get_Pragma_Arg (Arg1);
10435             Analyze (Arg1_X);
10436             Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
10437
10438             if not Is_Library_Level_Entity (Proc) then
10439                Error_Pragma_Arg
10440                 ("argument for pragma% must be library level entity", Arg1);
10441             end if;
10442
10443             --  The only processing required is to link this item on to the
10444             --  list of rep items for the given entity. This is accomplished
10445             --  by the call to Rep_Item_Too_Late (when no error is detected
10446             --  and False is returned).
10447
10448             if Rep_Item_Too_Late (Proc, N) then
10449                return;
10450             else
10451                Set_Has_Gigi_Rep_Item (Proc);
10452             end if;
10453          end Linker_Constructor;
10454
10455          --------------------
10456          -- Linker_Options --
10457          --------------------
10458
10459          --  pragma Linker_Options (string_EXPRESSION {, string_EXPRESSION});
10460
10461          when Pragma_Linker_Options => Linker_Options : declare
10462             Arg : Node_Id;
10463
10464          begin
10465             Check_Ada_83_Warning;
10466             Check_No_Identifiers;
10467             Check_Arg_Count (1);
10468             Check_Is_In_Decl_Part_Or_Package_Spec;
10469             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
10470             Start_String (Strval (Expr_Value_S (Get_Pragma_Arg (Arg1))));
10471
10472             Arg := Arg2;
10473             while Present (Arg) loop
10474                Check_Arg_Is_Static_Expression (Arg, Standard_String);
10475                Store_String_Char (ASCII.NUL);
10476                Store_String_Chars
10477                  (Strval (Expr_Value_S (Get_Pragma_Arg (Arg))));
10478                Arg := Next (Arg);
10479             end loop;
10480
10481             if Operating_Mode = Generate_Code
10482               and then In_Extended_Main_Source_Unit (N)
10483             then
10484                Store_Linker_Option_String (End_String);
10485             end if;
10486          end Linker_Options;
10487
10488          --------------------
10489          -- Linker_Section --
10490          --------------------
10491
10492          --  pragma Linker_Section (
10493          --      [Entity  =>]  LOCAL_NAME
10494          --      [Section =>]  static_string_EXPRESSION);
10495
10496          when Pragma_Linker_Section =>
10497             GNAT_Pragma;
10498             Check_Arg_Order ((Name_Entity, Name_Section));
10499             Check_Arg_Count (2);
10500             Check_Optional_Identifier (Arg1, Name_Entity);
10501             Check_Optional_Identifier (Arg2, Name_Section);
10502             Check_Arg_Is_Library_Level_Local_Name (Arg1);
10503             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10504
10505             --  This pragma applies only to objects
10506
10507             if not Is_Object (Entity (Get_Pragma_Arg (Arg1))) then
10508                Error_Pragma_Arg ("pragma% applies only to objects", Arg1);
10509             end if;
10510
10511             --  The only processing required is to link this item on to the
10512             --  list of rep items for the given entity. This is accomplished
10513             --  by the call to Rep_Item_Too_Late (when no error is detected
10514             --  and False is returned).
10515
10516             if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
10517                return;
10518             else
10519                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10520             end if;
10521
10522          ----------
10523          -- List --
10524          ----------
10525
10526          --  pragma List (On | Off)
10527
10528          --  There is nothing to do here, since we did all the processing for
10529          --  this pragma in Par.Prag (so that it works properly even in syntax
10530          --  only mode).
10531
10532          when Pragma_List =>
10533             null;
10534
10535          --------------------
10536          -- Locking_Policy --
10537          --------------------
10538
10539          --  pragma Locking_Policy (policy_IDENTIFIER);
10540
10541          when Pragma_Locking_Policy => declare
10542             LP : Character;
10543
10544          begin
10545             Check_Ada_83_Warning;
10546             Check_Arg_Count (1);
10547             Check_No_Identifiers;
10548             Check_Arg_Is_Locking_Policy (Arg1);
10549             Check_Valid_Configuration_Pragma;
10550             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
10551             LP := Fold_Upper (Name_Buffer (1));
10552
10553             if Locking_Policy /= ' '
10554               and then Locking_Policy /= LP
10555             then
10556                Error_Msg_Sloc := Locking_Policy_Sloc;
10557                Error_Pragma ("locking policy incompatible with policy#");
10558
10559             --  Set new policy, but always preserve System_Location since we
10560             --  like the error message with the run time name.
10561
10562             else
10563                Locking_Policy := LP;
10564
10565                if Locking_Policy_Sloc /= System_Location then
10566                   Locking_Policy_Sloc := Loc;
10567                end if;
10568             end if;
10569          end;
10570
10571          ----------------
10572          -- Long_Float --
10573          ----------------
10574
10575          --  pragma Long_Float (D_Float | G_Float);
10576
10577          when Pragma_Long_Float =>
10578             GNAT_Pragma;
10579             Check_Valid_Configuration_Pragma;
10580             Check_Arg_Count (1);
10581             Check_No_Identifier (Arg1);
10582             Check_Arg_Is_One_Of (Arg1, Name_D_Float, Name_G_Float);
10583
10584             if not OpenVMS_On_Target then
10585                Error_Pragma ("?pragma% ignored (applies only to Open'V'M'S)");
10586             end if;
10587
10588             --  D_Float case
10589
10590             if Chars (Get_Pragma_Arg (Arg1)) = Name_D_Float then
10591                if Opt.Float_Format_Long = 'G' then
10592                   Error_Pragma ("G_Float previously specified");
10593                end if;
10594
10595                Opt.Float_Format_Long := 'D';
10596
10597             --  G_Float case (this is the default, does not need overriding)
10598
10599             else
10600                if Opt.Float_Format_Long = 'D' then
10601                   Error_Pragma ("D_Float previously specified");
10602                end if;
10603
10604                Opt.Float_Format_Long := 'G';
10605             end if;
10606
10607             Set_Standard_Fpt_Formats;
10608
10609          -----------------------
10610          -- Machine_Attribute --
10611          -----------------------
10612
10613          --  pragma Machine_Attribute (
10614          --       [Entity         =>] LOCAL_NAME,
10615          --       [Attribute_Name =>] static_string_EXPRESSION
10616          --    [, [Info           =>] static_EXPRESSION] );
10617
10618          when Pragma_Machine_Attribute => Machine_Attribute : declare
10619             Def_Id : Entity_Id;
10620
10621          begin
10622             GNAT_Pragma;
10623             Check_Arg_Order ((Name_Entity, Name_Attribute_Name, Name_Info));
10624
10625             if Arg_Count = 3 then
10626                Check_Optional_Identifier (Arg3, Name_Info);
10627                Check_Arg_Is_Static_Expression (Arg3);
10628             else
10629                Check_Arg_Count (2);
10630             end if;
10631
10632             Check_Optional_Identifier (Arg1, Name_Entity);
10633             Check_Optional_Identifier (Arg2, Name_Attribute_Name);
10634             Check_Arg_Is_Local_Name (Arg1);
10635             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10636             Def_Id := Entity (Get_Pragma_Arg (Arg1));
10637
10638             if Is_Access_Type (Def_Id) then
10639                Def_Id := Designated_Type (Def_Id);
10640             end if;
10641
10642             if Rep_Item_Too_Early (Def_Id, N) then
10643                return;
10644             end if;
10645
10646             Def_Id := Underlying_Type (Def_Id);
10647
10648             --  The only processing required is to link this item on to the
10649             --  list of rep items for the given entity. This is accomplished
10650             --  by the call to Rep_Item_Too_Late (when no error is detected
10651             --  and False is returned).
10652
10653             if Rep_Item_Too_Late (Def_Id, N) then
10654                return;
10655             else
10656                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10657             end if;
10658          end Machine_Attribute;
10659
10660          ----------
10661          -- Main --
10662          ----------
10663
10664          --  pragma Main
10665          --   (MAIN_OPTION [, MAIN_OPTION]);
10666
10667          --  MAIN_OPTION ::=
10668          --    [STACK_SIZE              =>] static_integer_EXPRESSION
10669          --  | [TASK_STACK_SIZE_DEFAULT =>] static_integer_EXPRESSION
10670          --  | [TIME_SLICING_ENABLED    =>] static_boolean_EXPRESSION
10671
10672          when Pragma_Main => Main : declare
10673             Args  : Args_List (1 .. 3);
10674             Names : constant Name_List (1 .. 3) := (
10675                       Name_Stack_Size,
10676                       Name_Task_Stack_Size_Default,
10677                       Name_Time_Slicing_Enabled);
10678
10679             Nod : Node_Id;
10680
10681          begin
10682             GNAT_Pragma;
10683             Gather_Associations (Names, Args);
10684
10685             for J in 1 .. 2 loop
10686                if Present (Args (J)) then
10687                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
10688                end if;
10689             end loop;
10690
10691             if Present (Args (3)) then
10692                Check_Arg_Is_Static_Expression (Args (3), Standard_Boolean);
10693             end if;
10694
10695             Nod := Next (N);
10696             while Present (Nod) loop
10697                if Nkind (Nod) = N_Pragma
10698                  and then Pragma_Name (Nod) = Name_Main
10699                then
10700                   Error_Msg_Name_1 := Pname;
10701                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
10702                end if;
10703
10704                Next (Nod);
10705             end loop;
10706          end Main;
10707
10708          ------------------
10709          -- Main_Storage --
10710          ------------------
10711
10712          --  pragma Main_Storage
10713          --   (MAIN_STORAGE_OPTION [, MAIN_STORAGE_OPTION]);
10714
10715          --  MAIN_STORAGE_OPTION ::=
10716          --    [WORKING_STORAGE =>] static_SIMPLE_EXPRESSION
10717          --  | [TOP_GUARD =>] static_SIMPLE_EXPRESSION
10718
10719          when Pragma_Main_Storage => Main_Storage : declare
10720             Args  : Args_List (1 .. 2);
10721             Names : constant Name_List (1 .. 2) := (
10722                       Name_Working_Storage,
10723                       Name_Top_Guard);
10724
10725             Nod : Node_Id;
10726
10727          begin
10728             GNAT_Pragma;
10729             Gather_Associations (Names, Args);
10730
10731             for J in 1 .. 2 loop
10732                if Present (Args (J)) then
10733                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
10734                end if;
10735             end loop;
10736
10737             Check_In_Main_Program;
10738
10739             Nod := Next (N);
10740             while Present (Nod) loop
10741                if Nkind (Nod) = N_Pragma
10742                  and then Pragma_Name (Nod) = Name_Main_Storage
10743                then
10744                   Error_Msg_Name_1 := Pname;
10745                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
10746                end if;
10747
10748                Next (Nod);
10749             end loop;
10750          end Main_Storage;
10751
10752          -----------------
10753          -- Memory_Size --
10754          -----------------
10755
10756          --  pragma Memory_Size (NUMERIC_LITERAL)
10757
10758          when Pragma_Memory_Size =>
10759             GNAT_Pragma;
10760
10761             --  Memory size is simply ignored
10762
10763             Check_No_Identifiers;
10764             Check_Arg_Count (1);
10765             Check_Arg_Is_Integer_Literal (Arg1);
10766
10767          -------------
10768          -- No_Body --
10769          -------------
10770
10771          --  pragma No_Body;
10772
10773          --  The only correct use of this pragma is on its own in a file, in
10774          --  which case it is specially processed (see Gnat1drv.Check_Bad_Body
10775          --  and Frontend, which use Sinput.L.Source_File_Is_Pragma_No_Body to
10776          --  check for a file containing nothing but a No_Body pragma). If we
10777          --  attempt to process it during normal semantics processing, it means
10778          --  it was misplaced.
10779
10780          when Pragma_No_Body =>
10781             GNAT_Pragma;
10782             Pragma_Misplaced;
10783
10784          ---------------
10785          -- No_Return --
10786          ---------------
10787
10788          --  pragma No_Return (procedure_LOCAL_NAME {, procedure_Local_Name});
10789
10790          when Pragma_No_Return => No_Return : declare
10791             Id    : Node_Id;
10792             E     : Entity_Id;
10793             Found : Boolean;
10794             Arg   : Node_Id;
10795
10796          begin
10797             Ada_2005_Pragma;
10798             Check_At_Least_N_Arguments (1);
10799
10800             --  Loop through arguments of pragma
10801
10802             Arg := Arg1;
10803             while Present (Arg) loop
10804                Check_Arg_Is_Local_Name (Arg);
10805                Id := Get_Pragma_Arg (Arg);
10806                Analyze (Id);
10807
10808                if not Is_Entity_Name (Id) then
10809                   Error_Pragma_Arg ("entity name required", Arg);
10810                end if;
10811
10812                if Etype (Id) = Any_Type then
10813                   raise Pragma_Exit;
10814                end if;
10815
10816                --  Loop to find matching procedures
10817
10818                E := Entity (Id);
10819                Found := False;
10820                while Present (E)
10821                  and then Scope (E) = Current_Scope
10822                loop
10823                   if Ekind_In (E, E_Procedure, E_Generic_Procedure) then
10824                      Set_No_Return (E);
10825
10826                      --  Set flag on any alias as well
10827
10828                      if Is_Overloadable (E) and then Present (Alias (E)) then
10829                         Set_No_Return (Alias (E));
10830                      end if;
10831
10832                      Found := True;
10833                   end if;
10834
10835                   exit when From_Aspect_Specification (N);
10836                   E := Homonym (E);
10837                end loop;
10838
10839                if not Found then
10840                   Error_Pragma_Arg ("no procedure & found for pragma%", Arg);
10841                end if;
10842
10843                Next (Arg);
10844             end loop;
10845          end No_Return;
10846
10847          -----------------
10848          -- No_Run_Time --
10849          -----------------
10850
10851          --  pragma No_Run_Time;
10852
10853          --  Note: this pragma is retained for backwards compatibility. See
10854          --  body of Rtsfind for full details on its handling.
10855
10856          when Pragma_No_Run_Time =>
10857             GNAT_Pragma;
10858             Check_Valid_Configuration_Pragma;
10859             Check_Arg_Count (0);
10860
10861             No_Run_Time_Mode           := True;
10862             Configurable_Run_Time_Mode := True;
10863
10864             --  Set Duration to 32 bits if word size is 32
10865
10866             if Ttypes.System_Word_Size = 32 then
10867                Duration_32_Bits_On_Target := True;
10868             end if;
10869
10870             --  Set appropriate restrictions
10871
10872             Set_Restriction (No_Finalization, N);
10873             Set_Restriction (No_Exception_Handlers, N);
10874             Set_Restriction (Max_Tasks, N, 0);
10875             Set_Restriction (No_Tasking, N);
10876
10877          ------------------------
10878          -- No_Strict_Aliasing --
10879          ------------------------
10880
10881          --  pragma No_Strict_Aliasing [([Entity =>] type_LOCAL_NAME)];
10882
10883          when Pragma_No_Strict_Aliasing => No_Strict_Aliasing : declare
10884             E_Id : Entity_Id;
10885
10886          begin
10887             GNAT_Pragma;
10888             Check_At_Most_N_Arguments (1);
10889
10890             if Arg_Count = 0 then
10891                Check_Valid_Configuration_Pragma;
10892                Opt.No_Strict_Aliasing := True;
10893
10894             else
10895                Check_Optional_Identifier (Arg2, Name_Entity);
10896                Check_Arg_Is_Local_Name (Arg1);
10897                E_Id := Entity (Get_Pragma_Arg (Arg1));
10898
10899                if E_Id = Any_Type then
10900                   return;
10901                elsif No (E_Id) or else not Is_Access_Type (E_Id) then
10902                   Error_Pragma_Arg ("pragma% requires access type", Arg1);
10903                end if;
10904
10905                Set_No_Strict_Aliasing (Implementation_Base_Type (E_Id));
10906             end if;
10907          end No_Strict_Aliasing;
10908
10909          -----------------------
10910          -- Normalize_Scalars --
10911          -----------------------
10912
10913          --  pragma Normalize_Scalars;
10914
10915          when Pragma_Normalize_Scalars =>
10916             Check_Ada_83_Warning;
10917             Check_Arg_Count (0);
10918             Check_Valid_Configuration_Pragma;
10919
10920             --  Normalize_Scalars creates false positives in CodePeer, so
10921             --  ignore this pragma in this mode.
10922
10923             if not CodePeer_Mode then
10924                Normalize_Scalars := True;
10925                Init_Or_Norm_Scalars := True;
10926             end if;
10927
10928          -----------------
10929          -- Obsolescent --
10930          -----------------
10931
10932          --  pragma Obsolescent;
10933
10934          --  pragma Obsolescent (
10935          --    [Message =>] static_string_EXPRESSION
10936          --  [,[Version =>] Ada_05]]);
10937
10938          --  pragma Obsolescent (
10939          --    [Entity  =>] NAME
10940          --  [,[Message =>] static_string_EXPRESSION
10941          --  [,[Version =>] Ada_05]] );
10942
10943          when Pragma_Obsolescent => Obsolescent : declare
10944             Ename : Node_Id;
10945             Decl  : Node_Id;
10946
10947             procedure Set_Obsolescent (E : Entity_Id);
10948             --  Given an entity Ent, mark it as obsolescent if appropriate
10949
10950             ---------------------
10951             -- Set_Obsolescent --
10952             ---------------------
10953
10954             procedure Set_Obsolescent (E : Entity_Id) is
10955                Active : Boolean;
10956                Ent    : Entity_Id;
10957                S      : String_Id;
10958
10959             begin
10960                Active := True;
10961                Ent    := E;
10962
10963                --  Entity name was given
10964
10965                if Present (Ename) then
10966
10967                   --  If entity name matches, we are fine. Save entity in
10968                   --  pragma argument, for ASIS use.
10969
10970                   if Chars (Ename) = Chars (Ent) then
10971                      Set_Entity (Ename, Ent);
10972                      Generate_Reference (Ent, Ename);
10973
10974                   --  If entity name does not match, only possibility is an
10975                   --  enumeration literal from an enumeration type declaration.
10976
10977                   elsif Ekind (Ent) /= E_Enumeration_Type then
10978                      Error_Pragma
10979                        ("pragma % entity name does not match declaration");
10980
10981                   else
10982                      Ent := First_Literal (E);
10983                      loop
10984                         if No (Ent) then
10985                            Error_Pragma
10986                              ("pragma % entity name does not match any " &
10987                               "enumeration literal");
10988
10989                         elsif Chars (Ent) = Chars (Ename) then
10990                            Set_Entity (Ename, Ent);
10991                            Generate_Reference (Ent, Ename);
10992                            exit;
10993
10994                         else
10995                            Ent := Next_Literal (Ent);
10996                         end if;
10997                      end loop;
10998                   end if;
10999                end if;
11000
11001                --  Ent points to entity to be marked
11002
11003                if Arg_Count >= 1 then
11004
11005                   --  Deal with static string argument
11006
11007                   Check_Arg_Is_Static_Expression (Arg1, Standard_String);
11008                   S := Strval (Get_Pragma_Arg (Arg1));
11009
11010                   for J in 1 .. String_Length (S) loop
11011                      if not In_Character_Range (Get_String_Char (S, J)) then
11012                         Error_Pragma_Arg
11013                           ("pragma% argument does not allow wide characters",
11014                            Arg1);
11015                      end if;
11016                   end loop;
11017
11018                   Obsolescent_Warnings.Append
11019                     ((Ent => Ent, Msg => Strval (Get_Pragma_Arg (Arg1))));
11020
11021                   --  Check for Ada_05 parameter
11022
11023                   if Arg_Count /= 1 then
11024                      Check_Arg_Count (2);
11025
11026                      declare
11027                         Argx : constant Node_Id := Get_Pragma_Arg (Arg2);
11028
11029                      begin
11030                         Check_Arg_Is_Identifier (Argx);
11031
11032                         if Chars (Argx) /= Name_Ada_05 then
11033                            Error_Msg_Name_2 := Name_Ada_05;
11034                            Error_Pragma_Arg
11035                              ("only allowed argument for pragma% is %", Argx);
11036                         end if;
11037
11038                         if Ada_Version_Explicit < Ada_2005
11039                           or else not Warn_On_Ada_2005_Compatibility
11040                         then
11041                            Active := False;
11042                         end if;
11043                      end;
11044                   end if;
11045                end if;
11046
11047                --  Set flag if pragma active
11048
11049                if Active then
11050                   Set_Is_Obsolescent (Ent);
11051                end if;
11052
11053                return;
11054             end Set_Obsolescent;
11055
11056          --  Start of processing for pragma Obsolescent
11057
11058          begin
11059             GNAT_Pragma;
11060
11061             Check_At_Most_N_Arguments (3);
11062
11063             --  See if first argument specifies an entity name
11064
11065             if Arg_Count >= 1
11066               and then
11067                 (Chars (Arg1) = Name_Entity
11068                    or else
11069                      Nkind_In (Get_Pragma_Arg (Arg1), N_Character_Literal,
11070                                                       N_Identifier,
11071                                                       N_Operator_Symbol))
11072             then
11073                Ename := Get_Pragma_Arg (Arg1);
11074
11075                --  Eliminate first argument, so we can share processing
11076
11077                Arg1 := Arg2;
11078                Arg2 := Arg3;
11079                Arg_Count := Arg_Count - 1;
11080
11081             --  No Entity name argument given
11082
11083             else
11084                Ename := Empty;
11085             end if;
11086
11087             if Arg_Count >= 1 then
11088                Check_Optional_Identifier (Arg1, Name_Message);
11089
11090                if Arg_Count = 2 then
11091                   Check_Optional_Identifier (Arg2, Name_Version);
11092                end if;
11093             end if;
11094
11095             --  Get immediately preceding declaration
11096
11097             Decl := Prev (N);
11098             while Present (Decl) and then Nkind (Decl) = N_Pragma loop
11099                Prev (Decl);
11100             end loop;
11101
11102             --  Cases where we do not follow anything other than another pragma
11103
11104             if No (Decl) then
11105
11106                --  First case: library level compilation unit declaration with
11107                --  the pragma immediately following the declaration.
11108
11109                if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
11110                   Set_Obsolescent
11111                     (Defining_Entity (Unit (Parent (Parent (N)))));
11112                   return;
11113
11114                --  Case 2: library unit placement for package
11115
11116                else
11117                   declare
11118                      Ent : constant Entity_Id := Find_Lib_Unit_Name;
11119                   begin
11120                      if Is_Package_Or_Generic_Package (Ent) then
11121                         Set_Obsolescent (Ent);
11122                         return;
11123                      end if;
11124                   end;
11125                end if;
11126
11127             --  Cases where we must follow a declaration
11128
11129             else
11130                if         Nkind (Decl) not in N_Declaration
11131                  and then Nkind (Decl) not in N_Later_Decl_Item
11132                  and then Nkind (Decl) not in N_Generic_Declaration
11133                  and then Nkind (Decl) not in N_Renaming_Declaration
11134                then
11135                   Error_Pragma
11136                     ("pragma% misplaced, "
11137                      & "must immediately follow a declaration");
11138
11139                else
11140                   Set_Obsolescent (Defining_Entity (Decl));
11141                   return;
11142                end if;
11143             end if;
11144          end Obsolescent;
11145
11146          --------------
11147          -- Optimize --
11148          --------------
11149
11150          --  pragma Optimize (Time | Space | Off);
11151
11152          --  The actual check for optimize is done in Gigi. Note that this
11153          --  pragma does not actually change the optimization setting, it
11154          --  simply checks that it is consistent with the pragma.
11155
11156          when Pragma_Optimize =>
11157             Check_No_Identifiers;
11158             Check_Arg_Count (1);
11159             Check_Arg_Is_One_Of (Arg1, Name_Time, Name_Space, Name_Off);
11160
11161          ------------------------
11162          -- Optimize_Alignment --
11163          ------------------------
11164
11165          --  pragma Optimize_Alignment (Time | Space | Off);
11166
11167          when Pragma_Optimize_Alignment => Optimize_Alignment : begin
11168             GNAT_Pragma;
11169             Check_No_Identifiers;
11170             Check_Arg_Count (1);
11171             Check_Valid_Configuration_Pragma;
11172
11173             declare
11174                Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
11175             begin
11176                case Nam is
11177                   when Name_Time =>
11178                      Opt.Optimize_Alignment := 'T';
11179                   when Name_Space =>
11180                      Opt.Optimize_Alignment := 'S';
11181                   when Name_Off =>
11182                      Opt.Optimize_Alignment := 'O';
11183                   when others =>
11184                      Error_Pragma_Arg ("invalid argument for pragma%", Arg1);
11185                end case;
11186             end;
11187
11188             --  Set indication that mode is set locally. If we are in fact in a
11189             --  configuration pragma file, this setting is harmless since the
11190             --  switch will get reset anyway at the start of each unit.
11191
11192             Optimize_Alignment_Local := True;
11193          end Optimize_Alignment;
11194
11195          -------------
11196          -- Ordered --
11197          -------------
11198
11199          --  pragma Ordered (first_enumeration_subtype_LOCAL_NAME);
11200
11201          when Pragma_Ordered => Ordered : declare
11202             Assoc   : constant Node_Id := Arg1;
11203             Type_Id : Node_Id;
11204             Typ     : Entity_Id;
11205
11206          begin
11207             GNAT_Pragma;
11208             Check_No_Identifiers;
11209             Check_Arg_Count (1);
11210             Check_Arg_Is_Local_Name (Arg1);
11211
11212             Type_Id := Get_Pragma_Arg (Assoc);
11213             Find_Type (Type_Id);
11214             Typ := Entity (Type_Id);
11215
11216             if Typ = Any_Type then
11217                return;
11218             else
11219                Typ := Underlying_Type (Typ);
11220             end if;
11221
11222             if not Is_Enumeration_Type (Typ) then
11223                Error_Pragma ("pragma% must specify enumeration type");
11224             end if;
11225
11226             Check_First_Subtype (Arg1);
11227             Set_Has_Pragma_Ordered (Base_Type (Typ));
11228          end Ordered;
11229
11230          ----------
11231          -- Pack --
11232          ----------
11233
11234          --  pragma Pack (first_subtype_LOCAL_NAME);
11235
11236          when Pragma_Pack => Pack : declare
11237             Assoc   : constant Node_Id := Arg1;
11238             Type_Id : Node_Id;
11239             Typ     : Entity_Id;
11240             Ctyp    : Entity_Id;
11241             Ignore  : Boolean := False;
11242
11243          begin
11244             Check_No_Identifiers;
11245             Check_Arg_Count (1);
11246             Check_Arg_Is_Local_Name (Arg1);
11247
11248             Type_Id := Get_Pragma_Arg (Assoc);
11249             Find_Type (Type_Id);
11250             Typ := Entity (Type_Id);
11251
11252             if Typ = Any_Type
11253               or else Rep_Item_Too_Early (Typ, N)
11254             then
11255                return;
11256             else
11257                Typ := Underlying_Type (Typ);
11258             end if;
11259
11260             if not Is_Array_Type (Typ) and then not Is_Record_Type (Typ) then
11261                Error_Pragma ("pragma% must specify array or record type");
11262             end if;
11263
11264             Check_First_Subtype (Arg1);
11265             Check_Duplicate_Pragma (Typ);
11266
11267             --  Array type
11268
11269             if Is_Array_Type (Typ) then
11270                Ctyp := Component_Type (Typ);
11271
11272                --  Ignore pack that does nothing
11273
11274                if Known_Static_Esize (Ctyp)
11275                  and then Known_Static_RM_Size (Ctyp)
11276                  and then Esize (Ctyp) = RM_Size (Ctyp)
11277                  and then Addressable (Esize (Ctyp))
11278                then
11279                   Ignore := True;
11280                end if;
11281
11282                --  Process OK pragma Pack. Note that if there is a separate
11283                --  component clause present, the Pack will be cancelled. This
11284                --  processing is in Freeze.
11285
11286                if not Rep_Item_Too_Late (Typ, N) then
11287
11288                   --  In the context of static code analysis, we do not need
11289                   --  complex front-end expansions related to pragma Pack,
11290                   --  so disable handling of pragma Pack in this case.
11291
11292                   if CodePeer_Mode then
11293                      null;
11294
11295                   --  Don't attempt any packing for VM targets. We possibly
11296                   --  could deal with some cases of array bit-packing, but we
11297                   --  don't bother, since this is not a typical kind of
11298                   --  representation in the VM context anyway (and would not
11299                   --  for example work nicely with the debugger).
11300
11301                   elsif VM_Target /= No_VM then
11302                      if not GNAT_Mode then
11303                         Error_Pragma
11304                           ("?pragma% ignored in this configuration");
11305                      end if;
11306
11307                   --  Normal case where we do the pack action
11308
11309                   else
11310                      if not Ignore then
11311                         Set_Is_Packed            (Base_Type (Typ));
11312                         Set_Has_Non_Standard_Rep (Base_Type (Typ));
11313                      end if;
11314
11315                      Set_Has_Pragma_Pack (Base_Type (Typ));
11316                   end if;
11317                end if;
11318
11319             --  For record types, the pack is always effective
11320
11321             else pragma Assert (Is_Record_Type (Typ));
11322                if not Rep_Item_Too_Late (Typ, N) then
11323
11324                   --  Ignore pack request with warning in VM mode (skip warning
11325                   --  if we are compiling GNAT run time library).
11326
11327                   if VM_Target /= No_VM then
11328                      if not GNAT_Mode then
11329                         Error_Pragma
11330                           ("?pragma% ignored in this configuration");
11331                      end if;
11332
11333                   --  Normal case of pack request active
11334
11335                   else
11336                      Set_Is_Packed            (Base_Type (Typ));
11337                      Set_Has_Pragma_Pack      (Base_Type (Typ));
11338                      Set_Has_Non_Standard_Rep (Base_Type (Typ));
11339                   end if;
11340                end if;
11341             end if;
11342          end Pack;
11343
11344          ----------
11345          -- Page --
11346          ----------
11347
11348          --  pragma Page;
11349
11350          --  There is nothing to do here, since we did all the processing for
11351          --  this pragma in Par.Prag (so that it works properly even in syntax
11352          --  only mode).
11353
11354          when Pragma_Page =>
11355             null;
11356
11357          -------------
11358          -- Passive --
11359          -------------
11360
11361          --  pragma Passive [(PASSIVE_FORM)];
11362
11363          --  PASSIVE_FORM ::= Semaphore | No
11364
11365          when Pragma_Passive =>
11366             GNAT_Pragma;
11367
11368             if Nkind (Parent (N)) /= N_Task_Definition then
11369                Error_Pragma ("pragma% must be within task definition");
11370             end if;
11371
11372             if Arg_Count /= 0 then
11373                Check_Arg_Count (1);
11374                Check_Arg_Is_One_Of (Arg1, Name_Semaphore, Name_No);
11375             end if;
11376
11377          ----------------------------------
11378          -- Preelaborable_Initialization --
11379          ----------------------------------
11380
11381          --  pragma Preelaborable_Initialization (DIRECT_NAME);
11382
11383          when Pragma_Preelaborable_Initialization => Preelab_Init : declare
11384             Ent : Entity_Id;
11385
11386          begin
11387             Ada_2005_Pragma;
11388             Check_Arg_Count (1);
11389             Check_No_Identifiers;
11390             Check_Arg_Is_Identifier (Arg1);
11391             Check_Arg_Is_Local_Name (Arg1);
11392             Check_First_Subtype (Arg1);
11393             Ent := Entity (Get_Pragma_Arg (Arg1));
11394
11395             if not (Is_Private_Type (Ent)
11396                       or else
11397                     Is_Protected_Type (Ent)
11398                       or else
11399                     (Is_Generic_Type (Ent) and then Is_Derived_Type (Ent)))
11400             then
11401                Error_Pragma_Arg
11402                  ("pragma % can only be applied to private, formal derived or "
11403                   & "protected type",
11404                   Arg1);
11405             end if;
11406
11407             --  Give an error if the pragma is applied to a protected type that
11408             --  does not qualify (due to having entries, or due to components
11409             --  that do not qualify).
11410
11411             if Is_Protected_Type (Ent)
11412               and then not Has_Preelaborable_Initialization (Ent)
11413             then
11414                Error_Msg_N
11415                  ("protected type & does not have preelaborable " &
11416                   "initialization", Ent);
11417
11418             --  Otherwise mark the type as definitely having preelaborable
11419             --  initialization.
11420
11421             else
11422                Set_Known_To_Have_Preelab_Init (Ent);
11423             end if;
11424
11425             if Has_Pragma_Preelab_Init (Ent)
11426               and then Warn_On_Redundant_Constructs
11427             then
11428                Error_Pragma ("?duplicate pragma%!");
11429             else
11430                Set_Has_Pragma_Preelab_Init (Ent);
11431             end if;
11432          end Preelab_Init;
11433
11434          --------------------
11435          -- Persistent_BSS --
11436          --------------------
11437
11438          --  pragma Persistent_BSS [(object_NAME)];
11439
11440          when Pragma_Persistent_BSS => Persistent_BSS :  declare
11441             Decl : Node_Id;
11442             Ent  : Entity_Id;
11443             Prag : Node_Id;
11444
11445          begin
11446             GNAT_Pragma;
11447             Check_At_Most_N_Arguments (1);
11448
11449             --  Case of application to specific object (one argument)
11450
11451             if Arg_Count = 1 then
11452                Check_Arg_Is_Library_Level_Local_Name (Arg1);
11453
11454                if not Is_Entity_Name (Get_Pragma_Arg (Arg1))
11455                  or else not
11456                   Ekind_In (Entity (Get_Pragma_Arg (Arg1)), E_Variable,
11457                                                             E_Constant)
11458                then
11459                   Error_Pragma_Arg ("pragma% only applies to objects", Arg1);
11460                end if;
11461
11462                Ent := Entity (Get_Pragma_Arg (Arg1));
11463                Decl := Parent (Ent);
11464
11465                if Rep_Item_Too_Late (Ent, N) then
11466                   return;
11467                end if;
11468
11469                if Present (Expression (Decl)) then
11470                   Error_Pragma_Arg
11471                     ("object for pragma% cannot have initialization", Arg1);
11472                end if;
11473
11474                if not Is_Potentially_Persistent_Type (Etype (Ent)) then
11475                   Error_Pragma_Arg
11476                     ("object type for pragma% is not potentially persistent",
11477                      Arg1);
11478                end if;
11479
11480                Check_Duplicate_Pragma (Ent);
11481
11482                Prag :=
11483                  Make_Linker_Section_Pragma
11484                    (Ent, Sloc (N), ".persistent.bss");
11485                Insert_After (N, Prag);
11486                Analyze (Prag);
11487
11488             --  Case of use as configuration pragma with no arguments
11489
11490             else
11491                Check_Valid_Configuration_Pragma;
11492                Persistent_BSS_Mode := True;
11493             end if;
11494          end Persistent_BSS;
11495
11496          -------------
11497          -- Polling --
11498          -------------
11499
11500          --  pragma Polling (ON | OFF);
11501
11502          when Pragma_Polling =>
11503             GNAT_Pragma;
11504             Check_Arg_Count (1);
11505             Check_No_Identifiers;
11506             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
11507             Polling_Required := (Chars (Get_Pragma_Arg (Arg1)) = Name_On);
11508
11509          -------------------
11510          -- Postcondition --
11511          -------------------
11512
11513          --  pragma Postcondition ([Check   =>] Boolean_EXPRESSION
11514          --                      [,[Message =>] String_EXPRESSION]);
11515
11516          when Pragma_Postcondition => Postcondition : declare
11517             In_Body : Boolean;
11518             pragma Warnings (Off, In_Body);
11519
11520          begin
11521             GNAT_Pragma;
11522             Check_At_Least_N_Arguments (1);
11523             Check_At_Most_N_Arguments (2);
11524             Check_Optional_Identifier (Arg1, Name_Check);
11525
11526             --  All we need to do here is call the common check procedure,
11527             --  the remainder of the processing is found in Sem_Ch6/Sem_Ch7.
11528
11529             Check_Precondition_Postcondition (In_Body);
11530          end Postcondition;
11531
11532          ------------------
11533          -- Precondition --
11534          ------------------
11535
11536          --  pragma Precondition ([Check   =>] Boolean_EXPRESSION
11537          --                     [,[Message =>] String_EXPRESSION]);
11538
11539          when Pragma_Precondition => Precondition : declare
11540             In_Body : Boolean;
11541
11542          begin
11543             GNAT_Pragma;
11544             Check_At_Least_N_Arguments (1);
11545             Check_At_Most_N_Arguments (2);
11546             Check_Optional_Identifier (Arg1, Name_Check);
11547             Check_Precondition_Postcondition (In_Body);
11548
11549             --  If in spec, nothing more to do. If in body, then we convert the
11550             --  pragma to pragma Check (Precondition, cond [, msg]). Note we do
11551             --  this whether or not precondition checks are enabled. That works
11552             --  fine since pragma Check will do this check, and will also
11553             --  analyze the condition itself in the proper context.
11554
11555             if In_Body then
11556                Rewrite (N,
11557                  Make_Pragma (Loc,
11558                    Chars => Name_Check,
11559                    Pragma_Argument_Associations => New_List (
11560                      Make_Pragma_Argument_Association (Loc,
11561                        Expression => Make_Identifier (Loc, Name_Precondition)),
11562
11563                      Make_Pragma_Argument_Association (Sloc (Arg1),
11564                        Expression => Relocate_Node (Get_Pragma_Arg (Arg1))))));
11565
11566                if Arg_Count = 2 then
11567                   Append_To (Pragma_Argument_Associations (N),
11568                     Make_Pragma_Argument_Association (Sloc (Arg2),
11569                       Expression => Relocate_Node (Get_Pragma_Arg (Arg2))));
11570                end if;
11571
11572                Analyze (N);
11573             end if;
11574          end Precondition;
11575
11576          ---------------
11577          -- Predicate --
11578          ---------------
11579
11580          --  pragma Predicate
11581          --    ([Entity =>] type_LOCAL_NAME,
11582          --     [Check  =>] EXPRESSION);
11583
11584          when Pragma_Predicate => Predicate : declare
11585             Type_Id : Node_Id;
11586             Typ     : Entity_Id;
11587
11588             Discard : Boolean;
11589             pragma Unreferenced (Discard);
11590
11591          begin
11592             GNAT_Pragma;
11593             Check_Arg_Count (2);
11594             Check_Optional_Identifier (Arg1, Name_Entity);
11595             Check_Optional_Identifier (Arg2, Name_Check);
11596
11597             Check_Arg_Is_Local_Name (Arg1);
11598
11599             Type_Id := Get_Pragma_Arg (Arg1);
11600             Find_Type (Type_Id);
11601             Typ := Entity (Type_Id);
11602
11603             if Typ = Any_Type then
11604                return;
11605             end if;
11606
11607             --  The remaining processing is simply to link the pragma on to
11608             --  the rep item chain, for processing when the type is frozen.
11609             --  This is accomplished by a call to Rep_Item_Too_Late. We also
11610             --  mark the type as having predicates.
11611
11612             Set_Has_Predicates (Typ);
11613             Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
11614          end Predicate;
11615
11616          ------------------
11617          -- Preelaborate --
11618          ------------------
11619
11620          --  pragma Preelaborate [(library_unit_NAME)];
11621
11622          --  Set the flag Is_Preelaborated of program unit name entity
11623
11624          when Pragma_Preelaborate => Preelaborate : declare
11625             Pa  : constant Node_Id   := Parent (N);
11626             Pk  : constant Node_Kind := Nkind (Pa);
11627             Ent : Entity_Id;
11628
11629          begin
11630             Check_Ada_83_Warning;
11631             Check_Valid_Library_Unit_Pragma;
11632
11633             if Nkind (N) = N_Null_Statement then
11634                return;
11635             end if;
11636
11637             Ent := Find_Lib_Unit_Name;
11638             Check_Duplicate_Pragma (Ent);
11639
11640             --  This filters out pragmas inside generic parent then
11641             --  show up inside instantiation
11642
11643             if Present (Ent)
11644               and then not (Pk = N_Package_Specification
11645                              and then Present (Generic_Parent (Pa)))
11646             then
11647                if not Debug_Flag_U then
11648                   Set_Is_Preelaborated (Ent);
11649                   Set_Suppress_Elaboration_Warnings (Ent);
11650                end if;
11651             end if;
11652          end Preelaborate;
11653
11654          ---------------------
11655          -- Preelaborate_05 --
11656          ---------------------
11657
11658          --  pragma Preelaborate_05 [(library_unit_NAME)];
11659
11660          --  This pragma is useable only in GNAT_Mode, where it is used like
11661          --  pragma Preelaborate but it is only effective in Ada 2005 mode
11662          --  (otherwise it is ignored). This is used to implement AI-362 which
11663          --  recategorizes some run-time packages in Ada 2005 mode.
11664
11665          when Pragma_Preelaborate_05 => Preelaborate_05 : declare
11666             Ent : Entity_Id;
11667
11668          begin
11669             GNAT_Pragma;
11670             Check_Valid_Library_Unit_Pragma;
11671
11672             if not GNAT_Mode then
11673                Error_Pragma ("pragma% only available in GNAT mode");
11674             end if;
11675
11676             if Nkind (N) = N_Null_Statement then
11677                return;
11678             end if;
11679
11680             --  This is one of the few cases where we need to test the value of
11681             --  Ada_Version_Explicit rather than Ada_Version (which is always
11682             --  set to Ada_2012 in a predefined unit), we need to know the
11683             --  explicit version set to know if this pragma is active.
11684
11685             if Ada_Version_Explicit >= Ada_2005 then
11686                Ent := Find_Lib_Unit_Name;
11687                Set_Is_Preelaborated (Ent);
11688                Set_Suppress_Elaboration_Warnings (Ent);
11689             end if;
11690          end Preelaborate_05;
11691
11692          --------------
11693          -- Priority --
11694          --------------
11695
11696          --  pragma Priority (EXPRESSION);
11697
11698          when Pragma_Priority => Priority : declare
11699             P   : constant Node_Id := Parent (N);
11700             Arg : Node_Id;
11701
11702          begin
11703             Check_No_Identifiers;
11704             Check_Arg_Count (1);
11705
11706             --  Subprogram case
11707
11708             if Nkind (P) = N_Subprogram_Body then
11709                Check_In_Main_Program;
11710
11711                Arg := Get_Pragma_Arg (Arg1);
11712                Analyze_And_Resolve (Arg, Standard_Integer);
11713
11714                --  Must be static
11715
11716                if not Is_Static_Expression (Arg) then
11717                   Flag_Non_Static_Expr
11718                     ("main subprogram priority is not static!", Arg);
11719                   raise Pragma_Exit;
11720
11721                --  If constraint error, then we already signalled an error
11722
11723                elsif Raises_Constraint_Error (Arg) then
11724                   null;
11725
11726                --  Otherwise check in range
11727
11728                else
11729                   declare
11730                      Val : constant Uint := Expr_Value (Arg);
11731
11732                   begin
11733                      if Val < 0
11734                        or else Val > Expr_Value (Expression
11735                                        (Parent (RTE (RE_Max_Priority))))
11736                      then
11737                         Error_Pragma_Arg
11738                           ("main subprogram priority is out of range", Arg1);
11739                      end if;
11740                   end;
11741                end if;
11742
11743                Set_Main_Priority
11744                     (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
11745
11746                --  Load an arbitrary entity from System.Tasking to make sure
11747                --  this package is implicitly with'ed, since we need to have
11748                --  the tasking run-time active for the pragma Priority to have
11749                --  any effect.
11750
11751                declare
11752                   Discard : Entity_Id;
11753                   pragma Warnings (Off, Discard);
11754                begin
11755                   Discard := RTE (RE_Task_List);
11756                end;
11757
11758             --  Task or Protected, must be of type Integer
11759
11760             elsif Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
11761                Arg := Get_Pragma_Arg (Arg1);
11762
11763                --  The expression must be analyzed in the special manner
11764                --  described in "Handling of Default and Per-Object
11765                --  Expressions" in sem.ads.
11766
11767                Preanalyze_Spec_Expression (Arg, Standard_Integer);
11768
11769                if not Is_Static_Expression (Arg) then
11770                   Check_Restriction (Static_Priorities, Arg);
11771                end if;
11772
11773             --  Anything else is incorrect
11774
11775             else
11776                Pragma_Misplaced;
11777             end if;
11778
11779             if Has_Pragma_Priority (P) then
11780                Error_Pragma ("duplicate pragma% not allowed");
11781             else
11782                Set_Has_Pragma_Priority (P, True);
11783
11784                if Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
11785                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
11786                   --  exp_ch9 should use this ???
11787                end if;
11788             end if;
11789          end Priority;
11790
11791          -----------------------------------
11792          -- Priority_Specific_Dispatching --
11793          -----------------------------------
11794
11795          --  pragma Priority_Specific_Dispatching (
11796          --    policy_IDENTIFIER,
11797          --    first_priority_EXPRESSION,
11798          --    last_priority_EXPRESSION);
11799
11800          when Pragma_Priority_Specific_Dispatching =>
11801          Priority_Specific_Dispatching : declare
11802             Prio_Id : constant Entity_Id := RTE (RE_Any_Priority);
11803             --  This is the entity System.Any_Priority;
11804
11805             DP          : Character;
11806             Lower_Bound : Node_Id;
11807             Upper_Bound : Node_Id;
11808             Lower_Val   : Uint;
11809             Upper_Val   : Uint;
11810
11811          begin
11812             Ada_2005_Pragma;
11813             Check_Arg_Count (3);
11814             Check_No_Identifiers;
11815             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
11816             Check_Valid_Configuration_Pragma;
11817             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
11818             DP := Fold_Upper (Name_Buffer (1));
11819
11820             Lower_Bound := Get_Pragma_Arg (Arg2);
11821             Check_Arg_Is_Static_Expression (Lower_Bound, Standard_Integer);
11822             Lower_Val := Expr_Value (Lower_Bound);
11823
11824             Upper_Bound := Get_Pragma_Arg (Arg3);
11825             Check_Arg_Is_Static_Expression (Upper_Bound, Standard_Integer);
11826             Upper_Val := Expr_Value (Upper_Bound);
11827
11828             --  It is not allowed to use Task_Dispatching_Policy and
11829             --  Priority_Specific_Dispatching in the same partition.
11830
11831             if Task_Dispatching_Policy /= ' ' then
11832                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
11833                Error_Pragma
11834                  ("pragma% incompatible with Task_Dispatching_Policy#");
11835
11836             --  Check lower bound in range
11837
11838             elsif Lower_Val < Expr_Value (Type_Low_Bound (Prio_Id))
11839                     or else
11840                   Lower_Val > Expr_Value (Type_High_Bound (Prio_Id))
11841             then
11842                Error_Pragma_Arg
11843                  ("first_priority is out of range", Arg2);
11844
11845             --  Check upper bound in range
11846
11847             elsif Upper_Val < Expr_Value (Type_Low_Bound (Prio_Id))
11848                     or else
11849                   Upper_Val > Expr_Value (Type_High_Bound (Prio_Id))
11850             then
11851                Error_Pragma_Arg
11852                  ("last_priority is out of range", Arg3);
11853
11854             --  Check that the priority range is valid
11855
11856             elsif Lower_Val > Upper_Val then
11857                Error_Pragma
11858                  ("last_priority_expression must be greater than" &
11859                   " or equal to first_priority_expression");
11860
11861             --  Store the new policy, but always preserve System_Location since
11862             --  we like the error message with the run-time name.
11863
11864             else
11865                --  Check overlapping in the priority ranges specified in other
11866                --  Priority_Specific_Dispatching pragmas within the same
11867                --  partition. We can only check those we know about!
11868
11869                for J in
11870                   Specific_Dispatching.First .. Specific_Dispatching.Last
11871                loop
11872                   if Specific_Dispatching.Table (J).First_Priority in
11873                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
11874                   or else Specific_Dispatching.Table (J).Last_Priority in
11875                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
11876                   then
11877                      Error_Msg_Sloc :=
11878                        Specific_Dispatching.Table (J).Pragma_Loc;
11879                         Error_Pragma
11880                           ("priority range overlaps with "
11881                            & "Priority_Specific_Dispatching#");
11882                   end if;
11883                end loop;
11884
11885                --  The use of Priority_Specific_Dispatching is incompatible
11886                --  with Task_Dispatching_Policy.
11887
11888                if Task_Dispatching_Policy /= ' ' then
11889                   Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
11890                      Error_Pragma
11891                        ("Priority_Specific_Dispatching incompatible "
11892                         & "with Task_Dispatching_Policy#");
11893                end if;
11894
11895                --  The use of Priority_Specific_Dispatching forces ceiling
11896                --  locking policy.
11897
11898                if Locking_Policy /= ' ' and then Locking_Policy /= 'C' then
11899                   Error_Msg_Sloc := Locking_Policy_Sloc;
11900                      Error_Pragma
11901                        ("Priority_Specific_Dispatching incompatible "
11902                         & "with Locking_Policy#");
11903
11904                --  Set the Ceiling_Locking policy, but preserve System_Location
11905                --  since we like the error message with the run time name.
11906
11907                else
11908                   Locking_Policy := 'C';
11909
11910                   if Locking_Policy_Sloc /= System_Location then
11911                      Locking_Policy_Sloc := Loc;
11912                   end if;
11913                end if;
11914
11915                --  Add entry in the table
11916
11917                Specific_Dispatching.Append
11918                     ((Dispatching_Policy => DP,
11919                       First_Priority     => UI_To_Int (Lower_Val),
11920                       Last_Priority      => UI_To_Int (Upper_Val),
11921                       Pragma_Loc         => Loc));
11922             end if;
11923          end Priority_Specific_Dispatching;
11924
11925          -------------
11926          -- Profile --
11927          -------------
11928
11929          --  pragma Profile (profile_IDENTIFIER);
11930
11931          --  profile_IDENTIFIER => Restricted | Ravenscar
11932
11933          when Pragma_Profile =>
11934             Ada_2005_Pragma;
11935             Check_Arg_Count (1);
11936             Check_Valid_Configuration_Pragma;
11937             Check_No_Identifiers;
11938
11939             declare
11940                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
11941             begin
11942                if Chars (Argx) = Name_Ravenscar then
11943                   Set_Ravenscar_Profile (N);
11944                elsif Chars (Argx) = Name_Restricted then
11945                   Set_Profile_Restrictions
11946                     (Restricted, N, Warn => Treat_Restrictions_As_Warnings);
11947                else
11948                   Error_Pragma_Arg ("& is not a valid profile", Argx);
11949                end if;
11950             end;
11951
11952          ----------------------
11953          -- Profile_Warnings --
11954          ----------------------
11955
11956          --  pragma Profile_Warnings (profile_IDENTIFIER);
11957
11958          --  profile_IDENTIFIER => Restricted | Ravenscar
11959
11960          when Pragma_Profile_Warnings =>
11961             GNAT_Pragma;
11962             Check_Arg_Count (1);
11963             Check_Valid_Configuration_Pragma;
11964             Check_No_Identifiers;
11965
11966             declare
11967                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
11968             begin
11969                if Chars (Argx) = Name_Ravenscar then
11970                   Set_Profile_Restrictions (Ravenscar, N, Warn => True);
11971                elsif Chars (Argx) = Name_Restricted then
11972                   Set_Profile_Restrictions (Restricted, N, Warn => True);
11973                else
11974                   Error_Pragma_Arg ("& is not a valid profile", Argx);
11975                end if;
11976             end;
11977
11978          --------------------------
11979          -- Propagate_Exceptions --
11980          --------------------------
11981
11982          --  pragma Propagate_Exceptions;
11983
11984          --  Note: this pragma is obsolete and has no effect
11985
11986          when Pragma_Propagate_Exceptions =>
11987             GNAT_Pragma;
11988             Check_Arg_Count (0);
11989
11990             if In_Extended_Main_Source_Unit (N) then
11991                Propagate_Exceptions := True;
11992             end if;
11993
11994          ------------------
11995          -- Psect_Object --
11996          ------------------
11997
11998          --  pragma Psect_Object (
11999          --        [Internal =>] LOCAL_NAME,
12000          --     [, [External =>] EXTERNAL_SYMBOL]
12001          --     [, [Size     =>] EXTERNAL_SYMBOL]);
12002
12003          when Pragma_Psect_Object | Pragma_Common_Object =>
12004          Psect_Object : declare
12005             Args  : Args_List (1 .. 3);
12006             Names : constant Name_List (1 .. 3) := (
12007                       Name_Internal,
12008                       Name_External,
12009                       Name_Size);
12010
12011             Internal : Node_Id renames Args (1);
12012             External : Node_Id renames Args (2);
12013             Size     : Node_Id renames Args (3);
12014
12015             Def_Id : Entity_Id;
12016
12017             procedure Check_Too_Long (Arg : Node_Id);
12018             --  Posts message if the argument is an identifier with more
12019             --  than 31 characters, or a string literal with more than
12020             --  31 characters, and we are operating under VMS
12021
12022             --------------------
12023             -- Check_Too_Long --
12024             --------------------
12025
12026             procedure Check_Too_Long (Arg : Node_Id) is
12027                X : constant Node_Id := Original_Node (Arg);
12028
12029             begin
12030                if not Nkind_In (X, N_String_Literal, N_Identifier) then
12031                   Error_Pragma_Arg
12032                     ("inappropriate argument for pragma %", Arg);
12033                end if;
12034
12035                if OpenVMS_On_Target then
12036                   if (Nkind (X) = N_String_Literal
12037                        and then String_Length (Strval (X)) > 31)
12038                     or else
12039                      (Nkind (X) = N_Identifier
12040                        and then Length_Of_Name (Chars (X)) > 31)
12041                   then
12042                      Error_Pragma_Arg
12043                        ("argument for pragma % is longer than 31 characters",
12044                         Arg);
12045                   end if;
12046                end if;
12047             end Check_Too_Long;
12048
12049          --  Start of processing for Common_Object/Psect_Object
12050
12051          begin
12052             GNAT_Pragma;
12053             Gather_Associations (Names, Args);
12054             Process_Extended_Import_Export_Internal_Arg (Internal);
12055
12056             Def_Id := Entity (Internal);
12057
12058             if not Ekind_In (Def_Id, E_Constant, E_Variable) then
12059                Error_Pragma_Arg
12060                  ("pragma% must designate an object", Internal);
12061             end if;
12062
12063             Check_Too_Long (Internal);
12064
12065             if Is_Imported (Def_Id) or else Is_Exported (Def_Id) then
12066                Error_Pragma_Arg
12067                  ("cannot use pragma% for imported/exported object",
12068                   Internal);
12069             end if;
12070
12071             if Is_Concurrent_Type (Etype (Internal)) then
12072                Error_Pragma_Arg
12073                  ("cannot specify pragma % for task/protected object",
12074                   Internal);
12075             end if;
12076
12077             if Has_Rep_Pragma (Def_Id, Name_Common_Object)
12078                  or else
12079                Has_Rep_Pragma (Def_Id, Name_Psect_Object)
12080             then
12081                Error_Msg_N ("?duplicate Common/Psect_Object pragma", N);
12082             end if;
12083
12084             if Ekind (Def_Id) = E_Constant then
12085                Error_Pragma_Arg
12086                  ("cannot specify pragma % for a constant", Internal);
12087             end if;
12088
12089             if Is_Record_Type (Etype (Internal)) then
12090                declare
12091                   Ent  : Entity_Id;
12092                   Decl : Entity_Id;
12093
12094                begin
12095                   Ent := First_Entity (Etype (Internal));
12096                   while Present (Ent) loop
12097                      Decl := Declaration_Node (Ent);
12098
12099                      if Ekind (Ent) = E_Component
12100                        and then Nkind (Decl) = N_Component_Declaration
12101                        and then Present (Expression (Decl))
12102                        and then Warn_On_Export_Import
12103                      then
12104                         Error_Msg_N
12105                           ("?object for pragma % has defaults", Internal);
12106                         exit;
12107
12108                      else
12109                         Next_Entity (Ent);
12110                      end if;
12111                   end loop;
12112                end;
12113             end if;
12114
12115             if Present (Size) then
12116                Check_Too_Long (Size);
12117             end if;
12118
12119             if Present (External) then
12120                Check_Arg_Is_External_Name (External);
12121                Check_Too_Long (External);
12122             end if;
12123
12124             --  If all error tests pass, link pragma on to the rep item chain
12125
12126             Record_Rep_Item (Def_Id, N);
12127          end Psect_Object;
12128
12129          ----------
12130          -- Pure --
12131          ----------
12132
12133          --  pragma Pure [(library_unit_NAME)];
12134
12135          when Pragma_Pure => Pure : declare
12136             Ent : Entity_Id;
12137
12138          begin
12139             Check_Ada_83_Warning;
12140             Check_Valid_Library_Unit_Pragma;
12141
12142             if Nkind (N) = N_Null_Statement then
12143                return;
12144             end if;
12145
12146             Ent := Find_Lib_Unit_Name;
12147             Set_Is_Pure (Ent);
12148             Set_Has_Pragma_Pure (Ent);
12149             Set_Suppress_Elaboration_Warnings (Ent);
12150          end Pure;
12151
12152          -------------
12153          -- Pure_05 --
12154          -------------
12155
12156          --  pragma Pure_05 [(library_unit_NAME)];
12157
12158          --  This pragma is useable only in GNAT_Mode, where it is used like
12159          --  pragma Pure but it is only effective in Ada 2005 mode (otherwise
12160          --  it is ignored). It may be used after a pragma Preelaborate, in
12161          --  which case it overrides the effect of the pragma Preelaborate.
12162          --  This is used to implement AI-362 which recategorizes some run-time
12163          --  packages in Ada 2005 mode.
12164
12165          when Pragma_Pure_05 => Pure_05 : declare
12166             Ent : Entity_Id;
12167
12168          begin
12169             GNAT_Pragma;
12170             Check_Valid_Library_Unit_Pragma;
12171
12172             if not GNAT_Mode then
12173                Error_Pragma ("pragma% only available in GNAT mode");
12174             end if;
12175
12176             if Nkind (N) = N_Null_Statement then
12177                return;
12178             end if;
12179
12180             --  This is one of the few cases where we need to test the value of
12181             --  Ada_Version_Explicit rather than Ada_Version (which is always
12182             --  set to Ada_2012 in a predefined unit), we need to know the
12183             --  explicit version set to know if this pragma is active.
12184
12185             if Ada_Version_Explicit >= Ada_2005 then
12186                Ent := Find_Lib_Unit_Name;
12187                Set_Is_Preelaborated (Ent, False);
12188                Set_Is_Pure (Ent);
12189                Set_Suppress_Elaboration_Warnings (Ent);
12190             end if;
12191          end Pure_05;
12192
12193          -------------------
12194          -- Pure_Function --
12195          -------------------
12196
12197          --  pragma Pure_Function ([Entity =>] function_LOCAL_NAME);
12198
12199          when Pragma_Pure_Function => Pure_Function : declare
12200             E_Id      : Node_Id;
12201             E         : Entity_Id;
12202             Def_Id    : Entity_Id;
12203             Effective : Boolean := False;
12204
12205          begin
12206             GNAT_Pragma;
12207             Check_Arg_Count (1);
12208             Check_Optional_Identifier (Arg1, Name_Entity);
12209             Check_Arg_Is_Local_Name (Arg1);
12210             E_Id := Get_Pragma_Arg (Arg1);
12211
12212             if Error_Posted (E_Id) then
12213                return;
12214             end if;
12215
12216             --  Loop through homonyms (overloadings) of referenced entity
12217
12218             E := Entity (E_Id);
12219
12220             if Present (E) then
12221                loop
12222                   Def_Id := Get_Base_Subprogram (E);
12223
12224                   if not Ekind_In (Def_Id, E_Function,
12225                                            E_Generic_Function,
12226                                            E_Operator)
12227                   then
12228                      Error_Pragma_Arg
12229                        ("pragma% requires a function name", Arg1);
12230                   end if;
12231
12232                   Set_Is_Pure (Def_Id);
12233
12234                   if not Has_Pragma_Pure_Function (Def_Id) then
12235                      Set_Has_Pragma_Pure_Function (Def_Id);
12236                      Effective := True;
12237                   end if;
12238
12239                   exit when From_Aspect_Specification (N);
12240                   E := Homonym (E);
12241                   exit when No (E) or else Scope (E) /= Current_Scope;
12242                end loop;
12243
12244                if not Effective
12245                  and then Warn_On_Redundant_Constructs
12246                then
12247                   Error_Msg_NE
12248                     ("pragma Pure_Function on& is redundant?",
12249                      N, Entity (E_Id));
12250                end if;
12251             end if;
12252          end Pure_Function;
12253
12254          --------------------
12255          -- Queuing_Policy --
12256          --------------------
12257
12258          --  pragma Queuing_Policy (policy_IDENTIFIER);
12259
12260          when Pragma_Queuing_Policy => declare
12261             QP : Character;
12262
12263          begin
12264             Check_Ada_83_Warning;
12265             Check_Arg_Count (1);
12266             Check_No_Identifiers;
12267             Check_Arg_Is_Queuing_Policy (Arg1);
12268             Check_Valid_Configuration_Pragma;
12269             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
12270             QP := Fold_Upper (Name_Buffer (1));
12271
12272             if Queuing_Policy /= ' '
12273               and then Queuing_Policy /= QP
12274             then
12275                Error_Msg_Sloc := Queuing_Policy_Sloc;
12276                Error_Pragma ("queuing policy incompatible with policy#");
12277
12278             --  Set new policy, but always preserve System_Location since we
12279             --  like the error message with the run time name.
12280
12281             else
12282                Queuing_Policy := QP;
12283
12284                if Queuing_Policy_Sloc /= System_Location then
12285                   Queuing_Policy_Sloc := Loc;
12286                end if;
12287             end if;
12288          end;
12289
12290          -----------------------
12291          -- Relative_Deadline --
12292          -----------------------
12293
12294          --  pragma Relative_Deadline (time_span_EXPRESSION);
12295
12296          when Pragma_Relative_Deadline => Relative_Deadline : declare
12297             P   : constant Node_Id := Parent (N);
12298             Arg : Node_Id;
12299
12300          begin
12301             Ada_2005_Pragma;
12302             Check_No_Identifiers;
12303             Check_Arg_Count (1);
12304
12305             Arg := Get_Pragma_Arg (Arg1);
12306
12307             --  The expression must be analyzed in the special manner described
12308             --  in "Handling of Default and Per-Object Expressions" in sem.ads.
12309
12310             Preanalyze_Spec_Expression (Arg, RTE (RE_Time_Span));
12311
12312             --  Subprogram case
12313
12314             if Nkind (P) = N_Subprogram_Body then
12315                Check_In_Main_Program;
12316
12317             --  Tasks
12318
12319             elsif Nkind (P) = N_Task_Definition then
12320                null;
12321
12322             --  Anything else is incorrect
12323
12324             else
12325                Pragma_Misplaced;
12326             end if;
12327
12328             if Has_Relative_Deadline_Pragma (P) then
12329                Error_Pragma ("duplicate pragma% not allowed");
12330             else
12331                Set_Has_Relative_Deadline_Pragma (P, True);
12332
12333                if Nkind (P) = N_Task_Definition then
12334                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
12335                end if;
12336             end if;
12337          end Relative_Deadline;
12338
12339          ---------------------------
12340          -- Remote_Call_Interface --
12341          ---------------------------
12342
12343          --  pragma Remote_Call_Interface [(library_unit_NAME)];
12344
12345          when Pragma_Remote_Call_Interface => Remote_Call_Interface : declare
12346             Cunit_Node : Node_Id;
12347             Cunit_Ent  : Entity_Id;
12348             K          : Node_Kind;
12349
12350          begin
12351             Check_Ada_83_Warning;
12352             Check_Valid_Library_Unit_Pragma;
12353
12354             if Nkind (N) = N_Null_Statement then
12355                return;
12356             end if;
12357
12358             Cunit_Node := Cunit (Current_Sem_Unit);
12359             K          := Nkind (Unit (Cunit_Node));
12360             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12361
12362             if K = N_Package_Declaration
12363               or else K = N_Generic_Package_Declaration
12364               or else K = N_Subprogram_Declaration
12365               or else K = N_Generic_Subprogram_Declaration
12366               or else (K = N_Subprogram_Body
12367                          and then Acts_As_Spec (Unit (Cunit_Node)))
12368             then
12369                null;
12370             else
12371                Error_Pragma (
12372                  "pragma% must apply to package or subprogram declaration");
12373             end if;
12374
12375             Set_Is_Remote_Call_Interface (Cunit_Ent);
12376          end Remote_Call_Interface;
12377
12378          ------------------
12379          -- Remote_Types --
12380          ------------------
12381
12382          --  pragma Remote_Types [(library_unit_NAME)];
12383
12384          when Pragma_Remote_Types => Remote_Types : declare
12385             Cunit_Node : Node_Id;
12386             Cunit_Ent  : Entity_Id;
12387
12388          begin
12389             Check_Ada_83_Warning;
12390             Check_Valid_Library_Unit_Pragma;
12391
12392             if Nkind (N) = N_Null_Statement then
12393                return;
12394             end if;
12395
12396             Cunit_Node := Cunit (Current_Sem_Unit);
12397             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12398
12399             if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
12400                                                 N_Generic_Package_Declaration)
12401             then
12402                Error_Pragma
12403                  ("pragma% can only apply to a package declaration");
12404             end if;
12405
12406             Set_Is_Remote_Types (Cunit_Ent);
12407          end Remote_Types;
12408
12409          ---------------
12410          -- Ravenscar --
12411          ---------------
12412
12413          --  pragma Ravenscar;
12414
12415          when Pragma_Ravenscar =>
12416             GNAT_Pragma;
12417             Check_Arg_Count (0);
12418             Check_Valid_Configuration_Pragma;
12419             Set_Ravenscar_Profile (N);
12420
12421             if Warn_On_Obsolescent_Feature then
12422                Error_Msg_N ("pragma Ravenscar is an obsolescent feature?", N);
12423                Error_Msg_N ("|use pragma Profile (Ravenscar) instead", N);
12424             end if;
12425
12426          -------------------------
12427          -- Restricted_Run_Time --
12428          -------------------------
12429
12430          --  pragma Restricted_Run_Time;
12431
12432          when Pragma_Restricted_Run_Time =>
12433             GNAT_Pragma;
12434             Check_Arg_Count (0);
12435             Check_Valid_Configuration_Pragma;
12436             Set_Profile_Restrictions
12437               (Restricted, N, Warn => Treat_Restrictions_As_Warnings);
12438
12439             if Warn_On_Obsolescent_Feature then
12440                Error_Msg_N
12441                  ("pragma Restricted_Run_Time is an obsolescent feature?", N);
12442                Error_Msg_N ("|use pragma Profile (Restricted) instead", N);
12443             end if;
12444
12445          ------------------
12446          -- Restrictions --
12447          ------------------
12448
12449          --  pragma Restrictions (RESTRICTION {, RESTRICTION});
12450
12451          --  RESTRICTION ::=
12452          --    restriction_IDENTIFIER
12453          --  | restriction_parameter_IDENTIFIER => EXPRESSION
12454
12455          when Pragma_Restrictions =>
12456             Process_Restrictions_Or_Restriction_Warnings
12457               (Warn => Treat_Restrictions_As_Warnings);
12458
12459          --------------------------
12460          -- Restriction_Warnings --
12461          --------------------------
12462
12463          --  pragma Restriction_Warnings (RESTRICTION {, RESTRICTION});
12464
12465          --  RESTRICTION ::=
12466          --    restriction_IDENTIFIER
12467          --  | restriction_parameter_IDENTIFIER => EXPRESSION
12468
12469          when Pragma_Restriction_Warnings =>
12470             GNAT_Pragma;
12471             Process_Restrictions_Or_Restriction_Warnings (Warn => True);
12472
12473          ----------------
12474          -- Reviewable --
12475          ----------------
12476
12477          --  pragma Reviewable;
12478
12479          when Pragma_Reviewable =>
12480             Check_Ada_83_Warning;
12481             Check_Arg_Count (0);
12482
12483             --  Call dummy debugging function rv. This is done to assist front
12484             --  end debugging. By placing a Reviewable pragma in the source
12485             --  program, a breakpoint on rv catches this place in the source,
12486             --  allowing convenient stepping to the point of interest.
12487
12488             rv;
12489
12490          --------------------------
12491          -- Short_Circuit_And_Or --
12492          --------------------------
12493
12494          when Pragma_Short_Circuit_And_Or =>
12495             GNAT_Pragma;
12496             Check_Arg_Count (0);
12497             Check_Valid_Configuration_Pragma;
12498             Short_Circuit_And_Or := True;
12499
12500          -------------------
12501          -- Share_Generic --
12502          -------------------
12503
12504          --  pragma Share_Generic (NAME {, NAME});
12505
12506          when Pragma_Share_Generic =>
12507             GNAT_Pragma;
12508             Process_Generic_List;
12509
12510          ------------
12511          -- Shared --
12512          ------------
12513
12514          --  pragma Shared (LOCAL_NAME);
12515
12516          when Pragma_Shared =>
12517             GNAT_Pragma;
12518             Process_Atomic_Shared_Volatile;
12519
12520          --------------------
12521          -- Shared_Passive --
12522          --------------------
12523
12524          --  pragma Shared_Passive [(library_unit_NAME)];
12525
12526          --  Set the flag Is_Shared_Passive of program unit name entity
12527
12528          when Pragma_Shared_Passive => Shared_Passive : declare
12529             Cunit_Node : Node_Id;
12530             Cunit_Ent  : Entity_Id;
12531
12532          begin
12533             Check_Ada_83_Warning;
12534             Check_Valid_Library_Unit_Pragma;
12535
12536             if Nkind (N) = N_Null_Statement then
12537                return;
12538             end if;
12539
12540             Cunit_Node := Cunit (Current_Sem_Unit);
12541             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12542
12543             if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
12544                                                 N_Generic_Package_Declaration)
12545             then
12546                Error_Pragma
12547                  ("pragma% can only apply to a package declaration");
12548             end if;
12549
12550             Set_Is_Shared_Passive (Cunit_Ent);
12551          end Shared_Passive;
12552
12553          -----------------------
12554          -- Short_Descriptors --
12555          -----------------------
12556
12557          --  pragma Short_Descriptors;
12558
12559          when Pragma_Short_Descriptors =>
12560             GNAT_Pragma;
12561             Check_Arg_Count (0);
12562             Check_Valid_Configuration_Pragma;
12563             Short_Descriptors := True;
12564
12565          ----------------------
12566          -- Source_File_Name --
12567          ----------------------
12568
12569          --  There are five forms for this pragma:
12570
12571          --  pragma Source_File_Name (
12572          --    [UNIT_NAME      =>] unit_NAME,
12573          --     BODY_FILE_NAME =>  STRING_LITERAL
12574          --    [, [INDEX =>] INTEGER_LITERAL]);
12575
12576          --  pragma Source_File_Name (
12577          --    [UNIT_NAME      =>] unit_NAME,
12578          --     SPEC_FILE_NAME =>  STRING_LITERAL
12579          --    [, [INDEX =>] INTEGER_LITERAL]);
12580
12581          --  pragma Source_File_Name (
12582          --     BODY_FILE_NAME  => STRING_LITERAL
12583          --  [, DOT_REPLACEMENT => STRING_LITERAL]
12584          --  [, CASING          => CASING_SPEC]);
12585
12586          --  pragma Source_File_Name (
12587          --     SPEC_FILE_NAME  => STRING_LITERAL
12588          --  [, DOT_REPLACEMENT => STRING_LITERAL]
12589          --  [, CASING          => CASING_SPEC]);
12590
12591          --  pragma Source_File_Name (
12592          --     SUBUNIT_FILE_NAME  => STRING_LITERAL
12593          --  [, DOT_REPLACEMENT    => STRING_LITERAL]
12594          --  [, CASING             => CASING_SPEC]);
12595
12596          --  CASING_SPEC ::= Uppercase | Lowercase | Mixedcase
12597
12598          --  Pragma Source_File_Name_Project (SFNP) is equivalent to pragma
12599          --  Source_File_Name (SFN), however their usage is exclusive: SFN can
12600          --  only be used when no project file is used, while SFNP can only be
12601          --  used when a project file is used.
12602
12603          --  No processing here. Processing was completed during parsing, since
12604          --  we need to have file names set as early as possible. Units are
12605          --  loaded well before semantic processing starts.
12606
12607          --  The only processing we defer to this point is the check for
12608          --  correct placement.
12609
12610          when Pragma_Source_File_Name =>
12611             GNAT_Pragma;
12612             Check_Valid_Configuration_Pragma;
12613
12614          ------------------------------
12615          -- Source_File_Name_Project --
12616          ------------------------------
12617
12618          --  See Source_File_Name for syntax
12619
12620          --  No processing here. Processing was completed during parsing, since
12621          --  we need to have file names set as early as possible. Units are
12622          --  loaded well before semantic processing starts.
12623
12624          --  The only processing we defer to this point is the check for
12625          --  correct placement.
12626
12627          when Pragma_Source_File_Name_Project =>
12628             GNAT_Pragma;
12629             Check_Valid_Configuration_Pragma;
12630
12631             --  Check that a pragma Source_File_Name_Project is used only in a
12632             --  configuration pragmas file.
12633
12634             --  Pragmas Source_File_Name_Project should only be generated by
12635             --  the Project Manager in configuration pragmas files.
12636
12637             --  This is really an ugly test. It seems to depend on some
12638             --  accidental and undocumented property. At the very least it
12639             --  needs to be documented, but it would be better to have a
12640             --  clean way of testing if we are in a configuration file???
12641
12642             if Present (Parent (N)) then
12643                Error_Pragma
12644                  ("pragma% can only appear in a configuration pragmas file");
12645             end if;
12646
12647          ----------------------
12648          -- Source_Reference --
12649          ----------------------
12650
12651          --  pragma Source_Reference (INTEGER_LITERAL [, STRING_LITERAL]);
12652
12653          --  Nothing to do, all processing completed in Par.Prag, since we need
12654          --  the information for possible parser messages that are output.
12655
12656          when Pragma_Source_Reference =>
12657             GNAT_Pragma;
12658
12659          --------------------------------
12660          -- Static_Elaboration_Desired --
12661          --------------------------------
12662
12663          --  pragma Static_Elaboration_Desired (DIRECT_NAME);
12664
12665          when Pragma_Static_Elaboration_Desired =>
12666             GNAT_Pragma;
12667             Check_At_Most_N_Arguments (1);
12668
12669             if Is_Compilation_Unit (Current_Scope)
12670               and then Ekind (Current_Scope) = E_Package
12671             then
12672                Set_Static_Elaboration_Desired (Current_Scope, True);
12673             else
12674                Error_Pragma ("pragma% must apply to a library-level package");
12675             end if;
12676
12677          ------------------
12678          -- Storage_Size --
12679          ------------------
12680
12681          --  pragma Storage_Size (EXPRESSION);
12682
12683          when Pragma_Storage_Size => Storage_Size : declare
12684             P   : constant Node_Id := Parent (N);
12685             Arg : Node_Id;
12686
12687          begin
12688             Check_No_Identifiers;
12689             Check_Arg_Count (1);
12690
12691             --  The expression must be analyzed in the special manner described
12692             --  in "Handling of Default Expressions" in sem.ads.
12693
12694             Arg := Get_Pragma_Arg (Arg1);
12695             Preanalyze_Spec_Expression (Arg, Any_Integer);
12696
12697             if not Is_Static_Expression (Arg) then
12698                Check_Restriction (Static_Storage_Size, Arg);
12699             end if;
12700
12701             if Nkind (P) /= N_Task_Definition then
12702                Pragma_Misplaced;
12703                return;
12704
12705             else
12706                if Has_Storage_Size_Pragma (P) then
12707                   Error_Pragma ("duplicate pragma% not allowed");
12708                else
12709                   Set_Has_Storage_Size_Pragma (P, True);
12710                end if;
12711
12712                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
12713                --  ???  exp_ch9 should use this!
12714             end if;
12715          end Storage_Size;
12716
12717          ------------------
12718          -- Storage_Unit --
12719          ------------------
12720
12721          --  pragma Storage_Unit (NUMERIC_LITERAL);
12722
12723          --  Only permitted argument is System'Storage_Unit value
12724
12725          when Pragma_Storage_Unit =>
12726             Check_No_Identifiers;
12727             Check_Arg_Count (1);
12728             Check_Arg_Is_Integer_Literal (Arg1);
12729
12730             if Intval (Get_Pragma_Arg (Arg1)) /=
12731               UI_From_Int (Ttypes.System_Storage_Unit)
12732             then
12733                Error_Msg_Uint_1 := UI_From_Int (Ttypes.System_Storage_Unit);
12734                Error_Pragma_Arg
12735                  ("the only allowed argument for pragma% is ^", Arg1);
12736             end if;
12737
12738          --------------------
12739          -- Stream_Convert --
12740          --------------------
12741
12742          --  pragma Stream_Convert (
12743          --    [Entity =>] type_LOCAL_NAME,
12744          --    [Read   =>] function_NAME,
12745          --    [Write  =>] function NAME);
12746
12747          when Pragma_Stream_Convert => Stream_Convert : declare
12748
12749             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id);
12750             --  Check that the given argument is the name of a local function
12751             --  of one argument that is not overloaded earlier in the current
12752             --  local scope. A check is also made that the argument is a
12753             --  function with one parameter.
12754
12755             --------------------------------------
12756             -- Check_OK_Stream_Convert_Function --
12757             --------------------------------------
12758
12759             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id) is
12760                Ent : Entity_Id;
12761
12762             begin
12763                Check_Arg_Is_Local_Name (Arg);
12764                Ent := Entity (Get_Pragma_Arg (Arg));
12765
12766                if Has_Homonym (Ent) then
12767                   Error_Pragma_Arg
12768                     ("argument for pragma% may not be overloaded", Arg);
12769                end if;
12770
12771                if Ekind (Ent) /= E_Function
12772                  or else No (First_Formal (Ent))
12773                  or else Present (Next_Formal (First_Formal (Ent)))
12774                then
12775                   Error_Pragma_Arg
12776                     ("argument for pragma% must be" &
12777                      " function of one argument", Arg);
12778                end if;
12779             end Check_OK_Stream_Convert_Function;
12780
12781          --  Start of processing for Stream_Convert
12782
12783          begin
12784             GNAT_Pragma;
12785             Check_Arg_Order ((Name_Entity, Name_Read, Name_Write));
12786             Check_Arg_Count (3);
12787             Check_Optional_Identifier (Arg1, Name_Entity);
12788             Check_Optional_Identifier (Arg2, Name_Read);
12789             Check_Optional_Identifier (Arg3, Name_Write);
12790             Check_Arg_Is_Local_Name (Arg1);
12791             Check_OK_Stream_Convert_Function (Arg2);
12792             Check_OK_Stream_Convert_Function (Arg3);
12793
12794             declare
12795                Typ   : constant Entity_Id :=
12796                          Underlying_Type (Entity (Get_Pragma_Arg (Arg1)));
12797                Read  : constant Entity_Id := Entity (Get_Pragma_Arg (Arg2));
12798                Write : constant Entity_Id := Entity (Get_Pragma_Arg (Arg3));
12799
12800             begin
12801                Check_First_Subtype (Arg1);
12802
12803                --  Check for too early or too late. Note that we don't enforce
12804                --  the rule about primitive operations in this case, since, as
12805                --  is the case for explicit stream attributes themselves, these
12806                --  restrictions are not appropriate. Note that the chaining of
12807                --  the pragma by Rep_Item_Too_Late is actually the critical
12808                --  processing done for this pragma.
12809
12810                if Rep_Item_Too_Early (Typ, N)
12811                     or else
12812                   Rep_Item_Too_Late (Typ, N, FOnly => True)
12813                then
12814                   return;
12815                end if;
12816
12817                --  Return if previous error
12818
12819                if Etype (Typ) = Any_Type
12820                     or else
12821                   Etype (Read) = Any_Type
12822                     or else
12823                   Etype (Write) = Any_Type
12824                then
12825                   return;
12826                end if;
12827
12828                --  Error checks
12829
12830                if Underlying_Type (Etype (Read)) /= Typ then
12831                   Error_Pragma_Arg
12832                     ("incorrect return type for function&", Arg2);
12833                end if;
12834
12835                if Underlying_Type (Etype (First_Formal (Write))) /= Typ then
12836                   Error_Pragma_Arg
12837                     ("incorrect parameter type for function&", Arg3);
12838                end if;
12839
12840                if Underlying_Type (Etype (First_Formal (Read))) /=
12841                   Underlying_Type (Etype (Write))
12842                then
12843                   Error_Pragma_Arg
12844                     ("result type of & does not match Read parameter type",
12845                      Arg3);
12846                end if;
12847             end;
12848          end Stream_Convert;
12849
12850          -------------------------
12851          -- Style_Checks (GNAT) --
12852          -------------------------
12853
12854          --  pragma Style_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
12855
12856          --  This is processed by the parser since some of the style checks
12857          --  take place during source scanning and parsing. This means that
12858          --  we don't need to issue error messages here.
12859
12860          when Pragma_Style_Checks => Style_Checks : declare
12861             A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
12862             S  : String_Id;
12863             C  : Char_Code;
12864
12865          begin
12866             GNAT_Pragma;
12867             Check_No_Identifiers;
12868
12869             --  Two argument form
12870
12871             if Arg_Count = 2 then
12872                Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
12873
12874                declare
12875                   E_Id : Node_Id;
12876                   E    : Entity_Id;
12877
12878                begin
12879                   E_Id := Get_Pragma_Arg (Arg2);
12880                   Analyze (E_Id);
12881
12882                   if not Is_Entity_Name (E_Id) then
12883                      Error_Pragma_Arg
12884                        ("second argument of pragma% must be entity name",
12885                         Arg2);
12886                   end if;
12887
12888                   E := Entity (E_Id);
12889
12890                   if E = Any_Id then
12891                      return;
12892                   else
12893                      loop
12894                         Set_Suppress_Style_Checks (E,
12895                           (Chars (Get_Pragma_Arg (Arg1)) = Name_Off));
12896                         exit when No (Homonym (E));
12897                         E := Homonym (E);
12898                      end loop;
12899                   end if;
12900                end;
12901
12902             --  One argument form
12903
12904             else
12905                Check_Arg_Count (1);
12906
12907                if Nkind (A) = N_String_Literal then
12908                   S   := Strval (A);
12909
12910                   declare
12911                      Slen    : constant Natural := Natural (String_Length (S));
12912                      Options : String (1 .. Slen);
12913                      J       : Natural;
12914
12915                   begin
12916                      J := 1;
12917                      loop
12918                         C := Get_String_Char (S, Int (J));
12919                         exit when not In_Character_Range (C);
12920                         Options (J) := Get_Character (C);
12921
12922                         --  If at end of string, set options. As per discussion
12923                         --  above, no need to check for errors, since we issued
12924                         --  them in the parser.
12925
12926                         if J = Slen then
12927                            Set_Style_Check_Options (Options);
12928                            exit;
12929                         end if;
12930
12931                         J := J + 1;
12932                      end loop;
12933                   end;
12934
12935                elsif Nkind (A) = N_Identifier then
12936                   if Chars (A) = Name_All_Checks then
12937                      if GNAT_Mode then
12938                         Set_GNAT_Style_Check_Options;
12939                      else
12940                         Set_Default_Style_Check_Options;
12941                      end if;
12942
12943                   elsif Chars (A) = Name_On then
12944                      Style_Check := True;
12945
12946                   elsif Chars (A) = Name_Off then
12947                      Style_Check := False;
12948                   end if;
12949                end if;
12950             end if;
12951          end Style_Checks;
12952
12953          --------------
12954          -- Subtitle --
12955          --------------
12956
12957          --  pragma Subtitle ([Subtitle =>] STRING_LITERAL);
12958
12959          when Pragma_Subtitle =>
12960             GNAT_Pragma;
12961             Check_Arg_Count (1);
12962             Check_Optional_Identifier (Arg1, Name_Subtitle);
12963             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
12964             Store_Note (N);
12965
12966          --------------
12967          -- Suppress --
12968          --------------
12969
12970          --  pragma Suppress (IDENTIFIER [, [On =>] NAME]);
12971
12972          when Pragma_Suppress =>
12973             Process_Suppress_Unsuppress (True);
12974
12975          ------------------
12976          -- Suppress_All --
12977          ------------------
12978
12979          --  pragma Suppress_All;
12980
12981          --  The only check made here is that the pragma has no arguments.
12982          --  There are no placement rules, and the processing required (setting
12983          --  the Has_Pragma_Suppress_All flag in the compilation unit node was
12984          --  taken care of by the parser). Process_Compilation_Unit_Pragmas
12985          --  then creates and inserts a pragma Suppress (All_Checks).
12986
12987          when Pragma_Suppress_All =>
12988             GNAT_Pragma;
12989             Check_Arg_Count (0);
12990
12991          -------------------------
12992          -- Suppress_Debug_Info --
12993          -------------------------
12994
12995          --  pragma Suppress_Debug_Info ([Entity =>] LOCAL_NAME);
12996
12997          when Pragma_Suppress_Debug_Info =>
12998             GNAT_Pragma;
12999             Check_Arg_Count (1);
13000             Check_Optional_Identifier (Arg1, Name_Entity);
13001             Check_Arg_Is_Local_Name (Arg1);
13002             Set_Debug_Info_Off (Entity (Get_Pragma_Arg (Arg1)));
13003
13004          ----------------------------------
13005          -- Suppress_Exception_Locations --
13006          ----------------------------------
13007
13008          --  pragma Suppress_Exception_Locations;
13009
13010          when Pragma_Suppress_Exception_Locations =>
13011             GNAT_Pragma;
13012             Check_Arg_Count (0);
13013             Check_Valid_Configuration_Pragma;
13014             Exception_Locations_Suppressed := True;
13015
13016          -----------------------------
13017          -- Suppress_Initialization --
13018          -----------------------------
13019
13020          --  pragma Suppress_Initialization ([Entity =>] type_Name);
13021
13022          when Pragma_Suppress_Initialization => Suppress_Init : declare
13023             E_Id : Node_Id;
13024             E    : Entity_Id;
13025
13026          begin
13027             GNAT_Pragma;
13028             Check_Arg_Count (1);
13029             Check_Optional_Identifier (Arg1, Name_Entity);
13030             Check_Arg_Is_Local_Name (Arg1);
13031
13032             E_Id := Get_Pragma_Arg (Arg1);
13033
13034             if Etype (E_Id) = Any_Type then
13035                return;
13036             end if;
13037
13038             E := Entity (E_Id);
13039
13040             if not Is_Type (E) then
13041                Error_Pragma_Arg ("pragma% requires type or subtype", Arg1);
13042             end if;
13043
13044             if Rep_Item_Too_Early (E, N)
13045                  or else
13046                Rep_Item_Too_Late (E, N, FOnly => True)
13047             then
13048                return;
13049             end if;
13050
13051             --  For incomplete/private type, set flag on full view
13052
13053             if Is_Incomplete_Or_Private_Type (E) then
13054                if No (Full_View (Base_Type (E))) then
13055                   Error_Pragma_Arg
13056                     ("argument of pragma% cannot be an incomplete type", Arg1);
13057                else
13058                   Set_Suppress_Initialization (Full_View (Base_Type (E)));
13059                end if;
13060
13061             --  For first subtype, set flag on base type
13062
13063             elsif Is_First_Subtype (E) then
13064                Set_Suppress_Initialization (Base_Type (E));
13065
13066             --  For other than first subtype, set flag on subtype itself
13067
13068             else
13069                Set_Suppress_Initialization (E);
13070             end if;
13071          end Suppress_Init;
13072
13073          -----------------
13074          -- System_Name --
13075          -----------------
13076
13077          --  pragma System_Name (DIRECT_NAME);
13078
13079          --  Syntax check: one argument, which must be the identifier GNAT or
13080          --  the identifier GCC, no other identifiers are acceptable.
13081
13082          when Pragma_System_Name =>
13083             GNAT_Pragma;
13084             Check_No_Identifiers;
13085             Check_Arg_Count (1);
13086             Check_Arg_Is_One_Of (Arg1, Name_Gcc, Name_Gnat);
13087
13088          -----------------------------
13089          -- Task_Dispatching_Policy --
13090          -----------------------------
13091
13092          --  pragma Task_Dispatching_Policy (policy_IDENTIFIER);
13093
13094          when Pragma_Task_Dispatching_Policy => declare
13095             DP : Character;
13096
13097          begin
13098             Check_Ada_83_Warning;
13099             Check_Arg_Count (1);
13100             Check_No_Identifiers;
13101             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
13102             Check_Valid_Configuration_Pragma;
13103             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
13104             DP := Fold_Upper (Name_Buffer (1));
13105
13106             if Task_Dispatching_Policy /= ' '
13107               and then Task_Dispatching_Policy /= DP
13108             then
13109                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
13110                Error_Pragma
13111                  ("task dispatching policy incompatible with policy#");
13112
13113             --  Set new policy, but always preserve System_Location since we
13114             --  like the error message with the run time name.
13115
13116             else
13117                Task_Dispatching_Policy := DP;
13118
13119                if Task_Dispatching_Policy_Sloc /= System_Location then
13120                   Task_Dispatching_Policy_Sloc := Loc;
13121                end if;
13122             end if;
13123          end;
13124
13125          ---------------
13126          -- Task_Info --
13127          ---------------
13128
13129          --  pragma Task_Info (EXPRESSION);
13130
13131          when Pragma_Task_Info => Task_Info : declare
13132             P : constant Node_Id := Parent (N);
13133
13134          begin
13135             GNAT_Pragma;
13136
13137             if Nkind (P) /= N_Task_Definition then
13138                Error_Pragma ("pragma% must appear in task definition");
13139             end if;
13140
13141             Check_No_Identifiers;
13142             Check_Arg_Count (1);
13143
13144             Analyze_And_Resolve
13145               (Get_Pragma_Arg (Arg1), RTE (RE_Task_Info_Type));
13146
13147             if Etype (Get_Pragma_Arg (Arg1)) = Any_Type then
13148                return;
13149             end if;
13150
13151             if Has_Task_Info_Pragma (P) then
13152                Error_Pragma ("duplicate pragma% not allowed");
13153             else
13154                Set_Has_Task_Info_Pragma (P, True);
13155             end if;
13156          end Task_Info;
13157
13158          ---------------
13159          -- Task_Name --
13160          ---------------
13161
13162          --  pragma Task_Name (string_EXPRESSION);
13163
13164          when Pragma_Task_Name => Task_Name : declare
13165             P   : constant Node_Id := Parent (N);
13166             Arg : Node_Id;
13167
13168          begin
13169             Check_No_Identifiers;
13170             Check_Arg_Count (1);
13171
13172             Arg := Get_Pragma_Arg (Arg1);
13173
13174             --  The expression is used in the call to Create_Task, and must be
13175             --  expanded there, not in the context of the current spec. It must
13176             --  however be analyzed to capture global references, in case it
13177             --  appears in a generic context.
13178
13179             Preanalyze_And_Resolve (Arg, Standard_String);
13180
13181             if Nkind (P) /= N_Task_Definition then
13182                Pragma_Misplaced;
13183             end if;
13184
13185             if Has_Task_Name_Pragma (P) then
13186                Error_Pragma ("duplicate pragma% not allowed");
13187             else
13188                Set_Has_Task_Name_Pragma (P, True);
13189                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
13190             end if;
13191          end Task_Name;
13192
13193          ------------------
13194          -- Task_Storage --
13195          ------------------
13196
13197          --  pragma Task_Storage (
13198          --     [Task_Type =>] LOCAL_NAME,
13199          --     [Top_Guard =>] static_integer_EXPRESSION);
13200
13201          when Pragma_Task_Storage => Task_Storage : declare
13202             Args  : Args_List (1 .. 2);
13203             Names : constant Name_List (1 .. 2) := (
13204                       Name_Task_Type,
13205                       Name_Top_Guard);
13206
13207             Task_Type : Node_Id renames Args (1);
13208             Top_Guard : Node_Id renames Args (2);
13209
13210             Ent : Entity_Id;
13211
13212          begin
13213             GNAT_Pragma;
13214             Gather_Associations (Names, Args);
13215
13216             if No (Task_Type) then
13217                Error_Pragma
13218                  ("missing task_type argument for pragma%");
13219             end if;
13220
13221             Check_Arg_Is_Local_Name (Task_Type);
13222
13223             Ent := Entity (Task_Type);
13224
13225             if not Is_Task_Type (Ent) then
13226                Error_Pragma_Arg
13227                  ("argument for pragma% must be task type", Task_Type);
13228             end if;
13229
13230             if No (Top_Guard) then
13231                Error_Pragma_Arg
13232                  ("pragma% takes two arguments", Task_Type);
13233             else
13234                Check_Arg_Is_Static_Expression (Top_Guard, Any_Integer);
13235             end if;
13236
13237             Check_First_Subtype (Task_Type);
13238
13239             if Rep_Item_Too_Late (Ent, N) then
13240                raise Pragma_Exit;
13241             end if;
13242          end Task_Storage;
13243
13244          ---------------
13245          -- Test_Case --
13246          ---------------
13247
13248          --  pragma Test_Case ([Name     =>] Static_String_EXPRESSION
13249          --                   ,[Mode     =>] MODE_TYPE
13250          --                  [, Requires =>  Boolean_EXPRESSION]
13251          --                  [, Ensures  =>  Boolean_EXPRESSION]);
13252
13253          --  MODE_TYPE ::= Normal | Robustness
13254
13255          when Pragma_Test_Case => Test_Case : declare
13256          begin
13257             GNAT_Pragma;
13258             Check_At_Least_N_Arguments (3);
13259             Check_At_Most_N_Arguments (4);
13260             Check_Arg_Order
13261                  ((Name_Name, Name_Mode, Name_Requires, Name_Ensures));
13262
13263             Check_Optional_Identifier (Arg1, Name_Name);
13264             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
13265             Check_Optional_Identifier (Arg2, Name_Mode);
13266             Check_Arg_Is_One_Of (Arg2, Name_Normal, Name_Robustness);
13267
13268             if Arg_Count = 4 then
13269                Check_Identifier (Arg3, Name_Requires);
13270                Check_Identifier (Arg4, Name_Ensures);
13271             else
13272                Check_Identifier_Is_One_Of (Arg3, Name_Requires, Name_Ensures);
13273             end if;
13274
13275             Check_Test_Case;
13276          end Test_Case;
13277
13278          --------------------------
13279          -- Thread_Local_Storage --
13280          --------------------------
13281
13282          --  pragma Thread_Local_Storage ([Entity =>] LOCAL_NAME);
13283
13284          when Pragma_Thread_Local_Storage => Thread_Local_Storage : declare
13285             Id : Node_Id;
13286             E  : Entity_Id;
13287
13288          begin
13289             GNAT_Pragma;
13290             Check_Arg_Count (1);
13291             Check_Optional_Identifier (Arg1, Name_Entity);
13292             Check_Arg_Is_Library_Level_Local_Name (Arg1);
13293
13294             Id := Get_Pragma_Arg (Arg1);
13295             Analyze (Id);
13296
13297             if not Is_Entity_Name (Id)
13298               or else Ekind (Entity (Id)) /= E_Variable
13299             then
13300                Error_Pragma_Arg ("local variable name required", Arg1);
13301             end if;
13302
13303             E := Entity (Id);
13304
13305             if Rep_Item_Too_Early (E, N)
13306               or else Rep_Item_Too_Late (E, N)
13307             then
13308                raise Pragma_Exit;
13309             end if;
13310
13311             Set_Has_Pragma_Thread_Local_Storage (E);
13312             Set_Has_Gigi_Rep_Item (E);
13313          end Thread_Local_Storage;
13314
13315          ----------------
13316          -- Time_Slice --
13317          ----------------
13318
13319          --  pragma Time_Slice (static_duration_EXPRESSION);
13320
13321          when Pragma_Time_Slice => Time_Slice : declare
13322             Val : Ureal;
13323             Nod : Node_Id;
13324
13325          begin
13326             GNAT_Pragma;
13327             Check_Arg_Count (1);
13328             Check_No_Identifiers;
13329             Check_In_Main_Program;
13330             Check_Arg_Is_Static_Expression (Arg1, Standard_Duration);
13331
13332             if not Error_Posted (Arg1) then
13333                Nod := Next (N);
13334                while Present (Nod) loop
13335                   if Nkind (Nod) = N_Pragma
13336                     and then Pragma_Name (Nod) = Name_Time_Slice
13337                   then
13338                      Error_Msg_Name_1 := Pname;
13339                      Error_Msg_N ("duplicate pragma% not permitted", Nod);
13340                   end if;
13341
13342                   Next (Nod);
13343                end loop;
13344             end if;
13345
13346             --  Process only if in main unit
13347
13348             if Get_Source_Unit (Loc) = Main_Unit then
13349                Opt.Time_Slice_Set := True;
13350                Val := Expr_Value_R (Get_Pragma_Arg (Arg1));
13351
13352                if Val <= Ureal_0 then
13353                   Opt.Time_Slice_Value := 0;
13354
13355                elsif Val > UR_From_Uint (UI_From_Int (1000)) then
13356                   Opt.Time_Slice_Value := 1_000_000_000;
13357
13358                else
13359                   Opt.Time_Slice_Value :=
13360                     UI_To_Int (UR_To_Uint (Val * UI_From_Int (1_000_000)));
13361                end if;
13362             end if;
13363          end Time_Slice;
13364
13365          -----------
13366          -- Title --
13367          -----------
13368
13369          --  pragma Title (TITLING_OPTION [, TITLING OPTION]);
13370
13371          --   TITLING_OPTION ::=
13372          --     [Title =>] STRING_LITERAL
13373          --   | [Subtitle =>] STRING_LITERAL
13374
13375          when Pragma_Title => Title : declare
13376             Args  : Args_List (1 .. 2);
13377             Names : constant Name_List (1 .. 2) := (
13378                       Name_Title,
13379                       Name_Subtitle);
13380
13381          begin
13382             GNAT_Pragma;
13383             Gather_Associations (Names, Args);
13384             Store_Note (N);
13385
13386             for J in 1 .. 2 loop
13387                if Present (Args (J)) then
13388                   Check_Arg_Is_Static_Expression (Args (J), Standard_String);
13389                end if;
13390             end loop;
13391          end Title;
13392
13393          ---------------------
13394          -- Unchecked_Union --
13395          ---------------------
13396
13397          --  pragma Unchecked_Union (first_subtype_LOCAL_NAME)
13398
13399          when Pragma_Unchecked_Union => Unchecked_Union : declare
13400             Assoc   : constant Node_Id := Arg1;
13401             Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
13402             Typ     : Entity_Id;
13403             Discr   : Entity_Id;
13404             Tdef    : Node_Id;
13405             Clist   : Node_Id;
13406             Vpart   : Node_Id;
13407             Comp    : Node_Id;
13408             Variant : Node_Id;
13409
13410          begin
13411             Ada_2005_Pragma;
13412             Check_No_Identifiers;
13413             Check_Arg_Count (1);
13414             Check_Arg_Is_Local_Name (Arg1);
13415
13416             Find_Type (Type_Id);
13417             Typ := Entity (Type_Id);
13418
13419             if Typ = Any_Type
13420               or else Rep_Item_Too_Early (Typ, N)
13421             then
13422                return;
13423             else
13424                Typ := Underlying_Type (Typ);
13425             end if;
13426
13427             if Rep_Item_Too_Late (Typ, N) then
13428                return;
13429             end if;
13430
13431             Check_First_Subtype (Arg1);
13432
13433             --  Note remaining cases are references to a type in the current
13434             --  declarative part. If we find an error, we post the error on
13435             --  the relevant type declaration at an appropriate point.
13436
13437             if not Is_Record_Type (Typ) then
13438                Error_Msg_N ("Unchecked_Union must be record type", Typ);
13439                return;
13440
13441             elsif Is_Tagged_Type (Typ) then
13442                Error_Msg_N ("Unchecked_Union must not be tagged", Typ);
13443                return;
13444
13445             elsif Is_Limited_Type (Typ) then
13446                Error_Msg_N
13447                  ("Unchecked_Union must not be limited record type", Typ);
13448                Explain_Limited_Type (Typ, Typ);
13449                return;
13450
13451             else
13452                if not Has_Discriminants (Typ) then
13453                   Error_Msg_N
13454                     ("Unchecked_Union must have one discriminant", Typ);
13455                   return;
13456                end if;
13457
13458                Discr := First_Discriminant (Typ);
13459                while Present (Discr) loop
13460                   if No (Discriminant_Default_Value (Discr)) then
13461                      Error_Msg_N
13462                        ("Unchecked_Union discriminant must have default value",
13463                         Discr);
13464                   end if;
13465
13466                   Next_Discriminant (Discr);
13467                end loop;
13468
13469                Tdef  := Type_Definition (Declaration_Node (Typ));
13470                Clist := Component_List (Tdef);
13471
13472                Comp := First (Component_Items (Clist));
13473                while Present (Comp) loop
13474                   Check_Component (Comp, Typ);
13475                   Next (Comp);
13476                end loop;
13477
13478                if No (Clist) or else No (Variant_Part (Clist)) then
13479                   Error_Msg_N
13480                     ("Unchecked_Union must have variant part",
13481                      Tdef);
13482                   return;
13483                end if;
13484
13485                Vpart := Variant_Part (Clist);
13486
13487                Variant := First (Variants (Vpart));
13488                while Present (Variant) loop
13489                   Check_Variant (Variant, Typ);
13490                   Next (Variant);
13491                end loop;
13492             end if;
13493
13494             Set_Is_Unchecked_Union  (Typ);
13495             Set_Convention (Typ, Convention_C);
13496             Set_Has_Unchecked_Union (Base_Type (Typ));
13497             Set_Is_Unchecked_Union  (Base_Type (Typ));
13498          end Unchecked_Union;
13499
13500          ------------------------
13501          -- Unimplemented_Unit --
13502          ------------------------
13503
13504          --  pragma Unimplemented_Unit;
13505
13506          --  Note: this only gives an error if we are generating code, or if
13507          --  we are in a generic library unit (where the pragma appears in the
13508          --  body, not in the spec).
13509
13510          when Pragma_Unimplemented_Unit => Unimplemented_Unit : declare
13511             Cunitent : constant Entity_Id :=
13512                          Cunit_Entity (Get_Source_Unit (Loc));
13513             Ent_Kind : constant Entity_Kind :=
13514                          Ekind (Cunitent);
13515
13516          begin
13517             GNAT_Pragma;
13518             Check_Arg_Count (0);
13519
13520             if Operating_Mode = Generate_Code
13521               or else Ent_Kind = E_Generic_Function
13522               or else Ent_Kind = E_Generic_Procedure
13523               or else Ent_Kind = E_Generic_Package
13524             then
13525                Get_Name_String (Chars (Cunitent));
13526                Set_Casing (Mixed_Case);
13527                Write_Str (Name_Buffer (1 .. Name_Len));
13528                Write_Str (" is not supported in this configuration");
13529                Write_Eol;
13530                raise Unrecoverable_Error;
13531             end if;
13532          end Unimplemented_Unit;
13533
13534          ------------------------
13535          -- Universal_Aliasing --
13536          ------------------------
13537
13538          --  pragma Universal_Aliasing [([Entity =>] type_LOCAL_NAME)];
13539
13540          when Pragma_Universal_Aliasing => Universal_Alias : declare
13541             E_Id : Entity_Id;
13542
13543          begin
13544             GNAT_Pragma;
13545             Check_Arg_Count (1);
13546             Check_Optional_Identifier (Arg2, Name_Entity);
13547             Check_Arg_Is_Local_Name (Arg1);
13548             E_Id := Entity (Get_Pragma_Arg (Arg1));
13549
13550             if E_Id = Any_Type then
13551                return;
13552             elsif No (E_Id) or else not Is_Type (E_Id) then
13553                Error_Pragma_Arg ("pragma% requires type", Arg1);
13554             end if;
13555
13556             Set_Universal_Aliasing (Implementation_Base_Type (E_Id));
13557          end Universal_Alias;
13558
13559          --------------------
13560          -- Universal_Data --
13561          --------------------
13562
13563          --  pragma Universal_Data [(library_unit_NAME)];
13564
13565          when Pragma_Universal_Data =>
13566             GNAT_Pragma;
13567
13568             --  If this is a configuration pragma, then set the universal
13569             --  addressing option, otherwise confirm that the pragma satisfies
13570             --  the requirements of library unit pragma placement and leave it
13571             --  to the GNAAMP back end to detect the pragma (avoids transitive
13572             --  setting of the option due to withed units).
13573
13574             if Is_Configuration_Pragma then
13575                Universal_Addressing_On_AAMP := True;
13576             else
13577                Check_Valid_Library_Unit_Pragma;
13578             end if;
13579
13580             if not AAMP_On_Target then
13581                Error_Pragma ("?pragma% ignored (applies only to AAMP)");
13582             end if;
13583
13584          ----------------
13585          -- Unmodified --
13586          ----------------
13587
13588          --  pragma Unmodified (local_Name {, local_Name});
13589
13590          when Pragma_Unmodified => Unmodified : declare
13591             Arg_Node : Node_Id;
13592             Arg_Expr : Node_Id;
13593             Arg_Ent  : Entity_Id;
13594
13595          begin
13596             GNAT_Pragma;
13597             Check_At_Least_N_Arguments (1);
13598
13599             --  Loop through arguments
13600
13601             Arg_Node := Arg1;
13602             while Present (Arg_Node) loop
13603                Check_No_Identifier (Arg_Node);
13604
13605                --  Note: the analyze call done by Check_Arg_Is_Local_Name will
13606                --  in fact generate reference, so that the entity will have a
13607                --  reference, which will inhibit any warnings about it not
13608                --  being referenced, and also properly show up in the ali file
13609                --  as a reference. But this reference is recorded before the
13610                --  Has_Pragma_Unreferenced flag is set, so that no warning is
13611                --  generated for this reference.
13612
13613                Check_Arg_Is_Local_Name (Arg_Node);
13614                Arg_Expr := Get_Pragma_Arg (Arg_Node);
13615
13616                if Is_Entity_Name (Arg_Expr) then
13617                   Arg_Ent := Entity (Arg_Expr);
13618
13619                   if not Is_Assignable (Arg_Ent) then
13620                      Error_Pragma_Arg
13621                        ("pragma% can only be applied to a variable",
13622                         Arg_Expr);
13623                   else
13624                      Set_Has_Pragma_Unmodified (Arg_Ent);
13625                   end if;
13626                end if;
13627
13628                Next (Arg_Node);
13629             end loop;
13630          end Unmodified;
13631
13632          ------------------
13633          -- Unreferenced --
13634          ------------------
13635
13636          --  pragma Unreferenced (local_Name {, local_Name});
13637
13638          --    or when used in a context clause:
13639
13640          --  pragma Unreferenced (library_unit_NAME {, library_unit_NAME}
13641
13642          when Pragma_Unreferenced => Unreferenced : declare
13643             Arg_Node : Node_Id;
13644             Arg_Expr : Node_Id;
13645             Arg_Ent  : Entity_Id;
13646             Citem    : Node_Id;
13647
13648          begin
13649             GNAT_Pragma;
13650             Check_At_Least_N_Arguments (1);
13651
13652             --  Check case of appearing within context clause
13653
13654             if Is_In_Context_Clause then
13655
13656                --  The arguments must all be units mentioned in a with clause
13657                --  in the same context clause. Note we already checked (in
13658                --  Par.Prag) that the arguments are either identifiers or
13659                --  selected components.
13660
13661                Arg_Node := Arg1;
13662                while Present (Arg_Node) loop
13663                   Citem := First (List_Containing (N));
13664                   while Citem /= N loop
13665                      if Nkind (Citem) = N_With_Clause
13666                        and then
13667                          Same_Name (Name (Citem), Get_Pragma_Arg (Arg_Node))
13668                      then
13669                         Set_Has_Pragma_Unreferenced
13670                           (Cunit_Entity
13671                              (Get_Source_Unit
13672                                 (Library_Unit (Citem))));
13673                         Set_Unit_Name
13674                           (Get_Pragma_Arg (Arg_Node), Name (Citem));
13675                         exit;
13676                      end if;
13677
13678                      Next (Citem);
13679                   end loop;
13680
13681                   if Citem = N then
13682                      Error_Pragma_Arg
13683                        ("argument of pragma% is not with'ed unit", Arg_Node);
13684                   end if;
13685
13686                   Next (Arg_Node);
13687                end loop;
13688
13689             --  Case of not in list of context items
13690
13691             else
13692                Arg_Node := Arg1;
13693                while Present (Arg_Node) loop
13694                   Check_No_Identifier (Arg_Node);
13695
13696                   --  Note: the analyze call done by Check_Arg_Is_Local_Name
13697                   --  will in fact generate reference, so that the entity will
13698                   --  have a reference, which will inhibit any warnings about
13699                   --  it not being referenced, and also properly show up in the
13700                   --  ali file as a reference. But this reference is recorded
13701                   --  before the Has_Pragma_Unreferenced flag is set, so that
13702                   --  no warning is generated for this reference.
13703
13704                   Check_Arg_Is_Local_Name (Arg_Node);
13705                   Arg_Expr := Get_Pragma_Arg (Arg_Node);
13706
13707                   if Is_Entity_Name (Arg_Expr) then
13708                      Arg_Ent := Entity (Arg_Expr);
13709
13710                      --  If the entity is overloaded, the pragma applies to the
13711                      --  most recent overloading, as documented. In this case,
13712                      --  name resolution does not generate a reference, so it
13713                      --  must be done here explicitly.
13714
13715                      if Is_Overloaded (Arg_Expr) then
13716                         Generate_Reference (Arg_Ent, N);
13717                      end if;
13718
13719                      Set_Has_Pragma_Unreferenced (Arg_Ent);
13720                   end if;
13721
13722                   Next (Arg_Node);
13723                end loop;
13724             end if;
13725          end Unreferenced;
13726
13727          --------------------------
13728          -- Unreferenced_Objects --
13729          --------------------------
13730
13731          --  pragma Unreferenced_Objects (local_Name {, local_Name});
13732
13733          when Pragma_Unreferenced_Objects => Unreferenced_Objects : declare
13734             Arg_Node : Node_Id;
13735             Arg_Expr : Node_Id;
13736
13737          begin
13738             GNAT_Pragma;
13739             Check_At_Least_N_Arguments (1);
13740
13741             Arg_Node := Arg1;
13742             while Present (Arg_Node) loop
13743                Check_No_Identifier (Arg_Node);
13744                Check_Arg_Is_Local_Name (Arg_Node);
13745                Arg_Expr := Get_Pragma_Arg (Arg_Node);
13746
13747                if not Is_Entity_Name (Arg_Expr)
13748                  or else not Is_Type (Entity (Arg_Expr))
13749                then
13750                   Error_Pragma_Arg
13751                     ("argument for pragma% must be type or subtype", Arg_Node);
13752                end if;
13753
13754                Set_Has_Pragma_Unreferenced_Objects (Entity (Arg_Expr));
13755                Next (Arg_Node);
13756             end loop;
13757          end Unreferenced_Objects;
13758
13759          ------------------------------
13760          -- Unreserve_All_Interrupts --
13761          ------------------------------
13762
13763          --  pragma Unreserve_All_Interrupts;
13764
13765          when Pragma_Unreserve_All_Interrupts =>
13766             GNAT_Pragma;
13767             Check_Arg_Count (0);
13768
13769             if In_Extended_Main_Code_Unit (Main_Unit_Entity) then
13770                Unreserve_All_Interrupts := True;
13771             end if;
13772
13773          ----------------
13774          -- Unsuppress --
13775          ----------------
13776
13777          --  pragma Unsuppress (IDENTIFIER [, [On =>] NAME]);
13778
13779          when Pragma_Unsuppress =>
13780             Ada_2005_Pragma;
13781             Process_Suppress_Unsuppress (False);
13782
13783          -------------------
13784          -- Use_VADS_Size --
13785          -------------------
13786
13787          --  pragma Use_VADS_Size;
13788
13789          when Pragma_Use_VADS_Size =>
13790             GNAT_Pragma;
13791             Check_Arg_Count (0);
13792             Check_Valid_Configuration_Pragma;
13793             Use_VADS_Size := True;
13794
13795          ---------------------
13796          -- Validity_Checks --
13797          ---------------------
13798
13799          --  pragma Validity_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
13800
13801          when Pragma_Validity_Checks => Validity_Checks : declare
13802             A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
13803             S  : String_Id;
13804             C  : Char_Code;
13805
13806          begin
13807             GNAT_Pragma;
13808             Check_Arg_Count (1);
13809             Check_No_Identifiers;
13810
13811             if Nkind (A) = N_String_Literal then
13812                S   := Strval (A);
13813
13814                declare
13815                   Slen    : constant Natural := Natural (String_Length (S));
13816                   Options : String (1 .. Slen);
13817                   J       : Natural;
13818
13819                begin
13820                   J := 1;
13821                   loop
13822                      C := Get_String_Char (S, Int (J));
13823                      exit when not In_Character_Range (C);
13824                      Options (J) := Get_Character (C);
13825
13826                      if J = Slen then
13827                         Set_Validity_Check_Options (Options);
13828                         exit;
13829                      else
13830                         J := J + 1;
13831                      end if;
13832                   end loop;
13833                end;
13834
13835             elsif Nkind (A) = N_Identifier then
13836
13837                if Chars (A) = Name_All_Checks then
13838                   Set_Validity_Check_Options ("a");
13839
13840                elsif Chars (A) = Name_On then
13841                   Validity_Checks_On := True;
13842
13843                elsif Chars (A) = Name_Off then
13844                   Validity_Checks_On := False;
13845
13846                end if;
13847             end if;
13848          end Validity_Checks;
13849
13850          --------------
13851          -- Volatile --
13852          --------------
13853
13854          --  pragma Volatile (LOCAL_NAME);
13855
13856          when Pragma_Volatile =>
13857             Process_Atomic_Shared_Volatile;
13858
13859          -------------------------
13860          -- Volatile_Components --
13861          -------------------------
13862
13863          --  pragma Volatile_Components (array_LOCAL_NAME);
13864
13865          --  Volatile is handled by the same circuit as Atomic_Components
13866
13867          --------------
13868          -- Warnings --
13869          --------------
13870
13871          --  pragma Warnings (On | Off);
13872          --  pragma Warnings (On | Off, LOCAL_NAME);
13873          --  pragma Warnings (static_string_EXPRESSION);
13874          --  pragma Warnings (On | Off, STRING_LITERAL);
13875
13876          when Pragma_Warnings => Warnings : begin
13877             GNAT_Pragma;
13878             Check_At_Least_N_Arguments (1);
13879             Check_No_Identifiers;
13880
13881             --  If debug flag -gnatd.i is set, pragma is ignored
13882
13883             if Debug_Flag_Dot_I then
13884                return;
13885             end if;
13886
13887             --  Process various forms of the pragma
13888
13889             declare
13890                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
13891
13892             begin
13893                --  One argument case
13894
13895                if Arg_Count = 1 then
13896
13897                   --  On/Off one argument case was processed by parser
13898
13899                   if Nkind (Argx) = N_Identifier
13900                     and then
13901                       (Chars (Argx) = Name_On
13902                          or else
13903                        Chars (Argx) = Name_Off)
13904                   then
13905                      null;
13906
13907                   --  One argument case must be ON/OFF or static string expr
13908
13909                   elsif not Is_Static_String_Expression (Arg1) then
13910                      Error_Pragma_Arg
13911                        ("argument of pragma% must be On/Off or " &
13912                         "static string expression", Arg1);
13913
13914                   --  One argument string expression case
13915
13916                   else
13917                      declare
13918                         Lit : constant Node_Id   := Expr_Value_S (Argx);
13919                         Str : constant String_Id := Strval (Lit);
13920                         Len : constant Nat       := String_Length (Str);
13921                         C   : Char_Code;
13922                         J   : Nat;
13923                         OK  : Boolean;
13924                         Chr : Character;
13925
13926                      begin
13927                         J := 1;
13928                         while J <= Len loop
13929                            C := Get_String_Char (Str, J);
13930                            OK := In_Character_Range (C);
13931
13932                            if OK then
13933                               Chr := Get_Character (C);
13934
13935                               --  Dot case
13936
13937                               if J < Len and then Chr = '.' then
13938                                  J := J + 1;
13939                                  C := Get_String_Char (Str, J);
13940                                  Chr := Get_Character (C);
13941
13942                                  if not Set_Dot_Warning_Switch (Chr) then
13943                                     Error_Pragma_Arg
13944                                       ("invalid warning switch character " &
13945                                        '.' & Chr, Arg1);
13946                                  end if;
13947
13948                               --  Non-Dot case
13949
13950                               else
13951                                  OK := Set_Warning_Switch (Chr);
13952                               end if;
13953                            end if;
13954
13955                            if not OK then
13956                               Error_Pragma_Arg
13957                                 ("invalid warning switch character " & Chr,
13958                                  Arg1);
13959                            end if;
13960
13961                            J := J + 1;
13962                         end loop;
13963                      end;
13964                   end if;
13965
13966                   --  Two or more arguments (must be two)
13967
13968                else
13969                   Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
13970                   Check_At_Most_N_Arguments (2);
13971
13972                   declare
13973                      E_Id : Node_Id;
13974                      E    : Entity_Id;
13975                      Err  : Boolean;
13976
13977                   begin
13978                      E_Id := Get_Pragma_Arg (Arg2);
13979                      Analyze (E_Id);
13980
13981                      --  In the expansion of an inlined body, a reference to
13982                      --  the formal may be wrapped in a conversion if the
13983                      --  actual is a conversion. Retrieve the real entity name.
13984
13985                      if (In_Instance_Body
13986                          or else In_Inlined_Body)
13987                        and then Nkind (E_Id) = N_Unchecked_Type_Conversion
13988                      then
13989                         E_Id := Expression (E_Id);
13990                      end if;
13991
13992                      --  Entity name case
13993
13994                      if Is_Entity_Name (E_Id) then
13995                         E := Entity (E_Id);
13996
13997                         if E = Any_Id then
13998                            return;
13999                         else
14000                            loop
14001                               Set_Warnings_Off
14002                                 (E, (Chars (Get_Pragma_Arg (Arg1)) =
14003                                                               Name_Off));
14004
14005                               if Chars (Get_Pragma_Arg (Arg1)) = Name_Off
14006                                 and then Warn_On_Warnings_Off
14007                               then
14008                                  Warnings_Off_Pragmas.Append ((N, E));
14009                               end if;
14010
14011                               if Is_Enumeration_Type (E) then
14012                                  declare
14013                                     Lit : Entity_Id;
14014                                  begin
14015                                     Lit := First_Literal (E);
14016                                     while Present (Lit) loop
14017                                        Set_Warnings_Off (Lit);
14018                                        Next_Literal (Lit);
14019                                     end loop;
14020                                  end;
14021                               end if;
14022
14023                               exit when No (Homonym (E));
14024                               E := Homonym (E);
14025                            end loop;
14026                         end if;
14027
14028                      --  Error if not entity or static string literal case
14029
14030                      elsif not Is_Static_String_Expression (Arg2) then
14031                         Error_Pragma_Arg
14032                           ("second argument of pragma% must be entity " &
14033                            "name or static string expression", Arg2);
14034
14035                      --  String literal case
14036
14037                      else
14038                         String_To_Name_Buffer
14039                           (Strval (Expr_Value_S (Get_Pragma_Arg (Arg2))));
14040
14041                         --  Note on configuration pragma case: If this is a
14042                         --  configuration pragma, then for an OFF pragma, we
14043                         --  just set Config True in the call, which is all
14044                         --  that needs to be done. For the case of ON, this
14045                         --  is normally an error, unless it is canceling the
14046                         --  effect of a previous OFF pragma in the same file.
14047                         --  In any other case, an error will be signalled (ON
14048                         --  with no matching OFF).
14049
14050                         if Chars (Argx) = Name_Off then
14051                            Set_Specific_Warning_Off
14052                              (Loc, Name_Buffer (1 .. Name_Len),
14053                               Config => Is_Configuration_Pragma);
14054
14055                         elsif Chars (Argx) = Name_On then
14056                            Set_Specific_Warning_On
14057                              (Loc, Name_Buffer (1 .. Name_Len), Err);
14058
14059                            if Err then
14060                               Error_Msg
14061                                 ("?pragma Warnings On with no " &
14062                                  "matching Warnings Off",
14063                                  Loc);
14064                            end if;
14065                         end if;
14066                      end if;
14067                   end;
14068                end if;
14069             end;
14070          end Warnings;
14071
14072          -------------------
14073          -- Weak_External --
14074          -------------------
14075
14076          --  pragma Weak_External ([Entity =>] LOCAL_NAME);
14077
14078          when Pragma_Weak_External => Weak_External : declare
14079             Ent : Entity_Id;
14080
14081          begin
14082             GNAT_Pragma;
14083             Check_Arg_Count (1);
14084             Check_Optional_Identifier (Arg1, Name_Entity);
14085             Check_Arg_Is_Library_Level_Local_Name (Arg1);
14086             Ent := Entity (Get_Pragma_Arg (Arg1));
14087
14088             if Rep_Item_Too_Early (Ent, N) then
14089                return;
14090             else
14091                Ent := Underlying_Type (Ent);
14092             end if;
14093
14094             --  The only processing required is to link this item on to the
14095             --  list of rep items for the given entity. This is accomplished
14096             --  by the call to Rep_Item_Too_Late (when no error is detected
14097             --  and False is returned).
14098
14099             if Rep_Item_Too_Late (Ent, N) then
14100                return;
14101             else
14102                Set_Has_Gigi_Rep_Item (Ent);
14103             end if;
14104          end Weak_External;
14105
14106          -----------------------------
14107          -- Wide_Character_Encoding --
14108          -----------------------------
14109
14110          --  pragma Wide_Character_Encoding (IDENTIFIER);
14111
14112          when Pragma_Wide_Character_Encoding =>
14113             GNAT_Pragma;
14114
14115             --  Nothing to do, handled in parser. Note that we do not enforce
14116             --  configuration pragma placement, this pragma can appear at any
14117             --  place in the source, allowing mixed encodings within a single
14118             --  source program.
14119
14120             null;
14121
14122          --------------------
14123          -- Unknown_Pragma --
14124          --------------------
14125
14126          --  Should be impossible, since the case of an unknown pragma is
14127          --  separately processed before the case statement is entered.
14128
14129          when Unknown_Pragma =>
14130             raise Program_Error;
14131       end case;
14132
14133       --  AI05-0144: detect dangerous order dependence. Disabled for now,
14134       --  until AI is formally approved.
14135
14136       --  Check_Order_Dependence;
14137
14138    exception
14139       when Pragma_Exit => null;
14140    end Analyze_Pragma;
14141
14142    -----------------------------
14143    -- Analyze_TC_In_Decl_Part --
14144    -----------------------------
14145
14146    procedure Analyze_TC_In_Decl_Part (N : Node_Id; S : Entity_Id) is
14147    begin
14148       --  Install formals and push subprogram spec onto scope stack so that we
14149       --  can see the formals from the pragma.
14150
14151       Install_Formals (S);
14152       Push_Scope (S);
14153
14154       --  Preanalyze the boolean expressions, we treat these as spec
14155       --  expressions (i.e. similar to a default expression).
14156
14157       Preanalyze_TC_Args (Get_Requires_From_Test_Case_Pragma (N),
14158                           Get_Ensures_From_Test_Case_Pragma (N));
14159
14160       --  Remove the subprogram from the scope stack now that the pre-analysis
14161       --  of the expressions in the test-case is done.
14162
14163       End_Scope;
14164    end Analyze_TC_In_Decl_Part;
14165
14166    -------------------
14167    -- Check_Enabled --
14168    -------------------
14169
14170    function Check_Enabled (Nam : Name_Id) return Boolean is
14171       PP : Node_Id;
14172
14173    begin
14174       --  Loop through entries in check policy list
14175
14176       PP := Opt.Check_Policy_List;
14177       loop
14178          --  If there are no specific entries that matched, then we let the
14179          --  setting of assertions govern. Note that this provides the needed
14180          --  compatibility with the RM for the cases of assertion, invariant,
14181          --  precondition, predicate, and postcondition.
14182
14183          if No (PP) then
14184             return Assertions_Enabled;
14185
14186          --  Here we have an entry see if it matches
14187
14188          else
14189             declare
14190                PPA : constant List_Id := Pragma_Argument_Associations (PP);
14191
14192             begin
14193                if Nam = Chars (Get_Pragma_Arg (First (PPA))) then
14194                   case (Chars (Get_Pragma_Arg (Last (PPA)))) is
14195                      when Name_On | Name_Check =>
14196                         return True;
14197                      when Name_Off | Name_Ignore =>
14198                         return False;
14199                      when others =>
14200                         raise Program_Error;
14201                   end case;
14202
14203                else
14204                   PP := Next_Pragma (PP);
14205                end if;
14206             end;
14207          end if;
14208       end loop;
14209    end Check_Enabled;
14210
14211    ---------------------------------
14212    -- Delay_Config_Pragma_Analyze --
14213    ---------------------------------
14214
14215    function Delay_Config_Pragma_Analyze (N : Node_Id) return Boolean is
14216    begin
14217       return Pragma_Name (N) = Name_Interrupt_State
14218                or else
14219              Pragma_Name (N) = Name_Priority_Specific_Dispatching;
14220    end Delay_Config_Pragma_Analyze;
14221
14222    -------------------------
14223    -- Get_Base_Subprogram --
14224    -------------------------
14225
14226    function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id is
14227       Result : Entity_Id;
14228
14229    begin
14230       --  Follow subprogram renaming chain
14231
14232       Result := Def_Id;
14233       while Is_Subprogram (Result)
14234         and then
14235           Nkind (Parent (Declaration_Node (Result))) =
14236                                          N_Subprogram_Renaming_Declaration
14237         and then Present (Alias (Result))
14238       loop
14239          Result := Alias (Result);
14240       end loop;
14241
14242       return Result;
14243    end Get_Base_Subprogram;
14244
14245    ----------------
14246    -- Initialize --
14247    ----------------
14248
14249    procedure Initialize is
14250    begin
14251       Externals.Init;
14252    end Initialize;
14253
14254    -----------------------------
14255    -- Is_Config_Static_String --
14256    -----------------------------
14257
14258    function Is_Config_Static_String (Arg : Node_Id) return Boolean is
14259
14260       function Add_Config_Static_String (Arg : Node_Id) return Boolean;
14261       --  This is an internal recursive function that is just like the outer
14262       --  function except that it adds the string to the name buffer rather
14263       --  than placing the string in the name buffer.
14264
14265       ------------------------------
14266       -- Add_Config_Static_String --
14267       ------------------------------
14268
14269       function Add_Config_Static_String (Arg : Node_Id) return Boolean is
14270          N : Node_Id;
14271          C : Char_Code;
14272
14273       begin
14274          N := Arg;
14275
14276          if Nkind (N) = N_Op_Concat then
14277             if Add_Config_Static_String (Left_Opnd (N)) then
14278                N := Right_Opnd (N);
14279             else
14280                return False;
14281             end if;
14282          end if;
14283
14284          if Nkind (N) /= N_String_Literal then
14285             Error_Msg_N ("string literal expected for pragma argument", N);
14286             return False;
14287
14288          else
14289             for J in 1 .. String_Length (Strval (N)) loop
14290                C := Get_String_Char (Strval (N), J);
14291
14292                if not In_Character_Range (C) then
14293                   Error_Msg
14294                     ("string literal contains invalid wide character",
14295                      Sloc (N) + 1 + Source_Ptr (J));
14296                   return False;
14297                end if;
14298
14299                Add_Char_To_Name_Buffer (Get_Character (C));
14300             end loop;
14301          end if;
14302
14303          return True;
14304       end Add_Config_Static_String;
14305
14306    --  Start of processing for Is_Config_Static_String
14307
14308    begin
14309
14310       Name_Len := 0;
14311       return Add_Config_Static_String (Arg);
14312    end Is_Config_Static_String;
14313
14314    -----------------------------------------
14315    -- Is_Non_Significant_Pragma_Reference --
14316    -----------------------------------------
14317
14318    --  This function makes use of the following static table which indicates
14319    --  whether a given pragma is significant.
14320
14321    --  -1  indicates that references in any argument position are significant
14322    --  0   indicates that appearance in any argument is not significant
14323    --  +n  indicates that appearance as argument n is significant, but all
14324    --      other arguments are not significant
14325    --  99  special processing required (e.g. for pragma Check)
14326
14327    Sig_Flags : constant array (Pragma_Id) of Int :=
14328      (Pragma_AST_Entry                     => -1,
14329       Pragma_Abort_Defer                   => -1,
14330       Pragma_Ada_83                        => -1,
14331       Pragma_Ada_95                        => -1,
14332       Pragma_Ada_05                        => -1,
14333       Pragma_Ada_2005                      => -1,
14334       Pragma_Ada_12                        => -1,
14335       Pragma_Ada_2012                      => -1,
14336       Pragma_All_Calls_Remote              => -1,
14337       Pragma_Annotate                      => -1,
14338       Pragma_Assert                        => -1,
14339       Pragma_Assertion_Policy              =>  0,
14340       Pragma_Assume_No_Invalid_Values      =>  0,
14341       Pragma_Asynchronous                  => -1,
14342       Pragma_Atomic                        =>  0,
14343       Pragma_Atomic_Components             =>  0,
14344       Pragma_Attach_Handler                => -1,
14345       Pragma_Check                         => 99,
14346       Pragma_Check_Name                    =>  0,
14347       Pragma_Check_Policy                  =>  0,
14348       Pragma_CIL_Constructor               => -1,
14349       Pragma_CPP_Class                     =>  0,
14350       Pragma_CPP_Constructor               =>  0,
14351       Pragma_CPP_Virtual                   =>  0,
14352       Pragma_CPP_Vtable                    =>  0,
14353       Pragma_CPU                           => -1,
14354       Pragma_C_Pass_By_Copy                =>  0,
14355       Pragma_Comment                       =>  0,
14356       Pragma_Common_Object                 => -1,
14357       Pragma_Compile_Time_Error            => -1,
14358       Pragma_Compile_Time_Warning          => -1,
14359       Pragma_Compiler_Unit                 =>  0,
14360       Pragma_Complete_Representation       =>  0,
14361       Pragma_Complex_Representation        =>  0,
14362       Pragma_Component_Alignment           => -1,
14363       Pragma_Controlled                    =>  0,
14364       Pragma_Convention                    =>  0,
14365       Pragma_Convention_Identifier         =>  0,
14366       Pragma_Debug                         => -1,
14367       Pragma_Debug_Policy                  =>  0,
14368       Pragma_Detect_Blocking               => -1,
14369       Pragma_Default_Storage_Pool          => -1,
14370       Pragma_Dimension                     => -1,
14371       Pragma_Discard_Names                 =>  0,
14372       Pragma_Elaborate                     => -1,
14373       Pragma_Elaborate_All                 => -1,
14374       Pragma_Elaborate_Body                => -1,
14375       Pragma_Elaboration_Checks            => -1,
14376       Pragma_Eliminate                     => -1,
14377       Pragma_Export                        => -1,
14378       Pragma_Export_Exception              => -1,
14379       Pragma_Export_Function               => -1,
14380       Pragma_Export_Object                 => -1,
14381       Pragma_Export_Procedure              => -1,
14382       Pragma_Export_Value                  => -1,
14383       Pragma_Export_Valued_Procedure       => -1,
14384       Pragma_Extend_System                 => -1,
14385       Pragma_Extensions_Allowed            => -1,
14386       Pragma_External                      => -1,
14387       Pragma_Favor_Top_Level               => -1,
14388       Pragma_External_Name_Casing          => -1,
14389       Pragma_Fast_Math                     => -1,
14390       Pragma_Finalize_Storage_Only         =>  0,
14391       Pragma_Float_Representation          =>  0,
14392       Pragma_Ident                         => -1,
14393       Pragma_Implemented                   => -1,
14394       Pragma_Implicit_Packing              =>  0,
14395       Pragma_Import                        => +2,
14396       Pragma_Import_Exception              =>  0,
14397       Pragma_Import_Function               =>  0,
14398       Pragma_Import_Object                 =>  0,
14399       Pragma_Import_Procedure              =>  0,
14400       Pragma_Import_Valued_Procedure       =>  0,
14401       Pragma_Independent                   =>  0,
14402       Pragma_Independent_Components        =>  0,
14403       Pragma_Initialize_Scalars            => -1,
14404       Pragma_Inline                        =>  0,
14405       Pragma_Inline_Always                 =>  0,
14406       Pragma_Inline_Generic                =>  0,
14407       Pragma_Inspection_Point              => -1,
14408       Pragma_Interface                     => +2,
14409       Pragma_Interface_Name                => +2,
14410       Pragma_Interrupt_Handler             => -1,
14411       Pragma_Interrupt_Priority            => -1,
14412       Pragma_Interrupt_State               => -1,
14413       Pragma_Invariant                     => -1,
14414       Pragma_Java_Constructor              => -1,
14415       Pragma_Java_Interface                => -1,
14416       Pragma_Keep_Names                    =>  0,
14417       Pragma_License                       => -1,
14418       Pragma_Link_With                     => -1,
14419       Pragma_Linker_Alias                  => -1,
14420       Pragma_Linker_Constructor            => -1,
14421       Pragma_Linker_Destructor             => -1,
14422       Pragma_Linker_Options                => -1,
14423       Pragma_Linker_Section                => -1,
14424       Pragma_List                          => -1,
14425       Pragma_Locking_Policy                => -1,
14426       Pragma_Long_Float                    => -1,
14427       Pragma_Machine_Attribute             => -1,
14428       Pragma_Main                          => -1,
14429       Pragma_Main_Storage                  => -1,
14430       Pragma_Memory_Size                   => -1,
14431       Pragma_No_Return                     =>  0,
14432       Pragma_No_Body                       =>  0,
14433       Pragma_No_Run_Time                   => -1,
14434       Pragma_No_Strict_Aliasing            => -1,
14435       Pragma_Normalize_Scalars             => -1,
14436       Pragma_Obsolescent                   =>  0,
14437       Pragma_Optimize                      => -1,
14438       Pragma_Optimize_Alignment            => -1,
14439       Pragma_Ordered                       =>  0,
14440       Pragma_Pack                          =>  0,
14441       Pragma_Page                          => -1,
14442       Pragma_Passive                       => -1,
14443       Pragma_Preelaborable_Initialization  => -1,
14444       Pragma_Polling                       => -1,
14445       Pragma_Persistent_BSS                =>  0,
14446       Pragma_Postcondition                 => -1,
14447       Pragma_Precondition                  => -1,
14448       Pragma_Predicate                     => -1,
14449       Pragma_Preelaborate                  => -1,
14450       Pragma_Preelaborate_05               => -1,
14451       Pragma_Priority                      => -1,
14452       Pragma_Priority_Specific_Dispatching => -1,
14453       Pragma_Profile                       =>  0,
14454       Pragma_Profile_Warnings              =>  0,
14455       Pragma_Propagate_Exceptions          => -1,
14456       Pragma_Psect_Object                  => -1,
14457       Pragma_Pure                          => -1,
14458       Pragma_Pure_05                       => -1,
14459       Pragma_Pure_Function                 => -1,
14460       Pragma_Queuing_Policy                => -1,
14461       Pragma_Ravenscar                     => -1,
14462       Pragma_Relative_Deadline             => -1,
14463       Pragma_Remote_Call_Interface         => -1,
14464       Pragma_Remote_Types                  => -1,
14465       Pragma_Restricted_Run_Time           => -1,
14466       Pragma_Restriction_Warnings          => -1,
14467       Pragma_Restrictions                  => -1,
14468       Pragma_Reviewable                    => -1,
14469       Pragma_Short_Circuit_And_Or          => -1,
14470       Pragma_Share_Generic                 => -1,
14471       Pragma_Shared                        => -1,
14472       Pragma_Shared_Passive                => -1,
14473       Pragma_Short_Descriptors             =>  0,
14474       Pragma_Source_File_Name              => -1,
14475       Pragma_Source_File_Name_Project      => -1,
14476       Pragma_Source_Reference              => -1,
14477       Pragma_Storage_Size                  => -1,
14478       Pragma_Storage_Unit                  => -1,
14479       Pragma_Static_Elaboration_Desired    => -1,
14480       Pragma_Stream_Convert                => -1,
14481       Pragma_Style_Checks                  => -1,
14482       Pragma_Subtitle                      => -1,
14483       Pragma_Suppress                      =>  0,
14484       Pragma_Suppress_Exception_Locations  =>  0,
14485       Pragma_Suppress_All                  => -1,
14486       Pragma_Suppress_Debug_Info           =>  0,
14487       Pragma_Suppress_Initialization       =>  0,
14488       Pragma_System_Name                   => -1,
14489       Pragma_Task_Dispatching_Policy       => -1,
14490       Pragma_Task_Info                     => -1,
14491       Pragma_Task_Name                     => -1,
14492       Pragma_Task_Storage                  =>  0,
14493       Pragma_Test_Case                     => -1,
14494       Pragma_Thread_Local_Storage          =>  0,
14495       Pragma_Time_Slice                    => -1,
14496       Pragma_Title                         => -1,
14497       Pragma_Unchecked_Union               =>  0,
14498       Pragma_Unimplemented_Unit            => -1,
14499       Pragma_Universal_Aliasing            => -1,
14500       Pragma_Universal_Data                => -1,
14501       Pragma_Unmodified                    => -1,
14502       Pragma_Unreferenced                  => -1,
14503       Pragma_Unreferenced_Objects          => -1,
14504       Pragma_Unreserve_All_Interrupts      => -1,
14505       Pragma_Unsuppress                    =>  0,
14506       Pragma_Use_VADS_Size                 => -1,
14507       Pragma_Validity_Checks               => -1,
14508       Pragma_Volatile                      =>  0,
14509       Pragma_Volatile_Components           =>  0,
14510       Pragma_Warnings                      => -1,
14511       Pragma_Weak_External                 => -1,
14512       Pragma_Wide_Character_Encoding       =>  0,
14513       Unknown_Pragma                       =>  0);
14514
14515    function Is_Non_Significant_Pragma_Reference (N : Node_Id) return Boolean is
14516       Id : Pragma_Id;
14517       P  : Node_Id;
14518       C  : Int;
14519       A  : Node_Id;
14520
14521    begin
14522       P := Parent (N);
14523
14524       if Nkind (P) /= N_Pragma_Argument_Association then
14525          return False;
14526
14527       else
14528          Id := Get_Pragma_Id (Parent (P));
14529          C := Sig_Flags (Id);
14530
14531          case C is
14532             when -1 =>
14533                return False;
14534
14535             when 0 =>
14536                return True;
14537
14538             when 99 =>
14539                case Id is
14540
14541                   --  For pragma Check, the first argument is not significant,
14542                   --  the second and the third (if present) arguments are
14543                   --  significant.
14544
14545                   when Pragma_Check =>
14546                      return
14547                        P = First (Pragma_Argument_Associations (Parent (P)));
14548
14549                   when others =>
14550                      raise Program_Error;
14551                end case;
14552
14553             when others =>
14554                A := First (Pragma_Argument_Associations (Parent (P)));
14555                for J in 1 .. C - 1 loop
14556                   if No (A) then
14557                      return False;
14558                   end if;
14559
14560                   Next (A);
14561                end loop;
14562
14563                return A = P; -- is this wrong way round ???
14564          end case;
14565       end if;
14566    end Is_Non_Significant_Pragma_Reference;
14567
14568    ------------------------------
14569    -- Is_Pragma_String_Literal --
14570    ------------------------------
14571
14572    --  This function returns true if the corresponding pragma argument is a
14573    --  static string expression. These are the only cases in which string
14574    --  literals can appear as pragma arguments. We also allow a string literal
14575    --  as the first argument to pragma Assert (although it will of course
14576    --  always generate a type error).
14577
14578    function Is_Pragma_String_Literal (Par : Node_Id) return Boolean is
14579       Pragn : constant Node_Id := Parent (Par);
14580       Assoc : constant List_Id := Pragma_Argument_Associations (Pragn);
14581       Pname : constant Name_Id := Pragma_Name (Pragn);
14582       Argn  : Natural;
14583       N     : Node_Id;
14584
14585    begin
14586       Argn := 1;
14587       N := First (Assoc);
14588       loop
14589          exit when N = Par;
14590          Argn := Argn + 1;
14591          Next (N);
14592       end loop;
14593
14594       if Pname = Name_Assert then
14595          return True;
14596
14597       elsif Pname = Name_Export then
14598          return Argn > 2;
14599
14600       elsif Pname = Name_Ident then
14601          return Argn = 1;
14602
14603       elsif Pname = Name_Import then
14604          return Argn > 2;
14605
14606       elsif Pname = Name_Interface_Name then
14607          return Argn > 1;
14608
14609       elsif Pname = Name_Linker_Alias then
14610          return Argn = 2;
14611
14612       elsif Pname = Name_Linker_Section then
14613          return Argn = 2;
14614
14615       elsif Pname = Name_Machine_Attribute then
14616          return Argn = 2;
14617
14618       elsif Pname = Name_Source_File_Name then
14619          return True;
14620
14621       elsif Pname = Name_Source_Reference then
14622          return Argn = 2;
14623
14624       elsif Pname = Name_Title then
14625          return True;
14626
14627       elsif Pname = Name_Subtitle then
14628          return True;
14629
14630       else
14631          return False;
14632       end if;
14633    end Is_Pragma_String_Literal;
14634
14635    ------------------------
14636    -- Preanalyze_TC_Args --
14637    ------------------------
14638
14639    procedure Preanalyze_TC_Args (Arg_Req, Arg_Ens : Node_Id) is
14640    begin
14641       --  Preanalyze the boolean expressions, we treat these as spec
14642       --  expressions (i.e. similar to a default expression).
14643
14644       if Present (Arg_Req) then
14645          Preanalyze_Spec_Expression
14646            (Get_Pragma_Arg (Arg_Req), Standard_Boolean);
14647       end if;
14648
14649       if Present (Arg_Ens) then
14650          Preanalyze_Spec_Expression
14651            (Get_Pragma_Arg (Arg_Ens), Standard_Boolean);
14652       end if;
14653    end Preanalyze_TC_Args;
14654
14655    --------------------------------------
14656    -- Process_Compilation_Unit_Pragmas --
14657    --------------------------------------
14658
14659    procedure Process_Compilation_Unit_Pragmas (N : Node_Id) is
14660    begin
14661       --  A special check for pragma Suppress_All, a very strange DEC pragma,
14662       --  strange because it comes at the end of the unit. Rational has the
14663       --  same name for a pragma, but treats it as a program unit pragma, In
14664       --  GNAT we just decide to allow it anywhere at all. If it appeared then
14665       --  the flag Has_Pragma_Suppress_All was set on the compilation unit
14666       --  node, and we insert a pragma Suppress (All_Checks) at the start of
14667       --  the context clause to ensure the correct processing.
14668
14669       if Has_Pragma_Suppress_All (N) then
14670          Prepend_To (Context_Items (N),
14671            Make_Pragma (Sloc (N),
14672              Chars                        => Name_Suppress,
14673              Pragma_Argument_Associations => New_List (
14674                Make_Pragma_Argument_Association (Sloc (N),
14675                  Expression => Make_Identifier (Sloc (N), Name_All_Checks)))));
14676       end if;
14677
14678       --  Nothing else to do at the current time!
14679
14680    end Process_Compilation_Unit_Pragmas;
14681
14682    --------
14683    -- rv --
14684    --------
14685
14686    procedure rv is
14687    begin
14688       null;
14689    end rv;
14690
14691    --------------------------------
14692    -- Set_Encoded_Interface_Name --
14693    --------------------------------
14694
14695    procedure Set_Encoded_Interface_Name (E : Entity_Id; S : Node_Id) is
14696       Str : constant String_Id := Strval (S);
14697       Len : constant Int       := String_Length (Str);
14698       CC  : Char_Code;
14699       C   : Character;
14700       J   : Int;
14701
14702       Hex : constant array (0 .. 15) of Character := "0123456789abcdef";
14703
14704       procedure Encode;
14705       --  Stores encoded value of character code CC. The encoding we use an
14706       --  underscore followed by four lower case hex digits.
14707
14708       ------------
14709       -- Encode --
14710       ------------
14711
14712       procedure Encode is
14713       begin
14714          Store_String_Char (Get_Char_Code ('_'));
14715          Store_String_Char
14716            (Get_Char_Code (Hex (Integer (CC / 2 ** 12))));
14717          Store_String_Char
14718            (Get_Char_Code (Hex (Integer (CC / 2 ** 8 and 16#0F#))));
14719          Store_String_Char
14720            (Get_Char_Code (Hex (Integer (CC / 2 ** 4 and 16#0F#))));
14721          Store_String_Char
14722            (Get_Char_Code (Hex (Integer (CC and 16#0F#))));
14723       end Encode;
14724
14725    --  Start of processing for Set_Encoded_Interface_Name
14726
14727    begin
14728       --  If first character is asterisk, this is a link name, and we leave it
14729       --  completely unmodified. We also ignore null strings (the latter case
14730       --  happens only in error cases) and no encoding should occur for Java or
14731       --  AAMP interface names.
14732
14733       if Len = 0
14734         or else Get_String_Char (Str, 1) = Get_Char_Code ('*')
14735         or else VM_Target /= No_VM
14736         or else AAMP_On_Target
14737       then
14738          Set_Interface_Name (E, S);
14739
14740       else
14741          J := 1;
14742          loop
14743             CC := Get_String_Char (Str, J);
14744
14745             exit when not In_Character_Range (CC);
14746
14747             C := Get_Character (CC);
14748
14749             exit when C /= '_' and then C /= '$'
14750               and then C not in '0' .. '9'
14751               and then C not in 'a' .. 'z'
14752               and then C not in 'A' .. 'Z';
14753
14754             if J = Len then
14755                Set_Interface_Name (E, S);
14756                return;
14757
14758             else
14759                J := J + 1;
14760             end if;
14761          end loop;
14762
14763          --  Here we need to encode. The encoding we use as follows:
14764          --     three underscores  + four hex digits (lower case)
14765
14766          Start_String;
14767
14768          for J in 1 .. String_Length (Str) loop
14769             CC := Get_String_Char (Str, J);
14770
14771             if not In_Character_Range (CC) then
14772                Encode;
14773             else
14774                C := Get_Character (CC);
14775
14776                if C = '_' or else C = '$'
14777                  or else C in '0' .. '9'
14778                  or else C in 'a' .. 'z'
14779                  or else C in 'A' .. 'Z'
14780                then
14781                   Store_String_Char (CC);
14782                else
14783                   Encode;
14784                end if;
14785             end if;
14786          end loop;
14787
14788          Set_Interface_Name (E,
14789            Make_String_Literal (Sloc (S),
14790              Strval => End_String));
14791       end if;
14792    end Set_Encoded_Interface_Name;
14793
14794    -------------------
14795    -- Set_Unit_Name --
14796    -------------------
14797
14798    procedure Set_Unit_Name (N : Node_Id; With_Item : Node_Id) is
14799       Pref : Node_Id;
14800       Scop : Entity_Id;
14801
14802    begin
14803       if Nkind (N) = N_Identifier
14804         and then Nkind (With_Item) = N_Identifier
14805       then
14806          Set_Entity (N, Entity (With_Item));
14807
14808       elsif Nkind (N) = N_Selected_Component then
14809          Change_Selected_Component_To_Expanded_Name (N);
14810          Set_Entity (N, Entity (With_Item));
14811          Set_Entity (Selector_Name (N), Entity (N));
14812
14813          Pref := Prefix (N);
14814          Scop := Scope (Entity (N));
14815          while Nkind (Pref) = N_Selected_Component loop
14816             Change_Selected_Component_To_Expanded_Name (Pref);
14817             Set_Entity (Selector_Name (Pref), Scop);
14818             Set_Entity (Pref, Scop);
14819             Pref := Prefix (Pref);
14820             Scop := Scope (Scop);
14821          end loop;
14822
14823          Set_Entity (Pref, Scop);
14824       end if;
14825    end Set_Unit_Name;
14826
14827 end Sem_Prag;