OSDN Git Service

32d38d8f8d236ea64e755cc4440ecfd89edcd0f7
[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 and ALFA modes
5063
5064          if CodePeer_Mode or ALFA_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 and ALFA modes on
5287          --  user code: we want to generate checks for analysis purposes, as
5288          --  set respectively by -gnatC and -gnatd.F
5289
5290          if (CodePeer_Mode or ALFA_Mode)
5291            and then Comes_From_Source (N)
5292          then
5293             return;
5294          end if;
5295
5296          --  Suppress/Unsuppress can appear as a configuration pragma, or in a
5297          --  declarative part or a package spec (RM 11.5(5)).
5298
5299          if not Is_Configuration_Pragma then
5300             Check_Is_In_Decl_Part_Or_Package_Spec;
5301          end if;
5302
5303          Check_At_Least_N_Arguments (1);
5304          Check_At_Most_N_Arguments (2);
5305          Check_No_Identifier (Arg1);
5306          Check_Arg_Is_Identifier (Arg1);
5307
5308          C := Get_Check_Id (Chars (Get_Pragma_Arg (Arg1)));
5309
5310          if C = No_Check_Id then
5311             Error_Pragma_Arg
5312               ("argument of pragma% is not valid check name", Arg1);
5313          end if;
5314
5315          if not Suppress_Case
5316            and then (C = All_Checks or else C = Overflow_Check)
5317          then
5318             Opt.Overflow_Checks_Unsuppressed := True;
5319          end if;
5320
5321          if Arg_Count = 1 then
5322
5323             --  Make an entry in the local scope suppress table. This is the
5324             --  table that directly shows the current value of the scope
5325             --  suppress check for any check id value.
5326
5327             if C = All_Checks then
5328
5329                --  For All_Checks, we set all specific predefined checks with
5330                --  the exception of Elaboration_Check, which is handled
5331                --  specially because of not wanting All_Checks to have the
5332                --  effect of deactivating static elaboration order processing.
5333
5334                for J in Scope_Suppress'Range loop
5335                   if J /= Elaboration_Check then
5336                      Scope_Suppress (J) := Suppress_Case;
5337                   end if;
5338                end loop;
5339
5340             --  If not All_Checks, and predefined check, then set appropriate
5341             --  scope entry. Note that we will set Elaboration_Check if this
5342             --  is explicitly specified.
5343
5344             elsif C in Predefined_Check_Id then
5345                Scope_Suppress (C) := Suppress_Case;
5346             end if;
5347
5348             --  Also make an entry in the Local_Entity_Suppress table
5349
5350             Push_Local_Suppress_Stack_Entry
5351               (Entity   => Empty,
5352                Check    => C,
5353                Suppress => Suppress_Case);
5354
5355          --  Case of two arguments present, where the check is suppressed for
5356          --  a specified entity (given as the second argument of the pragma)
5357
5358          else
5359             --  This is obsolescent in Ada 2005 mode
5360
5361             if Ada_Version >= Ada_2005 then
5362                Check_Restriction (No_Obsolescent_Features, Arg2);
5363             end if;
5364
5365             Check_Optional_Identifier (Arg2, Name_On);
5366             E_Id := Get_Pragma_Arg (Arg2);
5367             Analyze (E_Id);
5368
5369             if not Is_Entity_Name (E_Id) then
5370                Error_Pragma_Arg
5371                  ("second argument of pragma% must be entity name", Arg2);
5372             end if;
5373
5374             E := Entity (E_Id);
5375
5376             if E = Any_Id then
5377                return;
5378             end if;
5379
5380             --  Enforce RM 11.5(7) which requires that for a pragma that
5381             --  appears within a package spec, the named entity must be
5382             --  within the package spec. We allow the package name itself
5383             --  to be mentioned since that makes sense, although it is not
5384             --  strictly allowed by 11.5(7).
5385
5386             if In_Package_Spec
5387               and then E /= Current_Scope
5388               and then Scope (E) /= Current_Scope
5389             then
5390                Error_Pragma_Arg
5391                  ("entity in pragma% is not in package spec (RM 11.5(7))",
5392                   Arg2);
5393             end if;
5394
5395             --  Loop through homonyms. As noted below, in the case of a package
5396             --  spec, only homonyms within the package spec are considered.
5397
5398             loop
5399                Suppress_Unsuppress_Echeck (E, C);
5400
5401                if Is_Generic_Instance (E)
5402                  and then Is_Subprogram (E)
5403                  and then Present (Alias (E))
5404                then
5405                   Suppress_Unsuppress_Echeck (Alias (E), C);
5406                end if;
5407
5408                --  Move to next homonym if not aspect spec case
5409
5410                exit when From_Aspect_Specification (N);
5411                E := Homonym (E);
5412                exit when No (E);
5413
5414                --  If we are within a package specification, the pragma only
5415                --  applies to homonyms in the same scope.
5416
5417                exit when In_Package_Spec
5418                  and then Scope (E) /= Current_Scope;
5419             end loop;
5420          end if;
5421       end Process_Suppress_Unsuppress;
5422
5423       ------------------
5424       -- Set_Exported --
5425       ------------------
5426
5427       procedure Set_Exported (E : Entity_Id; Arg : Node_Id) is
5428       begin
5429          if Is_Imported (E) then
5430             Error_Pragma_Arg
5431               ("cannot export entity& that was previously imported", Arg);
5432
5433          elsif Present (Address_Clause (E)) and then not CodePeer_Mode then
5434             Error_Pragma_Arg
5435               ("cannot export entity& that has an address clause", Arg);
5436          end if;
5437
5438          Set_Is_Exported (E);
5439
5440          --  Generate a reference for entity explicitly, because the
5441          --  identifier may be overloaded and name resolution will not
5442          --  generate one.
5443
5444          Generate_Reference (E, Arg);
5445
5446          --  Deal with exporting non-library level entity
5447
5448          if not Is_Library_Level_Entity (E) then
5449
5450             --  Not allowed at all for subprograms
5451
5452             if Is_Subprogram (E) then
5453                Error_Pragma_Arg ("local subprogram& cannot be exported", Arg);
5454
5455             --  Otherwise set public and statically allocated
5456
5457             else
5458                Set_Is_Public (E);
5459                Set_Is_Statically_Allocated (E);
5460
5461                --  Warn if the corresponding W flag is set and the pragma comes
5462                --  from source. The latter may not be true e.g. on VMS where we
5463                --  expand export pragmas for exception codes associated with
5464                --  imported or exported exceptions. We do not want to generate
5465                --  a warning for something that the user did not write.
5466
5467                if Warn_On_Export_Import
5468                  and then Comes_From_Source (Arg)
5469                then
5470                   Error_Msg_NE
5471                     ("?& has been made static as a result of Export", Arg, E);
5472                   Error_Msg_N
5473                     ("\this usage is non-standard and non-portable", Arg);
5474                end if;
5475             end if;
5476          end if;
5477
5478          if Warn_On_Export_Import and then Is_Type (E) then
5479             Error_Msg_NE ("exporting a type has no effect?", Arg, E);
5480          end if;
5481
5482          if Warn_On_Export_Import and Inside_A_Generic then
5483             Error_Msg_NE
5484               ("all instances of& will have the same external name?", Arg, E);
5485          end if;
5486       end Set_Exported;
5487
5488       ----------------------------------------------
5489       -- Set_Extended_Import_Export_External_Name --
5490       ----------------------------------------------
5491
5492       procedure Set_Extended_Import_Export_External_Name
5493         (Internal_Ent : Entity_Id;
5494          Arg_External : Node_Id)
5495       is
5496          Old_Name : constant Node_Id := Interface_Name (Internal_Ent);
5497          New_Name : Node_Id;
5498
5499       begin
5500          if No (Arg_External) then
5501             return;
5502          end if;
5503
5504          Check_Arg_Is_External_Name (Arg_External);
5505
5506          if Nkind (Arg_External) = N_String_Literal then
5507             if String_Length (Strval (Arg_External)) = 0 then
5508                return;
5509             else
5510                New_Name := Adjust_External_Name_Case (Arg_External);
5511             end if;
5512
5513          elsif Nkind (Arg_External) = N_Identifier then
5514             New_Name := Get_Default_External_Name (Arg_External);
5515
5516          --  Check_Arg_Is_External_Name should let through only identifiers and
5517          --  string literals or static string expressions (which are folded to
5518          --  string literals).
5519
5520          else
5521             raise Program_Error;
5522          end if;
5523
5524          --  If we already have an external name set (by a prior normal Import
5525          --  or Export pragma), then the external names must match
5526
5527          if Present (Interface_Name (Internal_Ent)) then
5528             Check_Matching_Internal_Names : declare
5529                S1 : constant String_Id := Strval (Old_Name);
5530                S2 : constant String_Id := Strval (New_Name);
5531
5532                procedure Mismatch;
5533                --  Called if names do not match
5534
5535                --------------
5536                -- Mismatch --
5537                --------------
5538
5539                procedure Mismatch is
5540                begin
5541                   Error_Msg_Sloc := Sloc (Old_Name);
5542                   Error_Pragma_Arg
5543                     ("external name does not match that given #",
5544                      Arg_External);
5545                end Mismatch;
5546
5547             --  Start of processing for Check_Matching_Internal_Names
5548
5549             begin
5550                if String_Length (S1) /= String_Length (S2) then
5551                   Mismatch;
5552
5553                else
5554                   for J in 1 .. String_Length (S1) loop
5555                      if Get_String_Char (S1, J) /= Get_String_Char (S2, J) then
5556                         Mismatch;
5557                      end if;
5558                   end loop;
5559                end if;
5560             end Check_Matching_Internal_Names;
5561
5562          --  Otherwise set the given name
5563
5564          else
5565             Set_Encoded_Interface_Name (Internal_Ent, New_Name);
5566             Check_Duplicated_Export_Name (New_Name);
5567          end if;
5568       end Set_Extended_Import_Export_External_Name;
5569
5570       ------------------
5571       -- Set_Imported --
5572       ------------------
5573
5574       procedure Set_Imported (E : Entity_Id) is
5575       begin
5576          --  Error message if already imported or exported
5577
5578          if Is_Exported (E) or else Is_Imported (E) then
5579
5580             --  Error if being set Exported twice
5581
5582             if Is_Exported (E) then
5583                Error_Msg_NE ("entity& was previously exported", N, E);
5584
5585             --  OK if Import/Interface case
5586
5587             elsif Import_Interface_Present (N) then
5588                goto OK;
5589
5590             --  Error if being set Imported twice
5591
5592             else
5593                Error_Msg_NE ("entity& was previously imported", N, E);
5594             end if;
5595
5596             Error_Msg_Name_1 := Pname;
5597             Error_Msg_N
5598               ("\(pragma% applies to all previous entities)", N);
5599
5600             Error_Msg_Sloc  := Sloc (E);
5601             Error_Msg_NE ("\import not allowed for& declared#", N, E);
5602
5603          --  Here if not previously imported or exported, OK to import
5604
5605          else
5606             Set_Is_Imported (E);
5607
5608             --  If the entity is an object that is not at the library level,
5609             --  then it is statically allocated. We do not worry about objects
5610             --  with address clauses in this context since they are not really
5611             --  imported in the linker sense.
5612
5613             if Is_Object (E)
5614               and then not Is_Library_Level_Entity (E)
5615               and then No (Address_Clause (E))
5616             then
5617                Set_Is_Statically_Allocated (E);
5618             end if;
5619          end if;
5620
5621          <<OK>> null;
5622       end Set_Imported;
5623
5624       -------------------------
5625       -- Set_Mechanism_Value --
5626       -------------------------
5627
5628       --  Note: the mechanism name has not been analyzed (and cannot indeed be
5629       --  analyzed, since it is semantic nonsense), so we get it in the exact
5630       --  form created by the parser.
5631
5632       procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id) is
5633          Class        : Node_Id;
5634          Param        : Node_Id;
5635          Mech_Name_Id : Name_Id;
5636
5637          procedure Bad_Class;
5638          --  Signal bad descriptor class name
5639
5640          procedure Bad_Mechanism;
5641          --  Signal bad mechanism name
5642
5643          ---------------
5644          -- Bad_Class --
5645          ---------------
5646
5647          procedure Bad_Class is
5648          begin
5649             Error_Pragma_Arg ("unrecognized descriptor class name", Class);
5650          end Bad_Class;
5651
5652          -------------------------
5653          -- Bad_Mechanism_Value --
5654          -------------------------
5655
5656          procedure Bad_Mechanism is
5657          begin
5658             Error_Pragma_Arg ("unrecognized mechanism name", Mech_Name);
5659          end Bad_Mechanism;
5660
5661       --  Start of processing for Set_Mechanism_Value
5662
5663       begin
5664          if Mechanism (Ent) /= Default_Mechanism then
5665             Error_Msg_NE
5666               ("mechanism for & has already been set", Mech_Name, Ent);
5667          end if;
5668
5669          --  MECHANISM_NAME ::= value | reference | descriptor |
5670          --                     short_descriptor
5671
5672          if Nkind (Mech_Name) = N_Identifier then
5673             if Chars (Mech_Name) = Name_Value then
5674                Set_Mechanism (Ent, By_Copy);
5675                return;
5676
5677             elsif Chars (Mech_Name) = Name_Reference then
5678                Set_Mechanism (Ent, By_Reference);
5679                return;
5680
5681             elsif Chars (Mech_Name) = Name_Descriptor then
5682                Check_VMS (Mech_Name);
5683
5684                --  Descriptor => Short_Descriptor if pragma was given
5685
5686                if Short_Descriptors then
5687                   Set_Mechanism (Ent, By_Short_Descriptor);
5688                else
5689                   Set_Mechanism (Ent, By_Descriptor);
5690                end if;
5691
5692                return;
5693
5694             elsif Chars (Mech_Name) = Name_Short_Descriptor then
5695                Check_VMS (Mech_Name);
5696                Set_Mechanism (Ent, By_Short_Descriptor);
5697                return;
5698
5699             elsif Chars (Mech_Name) = Name_Copy then
5700                Error_Pragma_Arg
5701                  ("bad mechanism name, Value assumed", Mech_Name);
5702
5703             else
5704                Bad_Mechanism;
5705             end if;
5706
5707          --  MECHANISM_NAME ::= descriptor (CLASS_NAME) |
5708          --                     short_descriptor (CLASS_NAME)
5709          --  CLASS_NAME     ::= ubs | ubsb | uba | s | sb | a | nca
5710
5711          --  Note: this form is parsed as an indexed component
5712
5713          elsif Nkind (Mech_Name) = N_Indexed_Component then
5714             Class := First (Expressions (Mech_Name));
5715
5716             if Nkind (Prefix (Mech_Name)) /= N_Identifier
5717              or else not (Chars (Prefix (Mech_Name)) = Name_Descriptor or else
5718                           Chars (Prefix (Mech_Name)) = Name_Short_Descriptor)
5719              or else Present (Next (Class))
5720             then
5721                Bad_Mechanism;
5722             else
5723                Mech_Name_Id := Chars (Prefix (Mech_Name));
5724
5725                --  Change Descriptor => Short_Descriptor if pragma was given
5726
5727                if Mech_Name_Id = Name_Descriptor
5728                  and then Short_Descriptors
5729                then
5730                   Mech_Name_Id := Name_Short_Descriptor;
5731                end if;
5732             end if;
5733
5734          --  MECHANISM_NAME ::= descriptor (Class => CLASS_NAME) |
5735          --                     short_descriptor (Class => CLASS_NAME)
5736          --  CLASS_NAME     ::= ubs | ubsb | uba | s | sb | a | nca
5737
5738          --  Note: this form is parsed as a function call
5739
5740          elsif Nkind (Mech_Name) = N_Function_Call then
5741             Param := First (Parameter_Associations (Mech_Name));
5742
5743             if Nkind (Name (Mech_Name)) /= N_Identifier
5744               or else not (Chars (Name (Mech_Name)) = Name_Descriptor or else
5745                            Chars (Name (Mech_Name)) = Name_Short_Descriptor)
5746               or else Present (Next (Param))
5747               or else No (Selector_Name (Param))
5748               or else Chars (Selector_Name (Param)) /= Name_Class
5749             then
5750                Bad_Mechanism;
5751             else
5752                Class := Explicit_Actual_Parameter (Param);
5753                Mech_Name_Id := Chars (Name (Mech_Name));
5754             end if;
5755
5756          else
5757             Bad_Mechanism;
5758          end if;
5759
5760          --  Fall through here with Class set to descriptor class name
5761
5762          Check_VMS (Mech_Name);
5763
5764          if Nkind (Class) /= N_Identifier then
5765             Bad_Class;
5766
5767          elsif Mech_Name_Id = Name_Descriptor
5768            and then Chars (Class) = Name_UBS
5769          then
5770             Set_Mechanism (Ent, By_Descriptor_UBS);
5771
5772          elsif Mech_Name_Id = Name_Descriptor
5773            and then Chars (Class) = Name_UBSB
5774          then
5775             Set_Mechanism (Ent, By_Descriptor_UBSB);
5776
5777          elsif Mech_Name_Id = Name_Descriptor
5778            and then Chars (Class) = Name_UBA
5779          then
5780             Set_Mechanism (Ent, By_Descriptor_UBA);
5781
5782          elsif Mech_Name_Id = Name_Descriptor
5783            and then Chars (Class) = Name_S
5784          then
5785             Set_Mechanism (Ent, By_Descriptor_S);
5786
5787          elsif Mech_Name_Id = Name_Descriptor
5788            and then Chars (Class) = Name_SB
5789          then
5790             Set_Mechanism (Ent, By_Descriptor_SB);
5791
5792          elsif Mech_Name_Id = Name_Descriptor
5793            and then Chars (Class) = Name_A
5794          then
5795             Set_Mechanism (Ent, By_Descriptor_A);
5796
5797          elsif Mech_Name_Id = Name_Descriptor
5798            and then Chars (Class) = Name_NCA
5799          then
5800             Set_Mechanism (Ent, By_Descriptor_NCA);
5801
5802          elsif Mech_Name_Id = Name_Short_Descriptor
5803            and then Chars (Class) = Name_UBS
5804          then
5805             Set_Mechanism (Ent, By_Short_Descriptor_UBS);
5806
5807          elsif Mech_Name_Id = Name_Short_Descriptor
5808            and then Chars (Class) = Name_UBSB
5809          then
5810             Set_Mechanism (Ent, By_Short_Descriptor_UBSB);
5811
5812          elsif Mech_Name_Id = Name_Short_Descriptor
5813            and then Chars (Class) = Name_UBA
5814          then
5815             Set_Mechanism (Ent, By_Short_Descriptor_UBA);
5816
5817          elsif Mech_Name_Id = Name_Short_Descriptor
5818            and then Chars (Class) = Name_S
5819          then
5820             Set_Mechanism (Ent, By_Short_Descriptor_S);
5821
5822          elsif Mech_Name_Id = Name_Short_Descriptor
5823            and then Chars (Class) = Name_SB
5824          then
5825             Set_Mechanism (Ent, By_Short_Descriptor_SB);
5826
5827          elsif Mech_Name_Id = Name_Short_Descriptor
5828            and then Chars (Class) = Name_A
5829          then
5830             Set_Mechanism (Ent, By_Short_Descriptor_A);
5831
5832          elsif Mech_Name_Id = Name_Short_Descriptor
5833            and then Chars (Class) = Name_NCA
5834          then
5835             Set_Mechanism (Ent, By_Short_Descriptor_NCA);
5836
5837          else
5838             Bad_Class;
5839          end if;
5840       end Set_Mechanism_Value;
5841
5842       ---------------------------
5843       -- Set_Ravenscar_Profile --
5844       ---------------------------
5845
5846       --  The tasks to be done here are
5847
5848       --    Set required policies
5849
5850       --      pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
5851       --      pragma Locking_Policy (Ceiling_Locking)
5852
5853       --    Set Detect_Blocking mode
5854
5855       --    Set required restrictions (see System.Rident for detailed list)
5856
5857       --    Set the No_Dependence rules
5858       --      No_Dependence => Ada.Asynchronous_Task_Control
5859       --      No_Dependence => Ada.Calendar
5860       --      No_Dependence => Ada.Execution_Time.Group_Budget
5861       --      No_Dependence => Ada.Execution_Time.Timers
5862       --      No_Dependence => Ada.Task_Attributes
5863       --      No_Dependence => System.Multiprocessors.Dispatching_Domains
5864
5865       procedure Set_Ravenscar_Profile (N : Node_Id) is
5866          Prefix_Entity   : Entity_Id;
5867          Selector_Entity : Entity_Id;
5868          Prefix_Node     : Node_Id;
5869          Node            : Node_Id;
5870
5871       begin
5872          --  pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
5873
5874          if Task_Dispatching_Policy /= ' '
5875            and then Task_Dispatching_Policy /= 'F'
5876          then
5877             Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
5878             Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
5879
5880          --  Set the FIFO_Within_Priorities policy, but always preserve
5881          --  System_Location since we like the error message with the run time
5882          --  name.
5883
5884          else
5885             Task_Dispatching_Policy := 'F';
5886
5887             if Task_Dispatching_Policy_Sloc /= System_Location then
5888                Task_Dispatching_Policy_Sloc := Loc;
5889             end if;
5890          end if;
5891
5892          --  pragma Locking_Policy (Ceiling_Locking)
5893
5894          if Locking_Policy /= ' '
5895            and then Locking_Policy /= 'C'
5896          then
5897             Error_Msg_Sloc := Locking_Policy_Sloc;
5898             Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
5899
5900          --  Set the Ceiling_Locking policy, but preserve System_Location since
5901          --  we like the error message with the run time name.
5902
5903          else
5904             Locking_Policy := 'C';
5905
5906             if Locking_Policy_Sloc /= System_Location then
5907                Locking_Policy_Sloc := Loc;
5908             end if;
5909          end if;
5910
5911          --  pragma Detect_Blocking
5912
5913          Detect_Blocking := True;
5914
5915          --  Set the corresponding restrictions
5916
5917          Set_Profile_Restrictions
5918            (Ravenscar, N, Warn => Treat_Restrictions_As_Warnings);
5919
5920          --  Set the No_Dependence restrictions
5921
5922          --  The following No_Dependence restrictions:
5923          --    No_Dependence => Ada.Asynchronous_Task_Control
5924          --    No_Dependence => Ada.Calendar
5925          --    No_Dependence => Ada.Task_Attributes
5926          --  are already set by previous call to Set_Profile_Restrictions.
5927
5928          --  Set the following restrictions which were added to Ada 2005:
5929          --    No_Dependence => Ada.Execution_Time.Group_Budget
5930          --    No_Dependence => Ada.Execution_Time.Timers
5931
5932          if Ada_Version >= Ada_2005 then
5933             Name_Buffer (1 .. 3) := "ada";
5934             Name_Len := 3;
5935
5936             Prefix_Entity := Make_Identifier (Loc, Name_Find);
5937
5938             Name_Buffer (1 .. 14) := "execution_time";
5939             Name_Len := 14;
5940
5941             Selector_Entity := Make_Identifier (Loc, Name_Find);
5942
5943             Prefix_Node :=
5944               Make_Selected_Component
5945                 (Sloc          => Loc,
5946                  Prefix        => Prefix_Entity,
5947                  Selector_Name => Selector_Entity);
5948
5949             Name_Buffer (1 .. 13) := "group_budgets";
5950             Name_Len := 13;
5951
5952             Selector_Entity := Make_Identifier (Loc, Name_Find);
5953
5954             Node :=
5955               Make_Selected_Component
5956                 (Sloc          => Loc,
5957                  Prefix        => Prefix_Node,
5958                  Selector_Name => Selector_Entity);
5959
5960             Set_Restriction_No_Dependence
5961               (Unit    => Node,
5962                Warn    => Treat_Restrictions_As_Warnings,
5963                Profile => Ravenscar);
5964
5965             Name_Buffer (1 .. 6) := "timers";
5966             Name_Len := 6;
5967
5968             Selector_Entity := Make_Identifier (Loc, Name_Find);
5969
5970             Node :=
5971               Make_Selected_Component
5972                 (Sloc          => Loc,
5973                  Prefix        => Prefix_Node,
5974                  Selector_Name => Selector_Entity);
5975
5976             Set_Restriction_No_Dependence
5977               (Unit    => Node,
5978                Warn    => Treat_Restrictions_As_Warnings,
5979                Profile => Ravenscar);
5980          end if;
5981
5982          --  Set the following restrictions which was added to Ada 2012 (see
5983          --  AI-0171):
5984          --    No_Dependence => System.Multiprocessors.Dispatching_Domains
5985
5986          if Ada_Version >= Ada_2012 then
5987             Name_Buffer (1 .. 6) := "system";
5988             Name_Len := 6;
5989
5990             Prefix_Entity := Make_Identifier (Loc, Name_Find);
5991
5992             Name_Buffer (1 .. 15) := "multiprocessors";
5993             Name_Len := 15;
5994
5995             Selector_Entity := Make_Identifier (Loc, Name_Find);
5996
5997             Prefix_Node :=
5998               Make_Selected_Component
5999                 (Sloc          => Loc,
6000                  Prefix        => Prefix_Entity,
6001                  Selector_Name => Selector_Entity);
6002
6003             Name_Buffer (1 .. 19) := "dispatching_domains";
6004             Name_Len := 19;
6005
6006             Selector_Entity := Make_Identifier (Loc, Name_Find);
6007
6008             Node :=
6009               Make_Selected_Component
6010                 (Sloc          => Loc,
6011                  Prefix        => Prefix_Node,
6012                  Selector_Name => Selector_Entity);
6013
6014             Set_Restriction_No_Dependence
6015               (Unit    => Node,
6016                Warn    => Treat_Restrictions_As_Warnings,
6017                Profile => Ravenscar);
6018          end if;
6019       end Set_Ravenscar_Profile;
6020
6021    --  Start of processing for Analyze_Pragma
6022
6023    begin
6024       --  The following code is a defense against recursion. Not clear that
6025       --  this can happen legitimately, but perhaps some error situations
6026       --  can cause it, and we did see this recursion during testing.
6027
6028       if Analyzed (N) then
6029          return;
6030       else
6031          Set_Analyzed (N, True);
6032       end if;
6033
6034       --  Deal with unrecognized pragma
6035
6036       if not Is_Pragma_Name (Pname) then
6037          if Warn_On_Unrecognized_Pragma then
6038             Error_Msg_Name_1 := Pname;
6039             Error_Msg_N ("?unrecognized pragma%!", Pragma_Identifier (N));
6040
6041             for PN in First_Pragma_Name .. Last_Pragma_Name loop
6042                if Is_Bad_Spelling_Of (Pname, PN) then
6043                   Error_Msg_Name_1 := PN;
6044                   Error_Msg_N -- CODEFIX
6045                     ("\?possible misspelling of %!", Pragma_Identifier (N));
6046                   exit;
6047                end if;
6048             end loop;
6049          end if;
6050
6051          return;
6052       end if;
6053
6054       --  Here to start processing for recognized pragma
6055
6056       Prag_Id := Get_Pragma_Id (Pname);
6057
6058       --  Preset arguments
6059
6060       Arg_Count := 0;
6061       Arg1      := Empty;
6062       Arg2      := Empty;
6063       Arg3      := Empty;
6064       Arg4      := Empty;
6065
6066       if Present (Pragma_Argument_Associations (N)) then
6067          Arg_Count := List_Length (Pragma_Argument_Associations (N));
6068          Arg1 := First (Pragma_Argument_Associations (N));
6069
6070          if Present (Arg1) then
6071             Arg2 := Next (Arg1);
6072
6073             if Present (Arg2) then
6074                Arg3 := Next (Arg2);
6075
6076                if Present (Arg3) then
6077                   Arg4 := Next (Arg3);
6078                end if;
6079             end if;
6080          end if;
6081       end if;
6082
6083       --  An enumeration type defines the pragmas that are supported by the
6084       --  implementation. Get_Pragma_Id (in package Prag) transforms a name
6085       --  into the corresponding enumeration value for the following case.
6086
6087       case Prag_Id is
6088
6089          -----------------
6090          -- Abort_Defer --
6091          -----------------
6092
6093          --  pragma Abort_Defer;
6094
6095          when Pragma_Abort_Defer =>
6096             GNAT_Pragma;
6097             Check_Arg_Count (0);
6098
6099             --  The only required semantic processing is to check the
6100             --  placement. This pragma must appear at the start of the
6101             --  statement sequence of a handled sequence of statements.
6102
6103             if Nkind (Parent (N)) /= N_Handled_Sequence_Of_Statements
6104               or else N /= First (Statements (Parent (N)))
6105             then
6106                Pragma_Misplaced;
6107             end if;
6108
6109          ------------
6110          -- Ada_83 --
6111          ------------
6112
6113          --  pragma Ada_83;
6114
6115          --  Note: this pragma also has some specific processing in Par.Prag
6116          --  because we want to set the Ada version mode during parsing.
6117
6118          when Pragma_Ada_83 =>
6119             GNAT_Pragma;
6120             Check_Arg_Count (0);
6121
6122             --  We really should check unconditionally for proper configuration
6123             --  pragma placement, since we really don't want mixed Ada modes
6124             --  within a single unit, and the GNAT reference manual has always
6125             --  said this was a configuration pragma, but we did not check and
6126             --  are hesitant to add the check now.
6127
6128             --  However, we really cannot tolerate mixing Ada 2005 or Ada 2012
6129             --  with Ada 83 or Ada 95, so we must check if we are in Ada 2005
6130             --  or Ada 2012 mode.
6131
6132             if Ada_Version >= Ada_2005 then
6133                Check_Valid_Configuration_Pragma;
6134             end if;
6135
6136             --  Now set Ada 83 mode
6137
6138             Ada_Version := Ada_83;
6139             Ada_Version_Explicit := Ada_Version;
6140
6141          ------------
6142          -- Ada_95 --
6143          ------------
6144
6145          --  pragma Ada_95;
6146
6147          --  Note: this pragma also has some specific processing in Par.Prag
6148          --  because we want to set the Ada 83 version mode during parsing.
6149
6150          when Pragma_Ada_95 =>
6151             GNAT_Pragma;
6152             Check_Arg_Count (0);
6153
6154             --  We really should check unconditionally for proper configuration
6155             --  pragma placement, since we really don't want mixed Ada modes
6156             --  within a single unit, and the GNAT reference manual has always
6157             --  said this was a configuration pragma, but we did not check and
6158             --  are hesitant to add the check now.
6159
6160             --  However, we really cannot tolerate mixing Ada 2005 with Ada 83
6161             --  or Ada 95, so we must check if we are in Ada 2005 mode.
6162
6163             if Ada_Version >= Ada_2005 then
6164                Check_Valid_Configuration_Pragma;
6165             end if;
6166
6167             --  Now set Ada 95 mode
6168
6169             Ada_Version := Ada_95;
6170             Ada_Version_Explicit := Ada_Version;
6171
6172          ---------------------
6173          -- Ada_05/Ada_2005 --
6174          ---------------------
6175
6176          --  pragma Ada_05;
6177          --  pragma Ada_05 (LOCAL_NAME);
6178
6179          --  pragma Ada_2005;
6180          --  pragma Ada_2005 (LOCAL_NAME):
6181
6182          --  Note: these pragmas also have some specific processing in Par.Prag
6183          --  because we want to set the Ada 2005 version mode during parsing.
6184
6185          when Pragma_Ada_05 | Pragma_Ada_2005 => declare
6186             E_Id : Node_Id;
6187
6188          begin
6189             GNAT_Pragma;
6190
6191             if Arg_Count = 1 then
6192                Check_Arg_Is_Local_Name (Arg1);
6193                E_Id := Get_Pragma_Arg (Arg1);
6194
6195                if Etype (E_Id) = Any_Type then
6196                   return;
6197                end if;
6198
6199                Set_Is_Ada_2005_Only (Entity (E_Id));
6200
6201             else
6202                Check_Arg_Count (0);
6203
6204                --  For Ada_2005 we unconditionally enforce the documented
6205                --  configuration pragma placement, since we do not want to
6206                --  tolerate mixed modes in a unit involving Ada 2005. That
6207                --  would cause real difficulties for those cases where there
6208                --  are incompatibilities between Ada 95 and Ada 2005.
6209
6210                Check_Valid_Configuration_Pragma;
6211
6212                --  Now set appropriate Ada mode
6213
6214                Ada_Version          := Ada_2005;
6215                Ada_Version_Explicit := Ada_2005;
6216             end if;
6217          end;
6218
6219          ---------------------
6220          -- Ada_12/Ada_2012 --
6221          ---------------------
6222
6223          --  pragma Ada_12;
6224          --  pragma Ada_12 (LOCAL_NAME);
6225
6226          --  pragma Ada_2012;
6227          --  pragma Ada_2012 (LOCAL_NAME):
6228
6229          --  Note: these pragmas also have some specific processing in Par.Prag
6230          --  because we want to set the Ada 2012 version mode during parsing.
6231
6232          when Pragma_Ada_12 | Pragma_Ada_2012 => declare
6233             E_Id : Node_Id;
6234
6235          begin
6236             GNAT_Pragma;
6237
6238             if Arg_Count = 1 then
6239                Check_Arg_Is_Local_Name (Arg1);
6240                E_Id := Get_Pragma_Arg (Arg1);
6241
6242                if Etype (E_Id) = Any_Type then
6243                   return;
6244                end if;
6245
6246                Set_Is_Ada_2012_Only (Entity (E_Id));
6247
6248             else
6249                Check_Arg_Count (0);
6250
6251                --  For Ada_2012 we unconditionally enforce the documented
6252                --  configuration pragma placement, since we do not want to
6253                --  tolerate mixed modes in a unit involving Ada 2012. That
6254                --  would cause real difficulties for those cases where there
6255                --  are incompatibilities between Ada 95 and Ada 2012. We could
6256                --  allow mixing of Ada 2005 and Ada 2012 but it's not worth it.
6257
6258                Check_Valid_Configuration_Pragma;
6259
6260                --  Now set appropriate Ada mode
6261
6262                Ada_Version          := Ada_2012;
6263                Ada_Version_Explicit := Ada_2012;
6264             end if;
6265          end;
6266
6267          ----------------------
6268          -- All_Calls_Remote --
6269          ----------------------
6270
6271          --  pragma All_Calls_Remote [(library_package_NAME)];
6272
6273          when Pragma_All_Calls_Remote => All_Calls_Remote : declare
6274             Lib_Entity : Entity_Id;
6275
6276          begin
6277             Check_Ada_83_Warning;
6278             Check_Valid_Library_Unit_Pragma;
6279
6280             if Nkind (N) = N_Null_Statement then
6281                return;
6282             end if;
6283
6284             Lib_Entity := Find_Lib_Unit_Name;
6285
6286             --  This pragma should only apply to a RCI unit (RM E.2.3(23))
6287
6288             if Present (Lib_Entity)
6289               and then not Debug_Flag_U
6290             then
6291                if not Is_Remote_Call_Interface (Lib_Entity) then
6292                   Error_Pragma ("pragma% only apply to rci unit");
6293
6294                --  Set flag for entity of the library unit
6295
6296                else
6297                   Set_Has_All_Calls_Remote (Lib_Entity);
6298                end if;
6299
6300             end if;
6301          end All_Calls_Remote;
6302
6303          --------------
6304          -- Annotate --
6305          --------------
6306
6307          --  pragma Annotate (IDENTIFIER [, IDENTIFIER {, ARG}]);
6308          --  ARG ::= NAME | EXPRESSION
6309
6310          --  The first two arguments are by convention intended to refer to an
6311          --  external tool and a tool-specific function. These arguments are
6312          --  not analyzed.
6313
6314          when Pragma_Annotate => Annotate : declare
6315             Arg : Node_Id;
6316             Exp : Node_Id;
6317
6318          begin
6319             GNAT_Pragma;
6320             Check_At_Least_N_Arguments (1);
6321             Check_Arg_Is_Identifier (Arg1);
6322             Check_No_Identifiers;
6323             Store_Note (N);
6324
6325             --  Second parameter is optional, it is never analyzed
6326
6327             if No (Arg2) then
6328                null;
6329
6330             --  Here if we have a second parameter
6331
6332             else
6333                --  Second parameter must be identifier
6334
6335                Check_Arg_Is_Identifier (Arg2);
6336
6337                --  Process remaining parameters if any
6338
6339                Arg := Next (Arg2);
6340                while Present (Arg) loop
6341                   Exp := Get_Pragma_Arg (Arg);
6342                   Analyze (Exp);
6343
6344                   if Is_Entity_Name (Exp) then
6345                      null;
6346
6347                   --  For string literals, we assume Standard_String as the
6348                   --  type, unless the string contains wide or wide_wide
6349                   --  characters.
6350
6351                   elsif Nkind (Exp) = N_String_Literal then
6352                      if Has_Wide_Wide_Character (Exp) then
6353                         Resolve (Exp, Standard_Wide_Wide_String);
6354                      elsif Has_Wide_Character (Exp) then
6355                         Resolve (Exp, Standard_Wide_String);
6356                      else
6357                         Resolve (Exp, Standard_String);
6358                      end if;
6359
6360                   elsif Is_Overloaded (Exp) then
6361                         Error_Pragma_Arg
6362                           ("ambiguous argument for pragma%", Exp);
6363
6364                   else
6365                      Resolve (Exp);
6366                   end if;
6367
6368                   Next (Arg);
6369                end loop;
6370             end if;
6371          end Annotate;
6372
6373          ------------
6374          -- Assert --
6375          ------------
6376
6377          --  pragma Assert ([Check =>] Boolean_EXPRESSION
6378          --                 [, [Message =>] Static_String_EXPRESSION]);
6379
6380          when Pragma_Assert => Assert : declare
6381             Expr : Node_Id;
6382             Newa : List_Id;
6383
6384          begin
6385             Ada_2005_Pragma;
6386             Check_At_Least_N_Arguments (1);
6387             Check_At_Most_N_Arguments (2);
6388             Check_Arg_Order ((Name_Check, Name_Message));
6389             Check_Optional_Identifier (Arg1, Name_Check);
6390
6391             --  We treat pragma Assert as equivalent to:
6392
6393             --    pragma Check (Assertion, condition [, msg]);
6394
6395             --  So rewrite pragma in this manner, and analyze the result
6396
6397             Expr := Get_Pragma_Arg (Arg1);
6398             Newa := New_List (
6399               Make_Pragma_Argument_Association (Loc,
6400                 Expression => Make_Identifier (Loc, Name_Assertion)),
6401
6402               Make_Pragma_Argument_Association (Sloc (Expr),
6403                 Expression => Expr));
6404
6405             if Arg_Count > 1 then
6406                Check_Optional_Identifier (Arg2, Name_Message);
6407                Analyze_And_Resolve (Get_Pragma_Arg (Arg2), Standard_String);
6408                Append_To (Newa, Relocate_Node (Arg2));
6409             end if;
6410
6411             Rewrite (N,
6412               Make_Pragma (Loc,
6413                 Chars => Name_Check,
6414                 Pragma_Argument_Associations => Newa));
6415             Analyze (N);
6416          end Assert;
6417
6418          ----------------------
6419          -- Assertion_Policy --
6420          ----------------------
6421
6422          --  pragma Assertion_Policy (Check | Ignore)
6423
6424          when Pragma_Assertion_Policy => Assertion_Policy : declare
6425             Policy : Node_Id;
6426
6427          begin
6428             Ada_2005_Pragma;
6429             Check_Valid_Configuration_Pragma;
6430             Check_Arg_Count (1);
6431             Check_No_Identifiers;
6432             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Ignore);
6433
6434             --  We treat pragma Assertion_Policy as equivalent to:
6435
6436             --    pragma Check_Policy (Assertion, policy)
6437
6438             --  So rewrite the pragma in that manner and link on to the chain
6439             --  of Check_Policy pragmas, marking the pragma as analyzed.
6440
6441             Policy := Get_Pragma_Arg (Arg1);
6442
6443             Rewrite (N,
6444               Make_Pragma (Loc,
6445                 Chars => Name_Check_Policy,
6446
6447                 Pragma_Argument_Associations => New_List (
6448                   Make_Pragma_Argument_Association (Loc,
6449                     Expression => Make_Identifier (Loc, Name_Assertion)),
6450
6451                   Make_Pragma_Argument_Association (Loc,
6452                     Expression =>
6453                       Make_Identifier (Sloc (Policy), Chars (Policy))))));
6454
6455             Set_Analyzed (N);
6456             Set_Next_Pragma (N, Opt.Check_Policy_List);
6457             Opt.Check_Policy_List := N;
6458          end Assertion_Policy;
6459
6460          ------------------------------
6461          -- Assume_No_Invalid_Values --
6462          ------------------------------
6463
6464          --  pragma Assume_No_Invalid_Values (On | Off);
6465
6466          when Pragma_Assume_No_Invalid_Values =>
6467             GNAT_Pragma;
6468             Check_Valid_Configuration_Pragma;
6469             Check_Arg_Count (1);
6470             Check_No_Identifiers;
6471             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
6472
6473             if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
6474                Assume_No_Invalid_Values := True;
6475             else
6476                Assume_No_Invalid_Values := False;
6477             end if;
6478
6479          ---------------
6480          -- AST_Entry --
6481          ---------------
6482
6483          --  pragma AST_Entry (entry_IDENTIFIER);
6484
6485          when Pragma_AST_Entry => AST_Entry : declare
6486             Ent : Node_Id;
6487
6488          begin
6489             GNAT_Pragma;
6490             Check_VMS (N);
6491             Check_Arg_Count (1);
6492             Check_No_Identifiers;
6493             Check_Arg_Is_Local_Name (Arg1);
6494             Ent := Entity (Get_Pragma_Arg (Arg1));
6495
6496             --  Note: the implementation of the AST_Entry pragma could handle
6497             --  the entry family case fine, but for now we are consistent with
6498             --  the DEC rules, and do not allow the pragma, which of course
6499             --  has the effect of also forbidding the attribute.
6500
6501             if Ekind (Ent) /= E_Entry then
6502                Error_Pragma_Arg
6503                  ("pragma% argument must be simple entry name", Arg1);
6504
6505             elsif Is_AST_Entry (Ent) then
6506                Error_Pragma_Arg
6507                  ("duplicate % pragma for entry", Arg1);
6508
6509             elsif Has_Homonym (Ent) then
6510                Error_Pragma_Arg
6511                  ("pragma% argument cannot specify overloaded entry", Arg1);
6512
6513             else
6514                declare
6515                   FF : constant Entity_Id := First_Formal (Ent);
6516
6517                begin
6518                   if Present (FF) then
6519                      if Present (Next_Formal (FF)) then
6520                         Error_Pragma_Arg
6521                           ("entry for pragma% can have only one argument",
6522                            Arg1);
6523
6524                      elsif Parameter_Mode (FF) /= E_In_Parameter then
6525                         Error_Pragma_Arg
6526                           ("entry parameter for pragma% must have mode IN",
6527                            Arg1);
6528                      end if;
6529                   end if;
6530                end;
6531
6532                Set_Is_AST_Entry (Ent);
6533             end if;
6534          end AST_Entry;
6535
6536          ------------------
6537          -- Asynchronous --
6538          ------------------
6539
6540          --  pragma Asynchronous (LOCAL_NAME);
6541
6542          when Pragma_Asynchronous => Asynchronous : declare
6543             Nm     : Entity_Id;
6544             C_Ent  : Entity_Id;
6545             L      : List_Id;
6546             S      : Node_Id;
6547             N      : Node_Id;
6548             Formal : Entity_Id;
6549
6550             procedure Process_Async_Pragma;
6551             --  Common processing for procedure and access-to-procedure case
6552
6553             --------------------------
6554             -- Process_Async_Pragma --
6555             --------------------------
6556
6557             procedure Process_Async_Pragma is
6558             begin
6559                if No (L) then
6560                   Set_Is_Asynchronous (Nm);
6561                   return;
6562                end if;
6563
6564                --  The formals should be of mode IN (RM E.4.1(6))
6565
6566                S := First (L);
6567                while Present (S) loop
6568                   Formal := Defining_Identifier (S);
6569
6570                   if Nkind (Formal) = N_Defining_Identifier
6571                     and then Ekind (Formal) /= E_In_Parameter
6572                   then
6573                      Error_Pragma_Arg
6574                        ("pragma% procedure can only have IN parameter",
6575                         Arg1);
6576                   end if;
6577
6578                   Next (S);
6579                end loop;
6580
6581                Set_Is_Asynchronous (Nm);
6582             end Process_Async_Pragma;
6583
6584          --  Start of processing for pragma Asynchronous
6585
6586          begin
6587             Check_Ada_83_Warning;
6588             Check_No_Identifiers;
6589             Check_Arg_Count (1);
6590             Check_Arg_Is_Local_Name (Arg1);
6591
6592             if Debug_Flag_U then
6593                return;
6594             end if;
6595
6596             C_Ent := Cunit_Entity (Current_Sem_Unit);
6597             Analyze (Get_Pragma_Arg (Arg1));
6598             Nm := Entity (Get_Pragma_Arg (Arg1));
6599
6600             if not Is_Remote_Call_Interface (C_Ent)
6601               and then not Is_Remote_Types (C_Ent)
6602             then
6603                --  This pragma should only appear in an RCI or Remote Types
6604                --  unit (RM E.4.1(4)).
6605
6606                Error_Pragma
6607                  ("pragma% not in Remote_Call_Interface or " &
6608                   "Remote_Types unit");
6609             end if;
6610
6611             if Ekind (Nm) = E_Procedure
6612               and then Nkind (Parent (Nm)) = N_Procedure_Specification
6613             then
6614                if not Is_Remote_Call_Interface (Nm) then
6615                   Error_Pragma_Arg
6616                     ("pragma% cannot be applied on non-remote procedure",
6617                      Arg1);
6618                end if;
6619
6620                L := Parameter_Specifications (Parent (Nm));
6621                Process_Async_Pragma;
6622                return;
6623
6624             elsif Ekind (Nm) = E_Function then
6625                Error_Pragma_Arg
6626                  ("pragma% cannot be applied to function", Arg1);
6627
6628             elsif Is_Remote_Access_To_Subprogram_Type (Nm) then
6629                   if Is_Record_Type (Nm) then
6630
6631                   --  A record type that is the Equivalent_Type for a remote
6632                   --  access-to-subprogram type.
6633
6634                      N := Declaration_Node (Corresponding_Remote_Type (Nm));
6635
6636                   else
6637                      --  A non-expanded RAS type (distribution is not enabled)
6638
6639                      N := Declaration_Node (Nm);
6640                   end if;
6641
6642                if Nkind (N) = N_Full_Type_Declaration
6643                  and then Nkind (Type_Definition (N)) =
6644                                      N_Access_Procedure_Definition
6645                then
6646                   L := Parameter_Specifications (Type_Definition (N));
6647                   Process_Async_Pragma;
6648
6649                   if Is_Asynchronous (Nm)
6650                     and then Expander_Active
6651                     and then Get_PCS_Name /= Name_No_DSA
6652                   then
6653                      RACW_Type_Is_Asynchronous (Underlying_RACW_Type (Nm));
6654                   end if;
6655
6656                else
6657                   Error_Pragma_Arg
6658                     ("pragma% cannot reference access-to-function type",
6659                     Arg1);
6660                end if;
6661
6662             --  Only other possibility is Access-to-class-wide type
6663
6664             elsif Is_Access_Type (Nm)
6665               and then Is_Class_Wide_Type (Designated_Type (Nm))
6666             then
6667                Check_First_Subtype (Arg1);
6668                Set_Is_Asynchronous (Nm);
6669                if Expander_Active then
6670                   RACW_Type_Is_Asynchronous (Nm);
6671                end if;
6672
6673             else
6674                Error_Pragma_Arg ("inappropriate argument for pragma%", Arg1);
6675             end if;
6676          end Asynchronous;
6677
6678          ------------
6679          -- Atomic --
6680          ------------
6681
6682          --  pragma Atomic (LOCAL_NAME);
6683
6684          when Pragma_Atomic =>
6685             Process_Atomic_Shared_Volatile;
6686
6687          -----------------------
6688          -- Atomic_Components --
6689          -----------------------
6690
6691          --  pragma Atomic_Components (array_LOCAL_NAME);
6692
6693          --  This processing is shared by Volatile_Components
6694
6695          when Pragma_Atomic_Components   |
6696               Pragma_Volatile_Components =>
6697
6698          Atomic_Components : declare
6699             E_Id : Node_Id;
6700             E    : Entity_Id;
6701             D    : Node_Id;
6702             K    : Node_Kind;
6703
6704          begin
6705             Check_Ada_83_Warning;
6706             Check_No_Identifiers;
6707             Check_Arg_Count (1);
6708             Check_Arg_Is_Local_Name (Arg1);
6709             E_Id := Get_Pragma_Arg (Arg1);
6710
6711             if Etype (E_Id) = Any_Type then
6712                return;
6713             end if;
6714
6715             E := Entity (E_Id);
6716
6717             Check_Duplicate_Pragma (E);
6718
6719             if Rep_Item_Too_Early (E, N)
6720                  or else
6721                Rep_Item_Too_Late (E, N)
6722             then
6723                return;
6724             end if;
6725
6726             D := Declaration_Node (E);
6727             K := Nkind (D);
6728
6729             if (K = N_Full_Type_Declaration and then Is_Array_Type (E))
6730               or else
6731                 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
6732                    and then Nkind (D) = N_Object_Declaration
6733                    and then Nkind (Object_Definition (D)) =
6734                                        N_Constrained_Array_Definition)
6735             then
6736                --  The flag is set on the object, or on the base type
6737
6738                if Nkind (D) /= N_Object_Declaration then
6739                   E := Base_Type (E);
6740                end if;
6741
6742                Set_Has_Volatile_Components (E);
6743
6744                if Prag_Id = Pragma_Atomic_Components then
6745                   Set_Has_Atomic_Components (E);
6746                end if;
6747
6748             else
6749                Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
6750             end if;
6751          end Atomic_Components;
6752
6753          --------------------
6754          -- Attach_Handler --
6755          --------------------
6756
6757          --  pragma Attach_Handler (handler_NAME, EXPRESSION);
6758
6759          when Pragma_Attach_Handler =>
6760             Check_Ada_83_Warning;
6761             Check_No_Identifiers;
6762             Check_Arg_Count (2);
6763
6764             if No_Run_Time_Mode then
6765                Error_Msg_CRT ("Attach_Handler pragma", N);
6766             else
6767                Check_Interrupt_Or_Attach_Handler;
6768
6769                --  The expression that designates the attribute may depend on a
6770                --  discriminant, and is therefore a per- object expression, to
6771                --  be expanded in the init proc. If expansion is enabled, then
6772                --  perform semantic checks on a copy only.
6773
6774                if Expander_Active then
6775                   declare
6776                      Temp : constant Node_Id :=
6777                               New_Copy_Tree (Get_Pragma_Arg (Arg2));
6778                   begin
6779                      Set_Parent (Temp, N);
6780                      Preanalyze_And_Resolve (Temp, RTE (RE_Interrupt_ID));
6781                   end;
6782
6783                else
6784                   Analyze (Get_Pragma_Arg (Arg2));
6785                   Resolve (Get_Pragma_Arg (Arg2), RTE (RE_Interrupt_ID));
6786                end if;
6787
6788                Process_Interrupt_Or_Attach_Handler;
6789             end if;
6790
6791          --------------------
6792          -- C_Pass_By_Copy --
6793          --------------------
6794
6795          --  pragma C_Pass_By_Copy ([Max_Size =>] static_integer_EXPRESSION);
6796
6797          when Pragma_C_Pass_By_Copy => C_Pass_By_Copy : declare
6798             Arg : Node_Id;
6799             Val : Uint;
6800
6801          begin
6802             GNAT_Pragma;
6803             Check_Valid_Configuration_Pragma;
6804             Check_Arg_Count (1);
6805             Check_Optional_Identifier (Arg1, "max_size");
6806
6807             Arg := Get_Pragma_Arg (Arg1);
6808             Check_Arg_Is_Static_Expression (Arg, Any_Integer);
6809
6810             Val := Expr_Value (Arg);
6811
6812             if Val <= 0 then
6813                Error_Pragma_Arg
6814                  ("maximum size for pragma% must be positive", Arg1);
6815
6816             elsif UI_Is_In_Int_Range (Val) then
6817                Default_C_Record_Mechanism := UI_To_Int (Val);
6818
6819             --  If a giant value is given, Int'Last will do well enough.
6820             --  If sometime someone complains that a record larger than
6821             --  two gigabytes is not copied, we will worry about it then!
6822
6823             else
6824                Default_C_Record_Mechanism := Mechanism_Type'Last;
6825             end if;
6826          end C_Pass_By_Copy;
6827
6828          -----------
6829          -- Check --
6830          -----------
6831
6832          --  pragma Check ([Name    =>] IDENTIFIER,
6833          --                [Check   =>] Boolean_EXPRESSION
6834          --              [,[Message =>] String_EXPRESSION]);
6835
6836          when Pragma_Check => Check : declare
6837             Expr : Node_Id;
6838             Eloc : Source_Ptr;
6839
6840             Check_On : Boolean;
6841             --  Set True if category of assertions referenced by Name enabled
6842
6843          begin
6844             GNAT_Pragma;
6845             Check_At_Least_N_Arguments (2);
6846             Check_At_Most_N_Arguments (3);
6847             Check_Optional_Identifier (Arg1, Name_Name);
6848             Check_Optional_Identifier (Arg2, Name_Check);
6849
6850             if Arg_Count = 3 then
6851                Check_Optional_Identifier (Arg3, Name_Message);
6852                Analyze_And_Resolve (Get_Pragma_Arg (Arg3), Standard_String);
6853             end if;
6854
6855             Check_Arg_Is_Identifier (Arg1);
6856
6857             --  Indicate if pragma is enabled. The Original_Node reference here
6858             --  is to deal with pragma Assert rewritten as a Check pragma.
6859
6860             Check_On := Check_Enabled (Chars (Get_Pragma_Arg (Arg1)));
6861
6862             if Check_On then
6863                Set_SCO_Pragma_Enabled (Loc);
6864             end if;
6865
6866             --  If expansion is active and the check is not enabled then we
6867             --  rewrite the Check as:
6868
6869             --    if False and then condition then
6870             --       null;
6871             --    end if;
6872
6873             --  The reason we do this rewriting during semantic analysis rather
6874             --  than as part of normal expansion is that we cannot analyze and
6875             --  expand the code for the boolean expression directly, or it may
6876             --  cause insertion of actions that would escape the attempt to
6877             --  suppress the check code.
6878
6879             --  Note that the Sloc for the if statement corresponds to the
6880             --  argument condition, not the pragma itself. The reason for this
6881             --  is that we may generate a warning if the condition is False at
6882             --  compile time, and we do not want to delete this warning when we
6883             --  delete the if statement.
6884
6885             Expr := Get_Pragma_Arg (Arg2);
6886
6887             if Expander_Active and then not Check_On then
6888                Eloc := Sloc (Expr);
6889
6890                Rewrite (N,
6891                  Make_If_Statement (Eloc,
6892                    Condition =>
6893                      Make_And_Then (Eloc,
6894                        Left_Opnd  => New_Occurrence_Of (Standard_False, Eloc),
6895                        Right_Opnd => Expr),
6896                    Then_Statements => New_List (
6897                      Make_Null_Statement (Eloc))));
6898
6899                Analyze (N);
6900
6901             --  Check is active
6902
6903             else
6904                Analyze_And_Resolve (Expr, Any_Boolean);
6905             end if;
6906          end Check;
6907
6908          ----------------
6909          -- Check_Name --
6910          ----------------
6911
6912          --  pragma Check_Name (check_IDENTIFIER);
6913
6914          when Pragma_Check_Name =>
6915             Check_No_Identifiers;
6916             GNAT_Pragma;
6917             Check_Valid_Configuration_Pragma;
6918             Check_Arg_Count (1);
6919             Check_Arg_Is_Identifier (Arg1);
6920
6921             declare
6922                Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
6923
6924             begin
6925                for J in Check_Names.First .. Check_Names.Last loop
6926                   if Check_Names.Table (J) = Nam then
6927                      return;
6928                   end if;
6929                end loop;
6930
6931                Check_Names.Append (Nam);
6932             end;
6933
6934          ------------------
6935          -- Check_Policy --
6936          ------------------
6937
6938          --  pragma Check_Policy (
6939          --    [Name   =>] IDENTIFIER,
6940          --    [Policy =>] POLICY_IDENTIFIER);
6941
6942          --  POLICY_IDENTIFIER ::= ON | OFF | CHECK | IGNORE
6943
6944          --  Note: this is a configuration pragma, but it is allowed to appear
6945          --  anywhere else.
6946
6947          when Pragma_Check_Policy =>
6948             GNAT_Pragma;
6949             Check_Arg_Count (2);
6950             Check_Optional_Identifier (Arg1, Name_Name);
6951             Check_Optional_Identifier (Arg2, Name_Policy);
6952             Check_Arg_Is_One_Of
6953               (Arg2, Name_On, Name_Off, Name_Check, Name_Ignore);
6954
6955             --  A Check_Policy pragma can appear either as a configuration
6956             --  pragma, or in a declarative part or a package spec (see RM
6957             --  11.5(5) for rules for Suppress/Unsuppress which are also
6958             --  followed for Check_Policy).
6959
6960             if not Is_Configuration_Pragma then
6961                Check_Is_In_Decl_Part_Or_Package_Spec;
6962             end if;
6963
6964             Set_Next_Pragma (N, Opt.Check_Policy_List);
6965             Opt.Check_Policy_List := N;
6966
6967          ---------------------
6968          -- CIL_Constructor --
6969          ---------------------
6970
6971          --  pragma CIL_Constructor ([Entity =>] LOCAL_NAME);
6972
6973          --  Processing for this pragma is shared with Java_Constructor
6974
6975          -------------
6976          -- Comment --
6977          -------------
6978
6979          --  pragma Comment (static_string_EXPRESSION)
6980
6981          --  Processing for pragma Comment shares the circuitry for pragma
6982          --  Ident. The only differences are that Ident enforces a limit of 31
6983          --  characters on its argument, and also enforces limitations on
6984          --  placement for DEC compatibility. Pragma Comment shares neither of
6985          --  these restrictions.
6986
6987          -------------------
6988          -- Common_Object --
6989          -------------------
6990
6991          --  pragma Common_Object (
6992          --        [Internal =>] LOCAL_NAME
6993          --     [, [External =>] EXTERNAL_SYMBOL]
6994          --     [, [Size     =>] EXTERNAL_SYMBOL]);
6995
6996          --  Processing for this pragma is shared with Psect_Object
6997
6998          ------------------------
6999          -- Compile_Time_Error --
7000          ------------------------
7001
7002          --  pragma Compile_Time_Error
7003          --    (boolean_EXPRESSION, static_string_EXPRESSION);
7004
7005          when Pragma_Compile_Time_Error =>
7006             GNAT_Pragma;
7007             Process_Compile_Time_Warning_Or_Error;
7008
7009          --------------------------
7010          -- Compile_Time_Warning --
7011          --------------------------
7012
7013          --  pragma Compile_Time_Warning
7014          --    (boolean_EXPRESSION, static_string_EXPRESSION);
7015
7016          when Pragma_Compile_Time_Warning =>
7017             GNAT_Pragma;
7018             Process_Compile_Time_Warning_Or_Error;
7019
7020          -------------------
7021          -- Compiler_Unit --
7022          -------------------
7023
7024          when Pragma_Compiler_Unit =>
7025             GNAT_Pragma;
7026             Check_Arg_Count (0);
7027             Set_Is_Compiler_Unit (Get_Source_Unit (N));
7028
7029          -----------------------------
7030          -- Complete_Representation --
7031          -----------------------------
7032
7033          --  pragma Complete_Representation;
7034
7035          when Pragma_Complete_Representation =>
7036             GNAT_Pragma;
7037             Check_Arg_Count (0);
7038
7039             if Nkind (Parent (N)) /= N_Record_Representation_Clause then
7040                Error_Pragma
7041                  ("pragma & must appear within record representation clause");
7042             end if;
7043
7044          ----------------------------
7045          -- Complex_Representation --
7046          ----------------------------
7047
7048          --  pragma Complex_Representation ([Entity =>] LOCAL_NAME);
7049
7050          when Pragma_Complex_Representation => Complex_Representation : declare
7051             E_Id : Entity_Id;
7052             E    : Entity_Id;
7053             Ent  : Entity_Id;
7054
7055          begin
7056             GNAT_Pragma;
7057             Check_Arg_Count (1);
7058             Check_Optional_Identifier (Arg1, Name_Entity);
7059             Check_Arg_Is_Local_Name (Arg1);
7060             E_Id := Get_Pragma_Arg (Arg1);
7061
7062             if Etype (E_Id) = Any_Type then
7063                return;
7064             end if;
7065
7066             E := Entity (E_Id);
7067
7068             if not Is_Record_Type (E) then
7069                Error_Pragma_Arg
7070                  ("argument for pragma% must be record type", Arg1);
7071             end if;
7072
7073             Ent := First_Entity (E);
7074
7075             if No (Ent)
7076               or else No (Next_Entity (Ent))
7077               or else Present (Next_Entity (Next_Entity (Ent)))
7078               or else not Is_Floating_Point_Type (Etype (Ent))
7079               or else Etype (Ent) /= Etype (Next_Entity (Ent))
7080             then
7081                Error_Pragma_Arg
7082                  ("record for pragma% must have two fields of the same "
7083                   & "floating-point type", Arg1);
7084
7085             else
7086                Set_Has_Complex_Representation (Base_Type (E));
7087
7088                --  We need to treat the type has having a non-standard
7089                --  representation, for back-end purposes, even though in
7090                --  general a complex will have the default representation
7091                --  of a record with two real components.
7092
7093                Set_Has_Non_Standard_Rep (Base_Type (E));
7094             end if;
7095          end Complex_Representation;
7096
7097          -------------------------
7098          -- Component_Alignment --
7099          -------------------------
7100
7101          --  pragma Component_Alignment (
7102          --        [Form =>] ALIGNMENT_CHOICE
7103          --     [, [Name =>] type_LOCAL_NAME]);
7104          --
7105          --   ALIGNMENT_CHOICE ::=
7106          --     Component_Size
7107          --   | Component_Size_4
7108          --   | Storage_Unit
7109          --   | Default
7110
7111          when Pragma_Component_Alignment => Component_AlignmentP : declare
7112             Args  : Args_List (1 .. 2);
7113             Names : constant Name_List (1 .. 2) := (
7114                       Name_Form,
7115                       Name_Name);
7116
7117             Form  : Node_Id renames Args (1);
7118             Name  : Node_Id renames Args (2);
7119
7120             Atype : Component_Alignment_Kind;
7121             Typ   : Entity_Id;
7122
7123          begin
7124             GNAT_Pragma;
7125             Gather_Associations (Names, Args);
7126
7127             if No (Form) then
7128                Error_Pragma ("missing Form argument for pragma%");
7129             end if;
7130
7131             Check_Arg_Is_Identifier (Form);
7132
7133             --  Get proper alignment, note that Default = Component_Size on all
7134             --  machines we have so far, and we want to set this value rather
7135             --  than the default value to indicate that it has been explicitly
7136             --  set (and thus will not get overridden by the default component
7137             --  alignment for the current scope)
7138
7139             if Chars (Form) = Name_Component_Size then
7140                Atype := Calign_Component_Size;
7141
7142             elsif Chars (Form) = Name_Component_Size_4 then
7143                Atype := Calign_Component_Size_4;
7144
7145             elsif Chars (Form) = Name_Default then
7146                Atype := Calign_Component_Size;
7147
7148             elsif Chars (Form) = Name_Storage_Unit then
7149                Atype := Calign_Storage_Unit;
7150
7151             else
7152                Error_Pragma_Arg
7153                  ("invalid Form parameter for pragma%", Form);
7154             end if;
7155
7156             --  Case with no name, supplied, affects scope table entry
7157
7158             if No (Name) then
7159                Scope_Stack.Table
7160                  (Scope_Stack.Last).Component_Alignment_Default := Atype;
7161
7162             --  Case of name supplied
7163
7164             else
7165                Check_Arg_Is_Local_Name (Name);
7166                Find_Type (Name);
7167                Typ := Entity (Name);
7168
7169                if Typ = Any_Type
7170                  or else Rep_Item_Too_Early (Typ, N)
7171                then
7172                   return;
7173                else
7174                   Typ := Underlying_Type (Typ);
7175                end if;
7176
7177                if not Is_Record_Type (Typ)
7178                  and then not Is_Array_Type (Typ)
7179                then
7180                   Error_Pragma_Arg
7181                     ("Name parameter of pragma% must identify record or " &
7182                      "array type", Name);
7183                end if;
7184
7185                --  An explicit Component_Alignment pragma overrides an
7186                --  implicit pragma Pack, but not an explicit one.
7187
7188                if not Has_Pragma_Pack (Base_Type (Typ)) then
7189                   Set_Is_Packed (Base_Type (Typ), False);
7190                   Set_Component_Alignment (Base_Type (Typ), Atype);
7191                end if;
7192             end if;
7193          end Component_AlignmentP;
7194
7195          ----------------
7196          -- Controlled --
7197          ----------------
7198
7199          --  pragma Controlled (first_subtype_LOCAL_NAME);
7200
7201          when Pragma_Controlled => Controlled : declare
7202             Arg : Node_Id;
7203
7204          begin
7205             Check_No_Identifiers;
7206             Check_Arg_Count (1);
7207             Check_Arg_Is_Local_Name (Arg1);
7208             Arg := Get_Pragma_Arg (Arg1);
7209
7210             if not Is_Entity_Name (Arg)
7211               or else not Is_Access_Type (Entity (Arg))
7212             then
7213                Error_Pragma_Arg ("pragma% requires access type", Arg1);
7214             else
7215                Set_Has_Pragma_Controlled (Base_Type (Entity (Arg)));
7216             end if;
7217          end Controlled;
7218
7219          ----------------
7220          -- Convention --
7221          ----------------
7222
7223          --  pragma Convention ([Convention =>] convention_IDENTIFIER,
7224          --    [Entity =>] LOCAL_NAME);
7225
7226          when Pragma_Convention => Convention : declare
7227             C : Convention_Id;
7228             E : Entity_Id;
7229             pragma Warnings (Off, C);
7230             pragma Warnings (Off, E);
7231          begin
7232             Check_Arg_Order ((Name_Convention, Name_Entity));
7233             Check_Ada_83_Warning;
7234             Check_Arg_Count (2);
7235             Process_Convention (C, E);
7236          end Convention;
7237
7238          ---------------------------
7239          -- Convention_Identifier --
7240          ---------------------------
7241
7242          --  pragma Convention_Identifier ([Name =>] IDENTIFIER,
7243          --    [Convention =>] convention_IDENTIFIER);
7244
7245          when Pragma_Convention_Identifier => Convention_Identifier : declare
7246             Idnam : Name_Id;
7247             Cname : Name_Id;
7248
7249          begin
7250             GNAT_Pragma;
7251             Check_Arg_Order ((Name_Name, Name_Convention));
7252             Check_Arg_Count (2);
7253             Check_Optional_Identifier (Arg1, Name_Name);
7254             Check_Optional_Identifier (Arg2, Name_Convention);
7255             Check_Arg_Is_Identifier (Arg1);
7256             Check_Arg_Is_Identifier (Arg2);
7257             Idnam := Chars (Get_Pragma_Arg (Arg1));
7258             Cname := Chars (Get_Pragma_Arg (Arg2));
7259
7260             if Is_Convention_Name (Cname) then
7261                Record_Convention_Identifier
7262                  (Idnam, Get_Convention_Id (Cname));
7263             else
7264                Error_Pragma_Arg
7265                  ("second arg for % pragma must be convention", Arg2);
7266             end if;
7267          end Convention_Identifier;
7268
7269          ---------------
7270          -- CPP_Class --
7271          ---------------
7272
7273          --  pragma CPP_Class ([Entity =>] local_NAME)
7274
7275          when Pragma_CPP_Class => CPP_Class : declare
7276             Arg : Node_Id;
7277             Typ : Entity_Id;
7278
7279          begin
7280             if Warn_On_Obsolescent_Feature then
7281                Error_Msg_N
7282                  ("'G'N'A'T pragma cpp'_class is now obsolete; replace it" &
7283                   " by pragma import?", N);
7284             end if;
7285
7286             GNAT_Pragma;
7287             Check_Arg_Count (1);
7288             Check_Optional_Identifier (Arg1, Name_Entity);
7289             Check_Arg_Is_Local_Name (Arg1);
7290
7291             Arg := Get_Pragma_Arg (Arg1);
7292             Analyze (Arg);
7293
7294             if Etype (Arg) = Any_Type then
7295                return;
7296             end if;
7297
7298             if not Is_Entity_Name (Arg)
7299               or else not Is_Type (Entity (Arg))
7300             then
7301                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
7302             end if;
7303
7304             Typ := Entity (Arg);
7305
7306             if not Is_Tagged_Type (Typ) then
7307                Error_Pragma_Arg ("pragma% applicable to tagged types ", Arg1);
7308             end if;
7309
7310             --  Types treated as CPP classes must be declared limited (note:
7311             --  this used to be a warning but there is no real benefit to it
7312             --  since we did effectively intend to treat the type as limited
7313             --  anyway).
7314
7315             if not Is_Limited_Type (Typ) then
7316                Error_Msg_N
7317                  ("imported 'C'P'P type must be limited",
7318                   Get_Pragma_Arg (Arg1));
7319             end if;
7320
7321             Set_Is_CPP_Class      (Typ);
7322             Set_Convention        (Typ, Convention_CPP);
7323
7324             --  Imported CPP types must not have discriminants (because C++
7325             --  classes do not have discriminants).
7326
7327             if Has_Discriminants (Typ) then
7328                Error_Msg_N
7329                  ("imported 'C'P'P type cannot have discriminants",
7330                   First (Discriminant_Specifications
7331                           (Declaration_Node (Typ))));
7332             end if;
7333
7334             --  Components of imported CPP types must not have default
7335             --  expressions because the constructor (if any) is in the
7336             --  C++ side.
7337
7338             if Is_Incomplete_Or_Private_Type (Typ)
7339               and then No (Underlying_Type (Typ))
7340             then
7341                --  It should be an error to apply pragma CPP to a private
7342                --  type if the underlying type is not visible (as it is
7343                --  for any representation item). For now, for backward
7344                --  compatibility we do nothing but we cannot check components
7345                --  because they are not available at this stage. All this code
7346                --  will be removed when we cleanup this obsolete GNAT pragma???
7347
7348                null;
7349
7350             else
7351                declare
7352                   Tdef  : constant Node_Id :=
7353                             Type_Definition (Declaration_Node (Typ));
7354                   Clist : Node_Id;
7355                   Comp  : Node_Id;
7356
7357                begin
7358                   if Nkind (Tdef) = N_Record_Definition then
7359                      Clist := Component_List (Tdef);
7360                   else
7361                      pragma Assert (Nkind (Tdef) = N_Derived_Type_Definition);
7362                      Clist := Component_List (Record_Extension_Part (Tdef));
7363                   end if;
7364
7365                   if Present (Clist) then
7366                      Comp := First (Component_Items (Clist));
7367                      while Present (Comp) loop
7368                         if Present (Expression (Comp)) then
7369                            Error_Msg_N
7370                              ("component of imported 'C'P'P type cannot have" &
7371                               " default expression", Expression (Comp));
7372                         end if;
7373
7374                         Next (Comp);
7375                      end loop;
7376                   end if;
7377                end;
7378             end if;
7379          end CPP_Class;
7380
7381          ---------------------
7382          -- CPP_Constructor --
7383          ---------------------
7384
7385          --  pragma CPP_Constructor ([Entity =>] LOCAL_NAME
7386          --    [, [External_Name =>] static_string_EXPRESSION ]
7387          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
7388
7389          when Pragma_CPP_Constructor => CPP_Constructor : declare
7390             Elmt    : Elmt_Id;
7391             Id      : Entity_Id;
7392             Def_Id  : Entity_Id;
7393             Tag_Typ : Entity_Id;
7394
7395          begin
7396             GNAT_Pragma;
7397             Check_At_Least_N_Arguments (1);
7398             Check_At_Most_N_Arguments (3);
7399             Check_Optional_Identifier (Arg1, Name_Entity);
7400             Check_Arg_Is_Local_Name (Arg1);
7401
7402             Id := Get_Pragma_Arg (Arg1);
7403             Find_Program_Unit_Name (Id);
7404
7405             --  If we did not find the name, we are done
7406
7407             if Etype (Id) = Any_Type then
7408                return;
7409             end if;
7410
7411             Def_Id := Entity (Id);
7412
7413             --  Check if already defined as constructor
7414
7415             if Is_Constructor (Def_Id) then
7416                Error_Msg_N
7417                  ("?duplicate argument for pragma 'C'P'P_Constructor", Arg1);
7418                return;
7419             end if;
7420
7421             if Ekind (Def_Id) = E_Function
7422               and then (Is_CPP_Class (Etype (Def_Id))
7423                          or else (Is_Class_Wide_Type (Etype (Def_Id))
7424                                    and then
7425                                   Is_CPP_Class (Root_Type (Etype (Def_Id)))))
7426             then
7427                if Arg_Count >= 2 then
7428                   Set_Imported (Def_Id);
7429                   Set_Is_Public (Def_Id);
7430                   Process_Interface_Name (Def_Id, Arg2, Arg3);
7431                end if;
7432
7433                Set_Has_Completion (Def_Id);
7434                Set_Is_Constructor (Def_Id);
7435
7436                --  Imported C++ constructors are not dispatching primitives
7437                --  because in C++ they don't have a dispatch table slot.
7438                --  However, in Ada the constructor has the profile of a
7439                --  function that returns a tagged type and therefore it has
7440                --  been treated as a primitive operation during semantic
7441                --  analysis. We now remove it from the list of primitive
7442                --  operations of the type.
7443
7444                if Is_Tagged_Type (Etype (Def_Id))
7445                  and then not Is_Class_Wide_Type (Etype (Def_Id))
7446                then
7447                   pragma Assert (Is_Dispatching_Operation (Def_Id));
7448                   Tag_Typ := Etype (Def_Id);
7449
7450                   Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
7451                   while Present (Elmt) and then Node (Elmt) /= Def_Id loop
7452                      Next_Elmt (Elmt);
7453                   end loop;
7454
7455                   Remove_Elmt (Primitive_Operations (Tag_Typ), Elmt);
7456                   Set_Is_Dispatching_Operation (Def_Id, False);
7457                end if;
7458
7459                --  For backward compatibility, if the constructor returns a
7460                --  class wide type, and we internally change the return type to
7461                --  the corresponding root type.
7462
7463                if Is_Class_Wide_Type (Etype (Def_Id)) then
7464                   Set_Etype (Def_Id, Root_Type (Etype (Def_Id)));
7465                end if;
7466             else
7467                Error_Pragma_Arg
7468                  ("pragma% requires function returning a 'C'P'P_Class type",
7469                    Arg1);
7470             end if;
7471          end CPP_Constructor;
7472
7473          -----------------
7474          -- CPP_Virtual --
7475          -----------------
7476
7477          when Pragma_CPP_Virtual => CPP_Virtual : declare
7478          begin
7479             GNAT_Pragma;
7480
7481             if Warn_On_Obsolescent_Feature then
7482                Error_Msg_N
7483                  ("'G'N'A'T pragma cpp'_virtual is now obsolete and has " &
7484                   "no effect?", N);
7485             end if;
7486          end CPP_Virtual;
7487
7488          ----------------
7489          -- CPP_Vtable --
7490          ----------------
7491
7492          when Pragma_CPP_Vtable => CPP_Vtable : declare
7493          begin
7494             GNAT_Pragma;
7495
7496             if Warn_On_Obsolescent_Feature then
7497                Error_Msg_N
7498                  ("'G'N'A'T pragma cpp'_vtable is now obsolete and has " &
7499                   "no effect?", N);
7500             end if;
7501          end CPP_Vtable;
7502
7503          ---------
7504          -- CPU --
7505          ---------
7506
7507          --  pragma CPU (EXPRESSION);
7508
7509          when Pragma_CPU => CPU : declare
7510             P   : constant Node_Id := Parent (N);
7511             Arg : Node_Id;
7512
7513          begin
7514             Ada_2012_Pragma;
7515             Check_No_Identifiers;
7516             Check_Arg_Count (1);
7517
7518             --  Subprogram case
7519
7520             if Nkind (P) = N_Subprogram_Body then
7521                Check_In_Main_Program;
7522
7523                Arg := Get_Pragma_Arg (Arg1);
7524                Analyze_And_Resolve (Arg, Any_Integer);
7525
7526                --  Must be static
7527
7528                if not Is_Static_Expression (Arg) then
7529                   Flag_Non_Static_Expr
7530                     ("main subprogram affinity is not static!", Arg);
7531                   raise Pragma_Exit;
7532
7533                --  If constraint error, then we already signalled an error
7534
7535                elsif Raises_Constraint_Error (Arg) then
7536                   null;
7537
7538                --  Otherwise check in range
7539
7540                else
7541                   declare
7542                      CPU_Id : constant Entity_Id := RTE (RE_CPU_Range);
7543                      --  This is the entity System.Multiprocessors.CPU_Range;
7544
7545                      Val : constant Uint := Expr_Value (Arg);
7546
7547                   begin
7548                      if Val < Expr_Value (Type_Low_Bound (CPU_Id))
7549                           or else
7550                         Val > Expr_Value (Type_High_Bound (CPU_Id))
7551                      then
7552                         Error_Pragma_Arg
7553                           ("main subprogram CPU is out of range", Arg1);
7554                      end if;
7555                   end;
7556                end if;
7557
7558                Set_Main_CPU
7559                     (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
7560
7561             --  Task case
7562
7563             elsif Nkind (P) = N_Task_Definition then
7564                Arg := Get_Pragma_Arg (Arg1);
7565
7566                --  The expression must be analyzed in the special manner
7567                --  described in "Handling of Default and Per-Object
7568                --  Expressions" in sem.ads.
7569
7570                Preanalyze_Spec_Expression (Arg, RTE (RE_CPU_Range));
7571
7572             --  Anything else is incorrect
7573
7574             else
7575                Pragma_Misplaced;
7576             end if;
7577
7578             if Has_Pragma_CPU (P) then
7579                Error_Pragma ("duplicate pragma% not allowed");
7580             else
7581                Set_Has_Pragma_CPU (P, True);
7582
7583                if Nkind (P) = N_Task_Definition then
7584                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
7585                end if;
7586             end if;
7587          end CPU;
7588
7589          -----------
7590          -- Debug --
7591          -----------
7592
7593          --  pragma Debug ([boolean_EXPRESSION,] PROCEDURE_CALL_STATEMENT);
7594
7595          when Pragma_Debug => Debug : declare
7596             Cond : Node_Id;
7597             Call : Node_Id;
7598
7599          begin
7600             GNAT_Pragma;
7601
7602             Cond :=
7603               New_Occurrence_Of
7604                 (Boolean_Literals (Debug_Pragmas_Enabled and Expander_Active),
7605                  Loc);
7606
7607             if Arg_Count = 2 then
7608                Cond :=
7609                  Make_And_Then (Loc,
7610                    Left_Opnd  => Relocate_Node (Cond),
7611                    Right_Opnd => Get_Pragma_Arg (Arg1));
7612                Call := Get_Pragma_Arg (Arg2);
7613             else
7614                Call := Get_Pragma_Arg (Arg1);
7615             end if;
7616
7617             if Nkind_In (Call,
7618                  N_Indexed_Component,
7619                  N_Function_Call,
7620                  N_Identifier,
7621                  N_Selected_Component)
7622             then
7623                --  If this pragma Debug comes from source, its argument was
7624                --  parsed as a name form (which is syntactically identical).
7625                --  Change it to a procedure call statement now.
7626
7627                Change_Name_To_Procedure_Call_Statement (Call);
7628
7629             elsif Nkind (Call) = N_Procedure_Call_Statement then
7630
7631                --  Already in the form of a procedure call statement: nothing
7632                --  to do (could happen in case of an internally generated
7633                --  pragma Debug).
7634
7635                null;
7636
7637             else
7638                --  All other cases: diagnose error
7639
7640                Error_Msg
7641                  ("argument of pragma% is not procedure call", Sloc (Call));
7642                return;
7643             end if;
7644
7645             --  Rewrite into a conditional with an appropriate condition. We
7646             --  wrap the procedure call in a block so that overhead from e.g.
7647             --  use of the secondary stack does not generate execution overhead
7648             --  for suppressed conditions.
7649
7650             Rewrite (N, Make_Implicit_If_Statement (N,
7651               Condition => Cond,
7652                  Then_Statements => New_List (
7653                    Make_Block_Statement (Loc,
7654                      Handled_Statement_Sequence =>
7655                        Make_Handled_Sequence_Of_Statements (Loc,
7656                          Statements => New_List (Relocate_Node (Call)))))));
7657             Analyze (N);
7658          end Debug;
7659
7660          ------------------
7661          -- Debug_Policy --
7662          ------------------
7663
7664          --  pragma Debug_Policy (Check | Ignore)
7665
7666          when Pragma_Debug_Policy =>
7667             GNAT_Pragma;
7668             Check_Arg_Count (1);
7669             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Ignore);
7670             Debug_Pragmas_Enabled :=
7671               Chars (Get_Pragma_Arg (Arg1)) = Name_Check;
7672
7673          ---------------------
7674          -- Detect_Blocking --
7675          ---------------------
7676
7677          --  pragma Detect_Blocking;
7678
7679          when Pragma_Detect_Blocking =>
7680             Ada_2005_Pragma;
7681             Check_Arg_Count (0);
7682             Check_Valid_Configuration_Pragma;
7683             Detect_Blocking := True;
7684
7685          --------------------------
7686          -- Default_Storage_Pool --
7687          --------------------------
7688
7689          --  pragma Default_Storage_Pool (storage_pool_NAME | null);
7690
7691          when Pragma_Default_Storage_Pool =>
7692             Ada_2012_Pragma;
7693             Check_Arg_Count (1);
7694
7695             --  Default_Storage_Pool can appear as a configuration pragma, or
7696             --  in a declarative part or a package spec.
7697
7698             if not Is_Configuration_Pragma then
7699                Check_Is_In_Decl_Part_Or_Package_Spec;
7700             end if;
7701
7702             --  Case of Default_Storage_Pool (null);
7703
7704             if Nkind (Expression (Arg1)) = N_Null then
7705                Analyze (Expression (Arg1));
7706
7707                --  This is an odd case, this is not really an expression, so
7708                --  we don't have a type for it. So just set the type to Empty.
7709
7710                Set_Etype (Expression (Arg1), Empty);
7711
7712             --  Case of Default_Storage_Pool (storage_pool_NAME);
7713
7714             else
7715                --  If it's a configuration pragma, then the only allowed
7716                --  argument is "null".
7717
7718                if Is_Configuration_Pragma then
7719                   Error_Pragma_Arg ("NULL expected", Arg1);
7720                end if;
7721
7722                --  The expected type for a non-"null" argument is
7723                --  Root_Storage_Pool'Class.
7724
7725                Analyze_And_Resolve
7726                  (Get_Pragma_Arg (Arg1),
7727                   Typ => Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
7728             end if;
7729
7730             --  Finally, record the pool name (or null). Freeze.Freeze_Entity
7731             --  for an access type will use this information to set the
7732             --  appropriate attributes of the access type.
7733
7734             Default_Pool := Expression (Arg1);
7735
7736          ---------------
7737          -- Dimension --
7738          ---------------
7739
7740          when Pragma_Dimension =>
7741             GNAT_Pragma;
7742             Check_Arg_Count (4);
7743             Check_No_Identifiers;
7744             Check_Arg_Is_Local_Name (Arg1);
7745
7746             if not Is_Type (Arg1) then
7747                Error_Pragma ("first argument for pragma% must be subtype");
7748             end if;
7749
7750             Check_Arg_Is_Static_Expression (Arg2, Standard_Integer);
7751             Check_Arg_Is_Static_Expression (Arg3, Standard_Integer);
7752             Check_Arg_Is_Static_Expression (Arg4, Standard_Integer);
7753
7754          -------------------
7755          -- Discard_Names --
7756          -------------------
7757
7758          --  pragma Discard_Names [([On =>] LOCAL_NAME)];
7759
7760          when Pragma_Discard_Names => Discard_Names : declare
7761             E    : Entity_Id;
7762             E_Id : Entity_Id;
7763
7764          begin
7765             Check_Ada_83_Warning;
7766
7767             --  Deal with configuration pragma case
7768
7769             if Arg_Count = 0 and then Is_Configuration_Pragma then
7770                Global_Discard_Names := True;
7771                return;
7772
7773             --  Otherwise, check correct appropriate context
7774
7775             else
7776                Check_Is_In_Decl_Part_Or_Package_Spec;
7777
7778                if Arg_Count = 0 then
7779
7780                   --  If there is no parameter, then from now on this pragma
7781                   --  applies to any enumeration, exception or tagged type
7782                   --  defined in the current declarative part, and recursively
7783                   --  to any nested scope.
7784
7785                   Set_Discard_Names (Current_Scope);
7786                   return;
7787
7788                else
7789                   Check_Arg_Count (1);
7790                   Check_Optional_Identifier (Arg1, Name_On);
7791                   Check_Arg_Is_Local_Name (Arg1);
7792
7793                   E_Id := Get_Pragma_Arg (Arg1);
7794
7795                   if Etype (E_Id) = Any_Type then
7796                      return;
7797                   else
7798                      E := Entity (E_Id);
7799                   end if;
7800
7801                   if (Is_First_Subtype (E)
7802                       and then
7803                         (Is_Enumeration_Type (E) or else Is_Tagged_Type (E)))
7804                     or else Ekind (E) = E_Exception
7805                   then
7806                      Set_Discard_Names (E);
7807                   else
7808                      Error_Pragma_Arg
7809                        ("inappropriate entity for pragma%", Arg1);
7810                   end if;
7811
7812                end if;
7813             end if;
7814          end Discard_Names;
7815
7816          ---------------
7817          -- Elaborate --
7818          ---------------
7819
7820          --  pragma Elaborate (library_unit_NAME {, library_unit_NAME});
7821
7822          when Pragma_Elaborate => Elaborate : declare
7823             Arg   : Node_Id;
7824             Citem : Node_Id;
7825
7826          begin
7827             --  Pragma must be in context items list of a compilation unit
7828
7829             if not Is_In_Context_Clause then
7830                Pragma_Misplaced;
7831             end if;
7832
7833             --  Must be at least one argument
7834
7835             if Arg_Count = 0 then
7836                Error_Pragma ("pragma% requires at least one argument");
7837             end if;
7838
7839             --  In Ada 83 mode, there can be no items following it in the
7840             --  context list except other pragmas and implicit with clauses
7841             --  (e.g. those added by use of Rtsfind). In Ada 95 mode, this
7842             --  placement rule does not apply.
7843
7844             if Ada_Version = Ada_83 and then Comes_From_Source (N) then
7845                Citem := Next (N);
7846                while Present (Citem) loop
7847                   if Nkind (Citem) = N_Pragma
7848                     or else (Nkind (Citem) = N_With_Clause
7849                               and then Implicit_With (Citem))
7850                   then
7851                      null;
7852                   else
7853                      Error_Pragma
7854                        ("(Ada 83) pragma% must be at end of context clause");
7855                   end if;
7856
7857                   Next (Citem);
7858                end loop;
7859             end if;
7860
7861             --  Finally, the arguments must all be units mentioned in a with
7862             --  clause in the same context clause. Note we already checked (in
7863             --  Par.Prag) that the arguments are all identifiers or selected
7864             --  components.
7865
7866             Arg := Arg1;
7867             Outer : while Present (Arg) loop
7868                Citem := First (List_Containing (N));
7869                Inner : while Citem /= N loop
7870                   if Nkind (Citem) = N_With_Clause
7871                     and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
7872                   then
7873                      Set_Elaborate_Present (Citem, True);
7874                      Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
7875                      Generate_Reference (Entity (Name (Citem)), Citem);
7876
7877                      --  With the pragma present, elaboration calls on
7878                      --  subprograms from the named unit need no further
7879                      --  checks, as long as the pragma appears in the current
7880                      --  compilation unit. If the pragma appears in some unit
7881                      --  in the context, there might still be a need for an
7882                      --  Elaborate_All_Desirable from the current compilation
7883                      --  to the named unit, so we keep the check enabled.
7884
7885                      if In_Extended_Main_Source_Unit (N) then
7886                         Set_Suppress_Elaboration_Warnings
7887                           (Entity (Name (Citem)));
7888                      end if;
7889
7890                      exit Inner;
7891                   end if;
7892
7893                   Next (Citem);
7894                end loop Inner;
7895
7896                if Citem = N then
7897                   Error_Pragma_Arg
7898                     ("argument of pragma% is not with'ed unit", Arg);
7899                end if;
7900
7901                Next (Arg);
7902             end loop Outer;
7903
7904             --  Give a warning if operating in static mode with -gnatwl
7905             --  (elaboration warnings enabled) switch set.
7906
7907             if Elab_Warnings and not Dynamic_Elaboration_Checks then
7908                Error_Msg_N
7909                  ("?use of pragma Elaborate may not be safe", N);
7910                Error_Msg_N
7911                  ("?use pragma Elaborate_All instead if possible", N);
7912             end if;
7913          end Elaborate;
7914
7915          -------------------
7916          -- Elaborate_All --
7917          -------------------
7918
7919          --  pragma Elaborate_All (library_unit_NAME {, library_unit_NAME});
7920
7921          when Pragma_Elaborate_All => Elaborate_All : declare
7922             Arg   : Node_Id;
7923             Citem : Node_Id;
7924
7925          begin
7926             Check_Ada_83_Warning;
7927
7928             --  Pragma must be in context items list of a compilation unit
7929
7930             if not Is_In_Context_Clause then
7931                Pragma_Misplaced;
7932             end if;
7933
7934             --  Must be at least one argument
7935
7936             if Arg_Count = 0 then
7937                Error_Pragma ("pragma% requires at least one argument");
7938             end if;
7939
7940             --  Note: unlike pragma Elaborate, pragma Elaborate_All does not
7941             --  have to appear at the end of the context clause, but may
7942             --  appear mixed in with other items, even in Ada 83 mode.
7943
7944             --  Final check: the arguments must all be units mentioned in
7945             --  a with clause in the same context clause. Note that we
7946             --  already checked (in Par.Prag) that all the arguments are
7947             --  either identifiers or selected components.
7948
7949             Arg := Arg1;
7950             Outr : while Present (Arg) loop
7951                Citem := First (List_Containing (N));
7952                Innr : while Citem /= N loop
7953                   if Nkind (Citem) = N_With_Clause
7954                     and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
7955                   then
7956                      Set_Elaborate_All_Present (Citem, True);
7957                      Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
7958
7959                      --  Suppress warnings and elaboration checks on the named
7960                      --  unit if the pragma is in the current compilation, as
7961                      --  for pragma Elaborate.
7962
7963                      if In_Extended_Main_Source_Unit (N) then
7964                         Set_Suppress_Elaboration_Warnings
7965                           (Entity (Name (Citem)));
7966                      end if;
7967                      exit Innr;
7968                   end if;
7969
7970                   Next (Citem);
7971                end loop Innr;
7972
7973                if Citem = N then
7974                   Set_Error_Posted (N);
7975                   Error_Pragma_Arg
7976                     ("argument of pragma% is not with'ed unit", Arg);
7977                end if;
7978
7979                Next (Arg);
7980             end loop Outr;
7981          end Elaborate_All;
7982
7983          --------------------
7984          -- Elaborate_Body --
7985          --------------------
7986
7987          --  pragma Elaborate_Body [( library_unit_NAME )];
7988
7989          when Pragma_Elaborate_Body => Elaborate_Body : declare
7990             Cunit_Node : Node_Id;
7991             Cunit_Ent  : Entity_Id;
7992
7993          begin
7994             Check_Ada_83_Warning;
7995             Check_Valid_Library_Unit_Pragma;
7996
7997             if Nkind (N) = N_Null_Statement then
7998                return;
7999             end if;
8000
8001             Cunit_Node := Cunit (Current_Sem_Unit);
8002             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
8003
8004             if Nkind_In (Unit (Cunit_Node), N_Package_Body,
8005                                             N_Subprogram_Body)
8006             then
8007                Error_Pragma ("pragma% must refer to a spec, not a body");
8008             else
8009                Set_Body_Required (Cunit_Node, True);
8010                Set_Has_Pragma_Elaborate_Body (Cunit_Ent);
8011
8012                --  If we are in dynamic elaboration mode, then we suppress
8013                --  elaboration warnings for the unit, since it is definitely
8014                --  fine NOT to do dynamic checks at the first level (and such
8015                --  checks will be suppressed because no elaboration boolean
8016                --  is created for Elaborate_Body packages).
8017
8018                --  But in the static model of elaboration, Elaborate_Body is
8019                --  definitely NOT good enough to ensure elaboration safety on
8020                --  its own, since the body may WITH other units that are not
8021                --  safe from an elaboration point of view, so a client must
8022                --  still do an Elaborate_All on such units.
8023
8024                --  Debug flag -gnatdD restores the old behavior of 3.13, where
8025                --  Elaborate_Body always suppressed elab warnings.
8026
8027                if Dynamic_Elaboration_Checks or Debug_Flag_DD then
8028                   Set_Suppress_Elaboration_Warnings (Cunit_Ent);
8029                end if;
8030             end if;
8031          end Elaborate_Body;
8032
8033          ------------------------
8034          -- Elaboration_Checks --
8035          ------------------------
8036
8037          --  pragma Elaboration_Checks (Static | Dynamic);
8038
8039          when Pragma_Elaboration_Checks =>
8040             GNAT_Pragma;
8041             Check_Arg_Count (1);
8042             Check_Arg_Is_One_Of (Arg1, Name_Static, Name_Dynamic);
8043             Dynamic_Elaboration_Checks :=
8044               (Chars (Get_Pragma_Arg (Arg1)) = Name_Dynamic);
8045
8046          ---------------
8047          -- Eliminate --
8048          ---------------
8049
8050          --  pragma Eliminate (
8051          --      [Unit_Name  =>] IDENTIFIER | SELECTED_COMPONENT,
8052          --    [,[Entity     =>] IDENTIFIER |
8053          --                      SELECTED_COMPONENT |
8054          --                      STRING_LITERAL]
8055          --    [,                OVERLOADING_RESOLUTION]);
8056
8057          --  OVERLOADING_RESOLUTION ::= PARAMETER_AND_RESULT_TYPE_PROFILE |
8058          --                             SOURCE_LOCATION
8059
8060          --  PARAMETER_AND_RESULT_TYPE_PROFILE ::= PROCEDURE_PROFILE |
8061          --                                        FUNCTION_PROFILE
8062
8063          --  PROCEDURE_PROFILE ::= Parameter_Types => PARAMETER_TYPES
8064
8065          --  FUNCTION_PROFILE ::= [Parameter_Types => PARAMETER_TYPES,]
8066          --                       Result_Type => result_SUBTYPE_NAME]
8067
8068          --  PARAMETER_TYPES ::= (SUBTYPE_NAME {, SUBTYPE_NAME})
8069          --  SUBTYPE_NAME    ::= STRING_LITERAL
8070
8071          --  SOURCE_LOCATION ::= Source_Location => SOURCE_TRACE
8072          --  SOURCE_TRACE    ::= STRING_LITERAL
8073
8074          when Pragma_Eliminate => Eliminate : declare
8075             Args  : Args_List (1 .. 5);
8076             Names : constant Name_List (1 .. 5) := (
8077                       Name_Unit_Name,
8078                       Name_Entity,
8079                       Name_Parameter_Types,
8080                       Name_Result_Type,
8081                       Name_Source_Location);
8082
8083             Unit_Name       : Node_Id renames Args (1);
8084             Entity          : Node_Id renames Args (2);
8085             Parameter_Types : Node_Id renames Args (3);
8086             Result_Type     : Node_Id renames Args (4);
8087             Source_Location : Node_Id renames Args (5);
8088
8089          begin
8090             GNAT_Pragma;
8091             Check_Valid_Configuration_Pragma;
8092             Gather_Associations (Names, Args);
8093
8094             if No (Unit_Name) then
8095                Error_Pragma ("missing Unit_Name argument for pragma%");
8096             end if;
8097
8098             if No (Entity)
8099               and then (Present (Parameter_Types)
8100                           or else
8101                         Present (Result_Type)
8102                           or else
8103                         Present (Source_Location))
8104             then
8105                Error_Pragma ("missing Entity argument for pragma%");
8106             end if;
8107
8108             if (Present (Parameter_Types)
8109                   or else
8110                 Present (Result_Type))
8111               and then
8112                 Present (Source_Location)
8113             then
8114                Error_Pragma
8115                  ("parameter profile and source location cannot " &
8116                   "be used together in pragma%");
8117             end if;
8118
8119             Process_Eliminate_Pragma
8120               (N,
8121                Unit_Name,
8122                Entity,
8123                Parameter_Types,
8124                Result_Type,
8125                Source_Location);
8126          end Eliminate;
8127
8128          ------------
8129          -- Export --
8130          ------------
8131
8132          --  pragma Export (
8133          --    [   Convention    =>] convention_IDENTIFIER,
8134          --    [   Entity        =>] local_NAME
8135          --    [, [External_Name =>] static_string_EXPRESSION ]
8136          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
8137
8138          when Pragma_Export => Export : declare
8139             C      : Convention_Id;
8140             Def_Id : Entity_Id;
8141
8142             pragma Warnings (Off, C);
8143
8144          begin
8145             Check_Ada_83_Warning;
8146             Check_Arg_Order
8147               ((Name_Convention,
8148                 Name_Entity,
8149                 Name_External_Name,
8150                 Name_Link_Name));
8151             Check_At_Least_N_Arguments (2);
8152             Check_At_Most_N_Arguments  (4);
8153             Process_Convention (C, Def_Id);
8154
8155             if Ekind (Def_Id) /= E_Constant then
8156                Note_Possible_Modification
8157                  (Get_Pragma_Arg (Arg2), Sure => False);
8158             end if;
8159
8160             Process_Interface_Name (Def_Id, Arg3, Arg4);
8161             Set_Exported (Def_Id, Arg2);
8162
8163             --  If the entity is a deferred constant, propagate the information
8164             --  to the full view, because gigi elaborates the full view only.
8165
8166             if Ekind (Def_Id) = E_Constant
8167               and then Present (Full_View (Def_Id))
8168             then
8169                declare
8170                   Id2 : constant Entity_Id := Full_View (Def_Id);
8171                begin
8172                   Set_Is_Exported    (Id2, Is_Exported          (Def_Id));
8173                   Set_First_Rep_Item (Id2, First_Rep_Item       (Def_Id));
8174                   Set_Interface_Name (Id2, Einfo.Interface_Name (Def_Id));
8175                end;
8176             end if;
8177          end Export;
8178
8179          ----------------------
8180          -- Export_Exception --
8181          ----------------------
8182
8183          --  pragma Export_Exception (
8184          --        [Internal         =>] LOCAL_NAME
8185          --     [, [External         =>] EXTERNAL_SYMBOL]
8186          --     [, [Form     =>] Ada | VMS]
8187          --     [, [Code     =>] static_integer_EXPRESSION]);
8188
8189          when Pragma_Export_Exception => Export_Exception : declare
8190             Args  : Args_List (1 .. 4);
8191             Names : constant Name_List (1 .. 4) := (
8192                       Name_Internal,
8193                       Name_External,
8194                       Name_Form,
8195                       Name_Code);
8196
8197             Internal : Node_Id renames Args (1);
8198             External : Node_Id renames Args (2);
8199             Form     : Node_Id renames Args (3);
8200             Code     : Node_Id renames Args (4);
8201
8202          begin
8203             GNAT_Pragma;
8204
8205             if Inside_A_Generic then
8206                Error_Pragma ("pragma% cannot be used for generic entities");
8207             end if;
8208
8209             Gather_Associations (Names, Args);
8210             Process_Extended_Import_Export_Exception_Pragma (
8211               Arg_Internal => Internal,
8212               Arg_External => External,
8213               Arg_Form     => Form,
8214               Arg_Code     => Code);
8215
8216             if not Is_VMS_Exception (Entity (Internal)) then
8217                Set_Exported (Entity (Internal), Internal);
8218             end if;
8219          end Export_Exception;
8220
8221          ---------------------
8222          -- Export_Function --
8223          ---------------------
8224
8225          --  pragma Export_Function (
8226          --        [Internal         =>] LOCAL_NAME
8227          --     [, [External         =>] EXTERNAL_SYMBOL]
8228          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8229          --     [, [Result_Type      =>] TYPE_DESIGNATOR]
8230          --     [, [Mechanism        =>] MECHANISM]
8231          --     [, [Result_Mechanism =>] MECHANISM_NAME]);
8232
8233          --  EXTERNAL_SYMBOL ::=
8234          --    IDENTIFIER
8235          --  | static_string_EXPRESSION
8236
8237          --  PARAMETER_TYPES ::=
8238          --    null
8239          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8240
8241          --  TYPE_DESIGNATOR ::=
8242          --    subtype_NAME
8243          --  | subtype_Name ' Access
8244
8245          --  MECHANISM ::=
8246          --    MECHANISM_NAME
8247          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8248
8249          --  MECHANISM_ASSOCIATION ::=
8250          --    [formal_parameter_NAME =>] MECHANISM_NAME
8251
8252          --  MECHANISM_NAME ::=
8253          --    Value
8254          --  | Reference
8255          --  | Descriptor [([Class =>] CLASS_NAME)]
8256
8257          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8258
8259          when Pragma_Export_Function => Export_Function : declare
8260             Args  : Args_List (1 .. 6);
8261             Names : constant Name_List (1 .. 6) := (
8262                       Name_Internal,
8263                       Name_External,
8264                       Name_Parameter_Types,
8265                       Name_Result_Type,
8266                       Name_Mechanism,
8267                       Name_Result_Mechanism);
8268
8269             Internal         : Node_Id renames Args (1);
8270             External         : Node_Id renames Args (2);
8271             Parameter_Types  : Node_Id renames Args (3);
8272             Result_Type      : Node_Id renames Args (4);
8273             Mechanism        : Node_Id renames Args (5);
8274             Result_Mechanism : Node_Id renames Args (6);
8275
8276          begin
8277             GNAT_Pragma;
8278             Gather_Associations (Names, Args);
8279             Process_Extended_Import_Export_Subprogram_Pragma (
8280               Arg_Internal         => Internal,
8281               Arg_External         => External,
8282               Arg_Parameter_Types  => Parameter_Types,
8283               Arg_Result_Type      => Result_Type,
8284               Arg_Mechanism        => Mechanism,
8285               Arg_Result_Mechanism => Result_Mechanism);
8286          end Export_Function;
8287
8288          -------------------
8289          -- Export_Object --
8290          -------------------
8291
8292          --  pragma Export_Object (
8293          --        [Internal =>] LOCAL_NAME
8294          --     [, [External =>] EXTERNAL_SYMBOL]
8295          --     [, [Size     =>] EXTERNAL_SYMBOL]);
8296
8297          --  EXTERNAL_SYMBOL ::=
8298          --    IDENTIFIER
8299          --  | static_string_EXPRESSION
8300
8301          --  PARAMETER_TYPES ::=
8302          --    null
8303          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8304
8305          --  TYPE_DESIGNATOR ::=
8306          --    subtype_NAME
8307          --  | subtype_Name ' Access
8308
8309          --  MECHANISM ::=
8310          --    MECHANISM_NAME
8311          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8312
8313          --  MECHANISM_ASSOCIATION ::=
8314          --    [formal_parameter_NAME =>] MECHANISM_NAME
8315
8316          --  MECHANISM_NAME ::=
8317          --    Value
8318          --  | Reference
8319          --  | Descriptor [([Class =>] CLASS_NAME)]
8320
8321          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8322
8323          when Pragma_Export_Object => Export_Object : declare
8324             Args  : Args_List (1 .. 3);
8325             Names : constant Name_List (1 .. 3) := (
8326                       Name_Internal,
8327                       Name_External,
8328                       Name_Size);
8329
8330             Internal : Node_Id renames Args (1);
8331             External : Node_Id renames Args (2);
8332             Size     : Node_Id renames Args (3);
8333
8334          begin
8335             GNAT_Pragma;
8336             Gather_Associations (Names, Args);
8337             Process_Extended_Import_Export_Object_Pragma (
8338               Arg_Internal => Internal,
8339               Arg_External => External,
8340               Arg_Size     => Size);
8341          end Export_Object;
8342
8343          ----------------------
8344          -- Export_Procedure --
8345          ----------------------
8346
8347          --  pragma Export_Procedure (
8348          --        [Internal         =>] LOCAL_NAME
8349          --     [, [External         =>] EXTERNAL_SYMBOL]
8350          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8351          --     [, [Mechanism        =>] MECHANISM]);
8352
8353          --  EXTERNAL_SYMBOL ::=
8354          --    IDENTIFIER
8355          --  | static_string_EXPRESSION
8356
8357          --  PARAMETER_TYPES ::=
8358          --    null
8359          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8360
8361          --  TYPE_DESIGNATOR ::=
8362          --    subtype_NAME
8363          --  | subtype_Name ' Access
8364
8365          --  MECHANISM ::=
8366          --    MECHANISM_NAME
8367          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8368
8369          --  MECHANISM_ASSOCIATION ::=
8370          --    [formal_parameter_NAME =>] MECHANISM_NAME
8371
8372          --  MECHANISM_NAME ::=
8373          --    Value
8374          --  | Reference
8375          --  | Descriptor [([Class =>] CLASS_NAME)]
8376
8377          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8378
8379          when Pragma_Export_Procedure => Export_Procedure : declare
8380             Args  : Args_List (1 .. 4);
8381             Names : constant Name_List (1 .. 4) := (
8382                       Name_Internal,
8383                       Name_External,
8384                       Name_Parameter_Types,
8385                       Name_Mechanism);
8386
8387             Internal        : Node_Id renames Args (1);
8388             External        : Node_Id renames Args (2);
8389             Parameter_Types : Node_Id renames Args (3);
8390             Mechanism       : Node_Id renames Args (4);
8391
8392          begin
8393             GNAT_Pragma;
8394             Gather_Associations (Names, Args);
8395             Process_Extended_Import_Export_Subprogram_Pragma (
8396               Arg_Internal        => Internal,
8397               Arg_External        => External,
8398               Arg_Parameter_Types => Parameter_Types,
8399               Arg_Mechanism       => Mechanism);
8400          end Export_Procedure;
8401
8402          ------------------
8403          -- Export_Value --
8404          ------------------
8405
8406          --  pragma Export_Value (
8407          --     [Value     =>] static_integer_EXPRESSION,
8408          --     [Link_Name =>] static_string_EXPRESSION);
8409
8410          when Pragma_Export_Value =>
8411             GNAT_Pragma;
8412             Check_Arg_Order ((Name_Value, Name_Link_Name));
8413             Check_Arg_Count (2);
8414
8415             Check_Optional_Identifier (Arg1, Name_Value);
8416             Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
8417
8418             Check_Optional_Identifier (Arg2, Name_Link_Name);
8419             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
8420
8421          -----------------------------
8422          -- Export_Valued_Procedure --
8423          -----------------------------
8424
8425          --  pragma Export_Valued_Procedure (
8426          --        [Internal         =>] LOCAL_NAME
8427          --     [, [External         =>] EXTERNAL_SYMBOL,]
8428          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8429          --     [, [Mechanism        =>] MECHANISM]);
8430
8431          --  EXTERNAL_SYMBOL ::=
8432          --    IDENTIFIER
8433          --  | static_string_EXPRESSION
8434
8435          --  PARAMETER_TYPES ::=
8436          --    null
8437          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8438
8439          --  TYPE_DESIGNATOR ::=
8440          --    subtype_NAME
8441          --  | subtype_Name ' Access
8442
8443          --  MECHANISM ::=
8444          --    MECHANISM_NAME
8445          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8446
8447          --  MECHANISM_ASSOCIATION ::=
8448          --    [formal_parameter_NAME =>] MECHANISM_NAME
8449
8450          --  MECHANISM_NAME ::=
8451          --    Value
8452          --  | Reference
8453          --  | Descriptor [([Class =>] CLASS_NAME)]
8454
8455          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8456
8457          when Pragma_Export_Valued_Procedure =>
8458          Export_Valued_Procedure : declare
8459             Args  : Args_List (1 .. 4);
8460             Names : constant Name_List (1 .. 4) := (
8461                       Name_Internal,
8462                       Name_External,
8463                       Name_Parameter_Types,
8464                       Name_Mechanism);
8465
8466             Internal        : Node_Id renames Args (1);
8467             External        : Node_Id renames Args (2);
8468             Parameter_Types : Node_Id renames Args (3);
8469             Mechanism       : Node_Id renames Args (4);
8470
8471          begin
8472             GNAT_Pragma;
8473             Gather_Associations (Names, Args);
8474             Process_Extended_Import_Export_Subprogram_Pragma (
8475               Arg_Internal        => Internal,
8476               Arg_External        => External,
8477               Arg_Parameter_Types => Parameter_Types,
8478               Arg_Mechanism       => Mechanism);
8479          end Export_Valued_Procedure;
8480
8481          -------------------
8482          -- Extend_System --
8483          -------------------
8484
8485          --  pragma Extend_System ([Name =>] Identifier);
8486
8487          when Pragma_Extend_System => Extend_System : declare
8488          begin
8489             GNAT_Pragma;
8490             Check_Valid_Configuration_Pragma;
8491             Check_Arg_Count (1);
8492             Check_Optional_Identifier (Arg1, Name_Name);
8493             Check_Arg_Is_Identifier (Arg1);
8494
8495             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
8496
8497             if Name_Len > 4
8498               and then Name_Buffer (1 .. 4) = "aux_"
8499             then
8500                if Present (System_Extend_Pragma_Arg) then
8501                   if Chars (Get_Pragma_Arg (Arg1)) =
8502                      Chars (Expression (System_Extend_Pragma_Arg))
8503                   then
8504                      null;
8505                   else
8506                      Error_Msg_Sloc := Sloc (System_Extend_Pragma_Arg);
8507                      Error_Pragma ("pragma% conflicts with that #");
8508                   end if;
8509
8510                else
8511                   System_Extend_Pragma_Arg := Arg1;
8512
8513                   if not GNAT_Mode then
8514                      System_Extend_Unit := Arg1;
8515                   end if;
8516                end if;
8517             else
8518                Error_Pragma ("incorrect name for pragma%, must be Aux_xxx");
8519             end if;
8520          end Extend_System;
8521
8522          ------------------------
8523          -- Extensions_Allowed --
8524          ------------------------
8525
8526          --  pragma Extensions_Allowed (ON | OFF);
8527
8528          when Pragma_Extensions_Allowed =>
8529             GNAT_Pragma;
8530             Check_Arg_Count (1);
8531             Check_No_Identifiers;
8532             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
8533
8534             if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
8535                Extensions_Allowed := True;
8536                Ada_Version := Ada_Version_Type'Last;
8537
8538             else
8539                Extensions_Allowed := False;
8540                Ada_Version := Ada_Version_Explicit;
8541             end if;
8542
8543          --------------
8544          -- External --
8545          --------------
8546
8547          --  pragma External (
8548          --    [   Convention    =>] convention_IDENTIFIER,
8549          --    [   Entity        =>] local_NAME
8550          --    [, [External_Name =>] static_string_EXPRESSION ]
8551          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
8552
8553          when Pragma_External => External : declare
8554                Def_Id : Entity_Id;
8555
8556                C : Convention_Id;
8557                pragma Warnings (Off, C);
8558
8559          begin
8560             GNAT_Pragma;
8561             Check_Arg_Order
8562               ((Name_Convention,
8563                 Name_Entity,
8564                 Name_External_Name,
8565                 Name_Link_Name));
8566             Check_At_Least_N_Arguments (2);
8567             Check_At_Most_N_Arguments  (4);
8568             Process_Convention (C, Def_Id);
8569             Note_Possible_Modification
8570               (Get_Pragma_Arg (Arg2), Sure => False);
8571             Process_Interface_Name (Def_Id, Arg3, Arg4);
8572             Set_Exported (Def_Id, Arg2);
8573          end External;
8574
8575          --------------------------
8576          -- External_Name_Casing --
8577          --------------------------
8578
8579          --  pragma External_Name_Casing (
8580          --    UPPERCASE | LOWERCASE
8581          --    [, AS_IS | UPPERCASE | LOWERCASE]);
8582
8583          when Pragma_External_Name_Casing => External_Name_Casing : declare
8584          begin
8585             GNAT_Pragma;
8586             Check_No_Identifiers;
8587
8588             if Arg_Count = 2 then
8589                Check_Arg_Is_One_Of
8590                  (Arg2, Name_As_Is, Name_Uppercase, Name_Lowercase);
8591
8592                case Chars (Get_Pragma_Arg (Arg2)) is
8593                   when Name_As_Is     =>
8594                      Opt.External_Name_Exp_Casing := As_Is;
8595
8596                   when Name_Uppercase =>
8597                      Opt.External_Name_Exp_Casing := Uppercase;
8598
8599                   when Name_Lowercase =>
8600                      Opt.External_Name_Exp_Casing := Lowercase;
8601
8602                   when others =>
8603                      null;
8604                end case;
8605
8606             else
8607                Check_Arg_Count (1);
8608             end if;
8609
8610             Check_Arg_Is_One_Of (Arg1, Name_Uppercase, Name_Lowercase);
8611
8612             case Chars (Get_Pragma_Arg (Arg1)) is
8613                when Name_Uppercase =>
8614                   Opt.External_Name_Imp_Casing := Uppercase;
8615
8616                when Name_Lowercase =>
8617                   Opt.External_Name_Imp_Casing := Lowercase;
8618
8619                when others =>
8620                   null;
8621             end case;
8622          end External_Name_Casing;
8623
8624          --------------------------
8625          -- Favor_Top_Level --
8626          --------------------------
8627
8628          --  pragma Favor_Top_Level (type_NAME);
8629
8630          when Pragma_Favor_Top_Level => Favor_Top_Level : declare
8631                Named_Entity : Entity_Id;
8632
8633          begin
8634             GNAT_Pragma;
8635             Check_No_Identifiers;
8636             Check_Arg_Count (1);
8637             Check_Arg_Is_Local_Name (Arg1);
8638             Named_Entity := Entity (Get_Pragma_Arg (Arg1));
8639
8640             --  If it's an access-to-subprogram type (in particular, not a
8641             --  subtype), set the flag on that type.
8642
8643             if Is_Access_Subprogram_Type (Named_Entity) then
8644                Set_Can_Use_Internal_Rep (Named_Entity, False);
8645
8646             --  Otherwise it's an error (name denotes the wrong sort of entity)
8647
8648             else
8649                Error_Pragma_Arg
8650                  ("access-to-subprogram type expected",
8651                   Get_Pragma_Arg (Arg1));
8652             end if;
8653          end Favor_Top_Level;
8654
8655          ---------------
8656          -- Fast_Math --
8657          ---------------
8658
8659          --  pragma Fast_Math;
8660
8661          when Pragma_Fast_Math =>
8662             GNAT_Pragma;
8663             Check_No_Identifiers;
8664             Check_Valid_Configuration_Pragma;
8665             Fast_Math := True;
8666
8667          ---------------------------
8668          -- Finalize_Storage_Only --
8669          ---------------------------
8670
8671          --  pragma Finalize_Storage_Only (first_subtype_LOCAL_NAME);
8672
8673          when Pragma_Finalize_Storage_Only => Finalize_Storage : declare
8674             Assoc   : constant Node_Id := Arg1;
8675             Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
8676             Typ     : Entity_Id;
8677
8678          begin
8679             GNAT_Pragma;
8680             Check_No_Identifiers;
8681             Check_Arg_Count (1);
8682             Check_Arg_Is_Local_Name (Arg1);
8683
8684             Find_Type (Type_Id);
8685             Typ := Entity (Type_Id);
8686
8687             if Typ = Any_Type
8688               or else Rep_Item_Too_Early (Typ, N)
8689             then
8690                return;
8691             else
8692                Typ := Underlying_Type (Typ);
8693             end if;
8694
8695             if not Is_Controlled (Typ) then
8696                Error_Pragma ("pragma% must specify controlled type");
8697             end if;
8698
8699             Check_First_Subtype (Arg1);
8700
8701             if Finalize_Storage_Only (Typ) then
8702                Error_Pragma ("duplicate pragma%, only one allowed");
8703
8704             elsif not Rep_Item_Too_Late (Typ, N) then
8705                Set_Finalize_Storage_Only (Base_Type (Typ), True);
8706             end if;
8707          end Finalize_Storage;
8708
8709          --------------------------
8710          -- Float_Representation --
8711          --------------------------
8712
8713          --  pragma Float_Representation (FLOAT_REP[, float_type_LOCAL_NAME]);
8714
8715          --  FLOAT_REP ::= VAX_Float | IEEE_Float
8716
8717          when Pragma_Float_Representation => Float_Representation : declare
8718             Argx : Node_Id;
8719             Digs : Nat;
8720             Ent  : Entity_Id;
8721
8722          begin
8723             GNAT_Pragma;
8724
8725             if Arg_Count = 1 then
8726                Check_Valid_Configuration_Pragma;
8727             else
8728                Check_Arg_Count (2);
8729                Check_Optional_Identifier (Arg2, Name_Entity);
8730                Check_Arg_Is_Local_Name (Arg2);
8731             end if;
8732
8733             Check_No_Identifier (Arg1);
8734             Check_Arg_Is_One_Of (Arg1, Name_VAX_Float, Name_IEEE_Float);
8735
8736             if not OpenVMS_On_Target then
8737                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
8738                   Error_Pragma
8739                     ("?pragma% ignored (applies only to Open'V'M'S)");
8740                end if;
8741
8742                return;
8743             end if;
8744
8745             --  One argument case
8746
8747             if Arg_Count = 1 then
8748                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
8749                   if Opt.Float_Format = 'I' then
8750                      Error_Pragma ("'I'E'E'E format previously specified");
8751                   end if;
8752
8753                   Opt.Float_Format := 'V';
8754
8755                else
8756                   if Opt.Float_Format = 'V' then
8757                      Error_Pragma ("'V'A'X format previously specified");
8758                   end if;
8759
8760                   Opt.Float_Format := 'I';
8761                end if;
8762
8763                Set_Standard_Fpt_Formats;
8764
8765             --  Two argument case
8766
8767             else
8768                Argx := Get_Pragma_Arg (Arg2);
8769
8770                if not Is_Entity_Name (Argx)
8771                  or else not Is_Floating_Point_Type (Entity (Argx))
8772                then
8773                   Error_Pragma_Arg
8774                     ("second argument of% pragma must be floating-point type",
8775                      Arg2);
8776                end if;
8777
8778                Ent  := Entity (Argx);
8779                Digs := UI_To_Int (Digits_Value (Ent));
8780
8781                --  Two arguments, VAX_Float case
8782
8783                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
8784                   case Digs is
8785                      when  6 => Set_F_Float (Ent);
8786                      when  9 => Set_D_Float (Ent);
8787                      when 15 => Set_G_Float (Ent);
8788
8789                      when others =>
8790                         Error_Pragma_Arg
8791                           ("wrong digits value, must be 6,9 or 15", Arg2);
8792                   end case;
8793
8794                --  Two arguments, IEEE_Float case
8795
8796                else
8797                   case Digs is
8798                      when  6 => Set_IEEE_Short (Ent);
8799                      when 15 => Set_IEEE_Long  (Ent);
8800
8801                      when others =>
8802                         Error_Pragma_Arg
8803                           ("wrong digits value, must be 6 or 15", Arg2);
8804                   end case;
8805                end if;
8806             end if;
8807          end Float_Representation;
8808
8809          -----------
8810          -- Ident --
8811          -----------
8812
8813          --  pragma Ident (static_string_EXPRESSION)
8814
8815          --  Note: pragma Comment shares this processing. Pragma Comment is
8816          --  identical to Ident, except that the restriction of the argument to
8817          --  31 characters and the placement restrictions are not enforced for
8818          --  pragma Comment.
8819
8820          when Pragma_Ident | Pragma_Comment => Ident : declare
8821             Str : Node_Id;
8822
8823          begin
8824             GNAT_Pragma;
8825             Check_Arg_Count (1);
8826             Check_No_Identifiers;
8827             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
8828             Store_Note (N);
8829
8830             --  For pragma Ident, preserve DEC compatibility by requiring the
8831             --  pragma to appear in a declarative part or package spec.
8832
8833             if Prag_Id = Pragma_Ident then
8834                Check_Is_In_Decl_Part_Or_Package_Spec;
8835             end if;
8836
8837             Str := Expr_Value_S (Get_Pragma_Arg (Arg1));
8838
8839             declare
8840                CS : Node_Id;
8841                GP : Node_Id;
8842
8843             begin
8844                GP := Parent (Parent (N));
8845
8846                if Nkind_In (GP, N_Package_Declaration,
8847                                 N_Generic_Package_Declaration)
8848                then
8849                   GP := Parent (GP);
8850                end if;
8851
8852                --  If we have a compilation unit, then record the ident value,
8853                --  checking for improper duplication.
8854
8855                if Nkind (GP) = N_Compilation_Unit then
8856                   CS := Ident_String (Current_Sem_Unit);
8857
8858                   if Present (CS) then
8859
8860                      --  For Ident, we do not permit multiple instances
8861
8862                      if Prag_Id = Pragma_Ident then
8863                         Error_Pragma ("duplicate% pragma not permitted");
8864
8865                      --  For Comment, we concatenate the string, unless we want
8866                      --  to preserve the tree structure for ASIS.
8867
8868                      elsif not ASIS_Mode then
8869                         Start_String (Strval (CS));
8870                         Store_String_Char (' ');
8871                         Store_String_Chars (Strval (Str));
8872                         Set_Strval (CS, End_String);
8873                      end if;
8874
8875                   else
8876                      --  In VMS, the effect of IDENT is achieved by passing
8877                      --  --identification=name as a --for-linker switch.
8878
8879                      if OpenVMS_On_Target then
8880                         Start_String;
8881                         Store_String_Chars
8882                           ("--for-linker=--identification=");
8883                         String_To_Name_Buffer (Strval (Str));
8884                         Store_String_Chars (Name_Buffer (1 .. Name_Len));
8885
8886                         --  Only the last processed IDENT is saved. The main
8887                         --  purpose is so an IDENT associated with a main
8888                         --  procedure will be used in preference to an IDENT
8889                         --  associated with a with'd package.
8890
8891                         Replace_Linker_Option_String
8892                           (End_String, "--for-linker=--identification=");
8893                      end if;
8894
8895                      Set_Ident_String (Current_Sem_Unit, Str);
8896                   end if;
8897
8898                --  For subunits, we just ignore the Ident, since in GNAT these
8899                --  are not separate object files, and hence not separate units
8900                --  in the unit table.
8901
8902                elsif Nkind (GP) = N_Subunit then
8903                   null;
8904
8905                --  Otherwise we have a misplaced pragma Ident, but we ignore
8906                --  this if we are in an instantiation, since it comes from
8907                --  a generic, and has no relevance to the instantiation.
8908
8909                elsif Prag_Id = Pragma_Ident then
8910                   if Instantiation_Location (Loc) = No_Location then
8911                      Error_Pragma ("pragma% only allowed at outer level");
8912                   end if;
8913                end if;
8914             end;
8915          end Ident;
8916
8917          -----------------
8918          -- Implemented --
8919          -----------------
8920
8921          --  pragma Implemented (procedure_LOCAL_NAME, implementation_kind);
8922          --  implementation_kind ::= By_Entry | By_Protected_Procedure | By_Any
8923
8924          when Pragma_Implemented => Implemented : declare
8925             Proc_Id : Entity_Id;
8926             Typ     : Entity_Id;
8927
8928          begin
8929             Ada_2012_Pragma;
8930             Check_Arg_Count (2);
8931             Check_No_Identifiers;
8932             Check_Arg_Is_Identifier (Arg1);
8933             Check_Arg_Is_Local_Name (Arg1);
8934             Check_Arg_Is_One_Of
8935               (Arg2, Name_By_Any, Name_By_Entry, Name_By_Protected_Procedure);
8936
8937             --  Extract the name of the local procedure
8938
8939             Proc_Id := Entity (Get_Pragma_Arg (Arg1));
8940
8941             --  Ada 2012 (AI05-0030): The procedure_LOCAL_NAME must denote a
8942             --  primitive procedure of a synchronized tagged type.
8943
8944             if Ekind (Proc_Id) = E_Procedure
8945               and then Is_Primitive (Proc_Id)
8946               and then Present (First_Formal (Proc_Id))
8947             then
8948                Typ := Etype (First_Formal (Proc_Id));
8949
8950                if Is_Tagged_Type (Typ)
8951                  and then
8952
8953                   --  Check for a protected, a synchronized or a task interface
8954
8955                    ((Is_Interface (Typ)
8956                        and then Is_Synchronized_Interface (Typ))
8957
8958                   --  Check for a protected type or a task type that implements
8959                   --  an interface.
8960
8961                    or else
8962                     (Is_Concurrent_Record_Type (Typ)
8963                        and then Present (Interfaces (Typ)))
8964
8965                   --  Check for a private record extension with keyword
8966                   --  "synchronized".
8967
8968                    or else
8969                     (Ekind_In (Typ, E_Record_Type_With_Private,
8970                                     E_Record_Subtype_With_Private)
8971                        and then Synchronized_Present (Parent (Typ))))
8972                then
8973                   null;
8974                else
8975                   Error_Pragma_Arg
8976                     ("controlling formal must be of synchronized " &
8977                      "tagged type", Arg1);
8978                   return;
8979                end if;
8980
8981             --  Procedures declared inside a protected type must be accepted
8982
8983             elsif Ekind (Proc_Id) = E_Procedure
8984               and then Is_Protected_Type (Scope (Proc_Id))
8985             then
8986                null;
8987
8988             --  The first argument is not a primitive procedure
8989
8990             else
8991                Error_Pragma_Arg
8992                  ("pragma % must be applied to a primitive procedure", Arg1);
8993                return;
8994             end if;
8995
8996             --  Ada 2012 (AI05-0030): Cannot apply the implementation_kind
8997             --  By_Protected_Procedure to the primitive procedure of a task
8998             --  interface.
8999
9000             if Chars (Arg2) = Name_By_Protected_Procedure
9001               and then Is_Interface (Typ)
9002               and then Is_Task_Interface (Typ)
9003             then
9004                Error_Pragma_Arg
9005                  ("implementation kind By_Protected_Procedure cannot be " &
9006                   "applied to a task interface primitive", Arg2);
9007                return;
9008             end if;
9009
9010             Record_Rep_Item (Proc_Id, N);
9011          end Implemented;
9012
9013          ----------------------
9014          -- Implicit_Packing --
9015          ----------------------
9016
9017          --  pragma Implicit_Packing;
9018
9019          when Pragma_Implicit_Packing =>
9020             GNAT_Pragma;
9021             Check_Arg_Count (0);
9022             Implicit_Packing := True;
9023
9024          ------------
9025          -- Import --
9026          ------------
9027
9028          --  pragma Import (
9029          --       [Convention    =>] convention_IDENTIFIER,
9030          --       [Entity        =>] local_NAME
9031          --    [, [External_Name =>] static_string_EXPRESSION ]
9032          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
9033
9034          when Pragma_Import =>
9035             Check_Ada_83_Warning;
9036             Check_Arg_Order
9037               ((Name_Convention,
9038                 Name_Entity,
9039                 Name_External_Name,
9040                 Name_Link_Name));
9041             Check_At_Least_N_Arguments (2);
9042             Check_At_Most_N_Arguments  (4);
9043             Process_Import_Or_Interface;
9044
9045          ----------------------
9046          -- Import_Exception --
9047          ----------------------
9048
9049          --  pragma Import_Exception (
9050          --        [Internal         =>] LOCAL_NAME
9051          --     [, [External         =>] EXTERNAL_SYMBOL]
9052          --     [, [Form     =>] Ada | VMS]
9053          --     [, [Code     =>] static_integer_EXPRESSION]);
9054
9055          when Pragma_Import_Exception => Import_Exception : declare
9056             Args  : Args_List (1 .. 4);
9057             Names : constant Name_List (1 .. 4) := (
9058                       Name_Internal,
9059                       Name_External,
9060                       Name_Form,
9061                       Name_Code);
9062
9063             Internal : Node_Id renames Args (1);
9064             External : Node_Id renames Args (2);
9065             Form     : Node_Id renames Args (3);
9066             Code     : Node_Id renames Args (4);
9067
9068          begin
9069             GNAT_Pragma;
9070             Gather_Associations (Names, Args);
9071
9072             if Present (External) and then Present (Code) then
9073                Error_Pragma
9074                  ("cannot give both External and Code options for pragma%");
9075             end if;
9076
9077             Process_Extended_Import_Export_Exception_Pragma (
9078               Arg_Internal => Internal,
9079               Arg_External => External,
9080               Arg_Form     => Form,
9081               Arg_Code     => Code);
9082
9083             if not Is_VMS_Exception (Entity (Internal)) then
9084                Set_Imported (Entity (Internal));
9085             end if;
9086          end Import_Exception;
9087
9088          ---------------------
9089          -- Import_Function --
9090          ---------------------
9091
9092          --  pragma Import_Function (
9093          --        [Internal                 =>] LOCAL_NAME,
9094          --     [, [External                 =>] EXTERNAL_SYMBOL]
9095          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9096          --     [, [Result_Type              =>] SUBTYPE_MARK]
9097          --     [, [Mechanism                =>] MECHANISM]
9098          --     [, [Result_Mechanism         =>] MECHANISM_NAME]
9099          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9100
9101          --  EXTERNAL_SYMBOL ::=
9102          --    IDENTIFIER
9103          --  | static_string_EXPRESSION
9104
9105          --  PARAMETER_TYPES ::=
9106          --    null
9107          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9108
9109          --  TYPE_DESIGNATOR ::=
9110          --    subtype_NAME
9111          --  | subtype_Name ' Access
9112
9113          --  MECHANISM ::=
9114          --    MECHANISM_NAME
9115          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9116
9117          --  MECHANISM_ASSOCIATION ::=
9118          --    [formal_parameter_NAME =>] MECHANISM_NAME
9119
9120          --  MECHANISM_NAME ::=
9121          --    Value
9122          --  | Reference
9123          --  | Descriptor [([Class =>] CLASS_NAME)]
9124
9125          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9126
9127          when Pragma_Import_Function => Import_Function : declare
9128             Args  : Args_List (1 .. 7);
9129             Names : constant Name_List (1 .. 7) := (
9130                       Name_Internal,
9131                       Name_External,
9132                       Name_Parameter_Types,
9133                       Name_Result_Type,
9134                       Name_Mechanism,
9135                       Name_Result_Mechanism,
9136                       Name_First_Optional_Parameter);
9137
9138             Internal                 : Node_Id renames Args (1);
9139             External                 : Node_Id renames Args (2);
9140             Parameter_Types          : Node_Id renames Args (3);
9141             Result_Type              : Node_Id renames Args (4);
9142             Mechanism                : Node_Id renames Args (5);
9143             Result_Mechanism         : Node_Id renames Args (6);
9144             First_Optional_Parameter : Node_Id renames Args (7);
9145
9146          begin
9147             GNAT_Pragma;
9148             Gather_Associations (Names, Args);
9149             Process_Extended_Import_Export_Subprogram_Pragma (
9150               Arg_Internal                 => Internal,
9151               Arg_External                 => External,
9152               Arg_Parameter_Types          => Parameter_Types,
9153               Arg_Result_Type              => Result_Type,
9154               Arg_Mechanism                => Mechanism,
9155               Arg_Result_Mechanism         => Result_Mechanism,
9156               Arg_First_Optional_Parameter => First_Optional_Parameter);
9157          end Import_Function;
9158
9159          -------------------
9160          -- Import_Object --
9161          -------------------
9162
9163          --  pragma Import_Object (
9164          --        [Internal =>] LOCAL_NAME
9165          --     [, [External =>] EXTERNAL_SYMBOL]
9166          --     [, [Size     =>] EXTERNAL_SYMBOL]);
9167
9168          --  EXTERNAL_SYMBOL ::=
9169          --    IDENTIFIER
9170          --  | static_string_EXPRESSION
9171
9172          when Pragma_Import_Object => Import_Object : declare
9173             Args  : Args_List (1 .. 3);
9174             Names : constant Name_List (1 .. 3) := (
9175                       Name_Internal,
9176                       Name_External,
9177                       Name_Size);
9178
9179             Internal : Node_Id renames Args (1);
9180             External : Node_Id renames Args (2);
9181             Size     : Node_Id renames Args (3);
9182
9183          begin
9184             GNAT_Pragma;
9185             Gather_Associations (Names, Args);
9186             Process_Extended_Import_Export_Object_Pragma (
9187               Arg_Internal => Internal,
9188               Arg_External => External,
9189               Arg_Size     => Size);
9190          end Import_Object;
9191
9192          ----------------------
9193          -- Import_Procedure --
9194          ----------------------
9195
9196          --  pragma Import_Procedure (
9197          --        [Internal                 =>] LOCAL_NAME
9198          --     [, [External                 =>] EXTERNAL_SYMBOL]
9199          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9200          --     [, [Mechanism                =>] MECHANISM]
9201          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9202
9203          --  EXTERNAL_SYMBOL ::=
9204          --    IDENTIFIER
9205          --  | static_string_EXPRESSION
9206
9207          --  PARAMETER_TYPES ::=
9208          --    null
9209          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9210
9211          --  TYPE_DESIGNATOR ::=
9212          --    subtype_NAME
9213          --  | subtype_Name ' Access
9214
9215          --  MECHANISM ::=
9216          --    MECHANISM_NAME
9217          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9218
9219          --  MECHANISM_ASSOCIATION ::=
9220          --    [formal_parameter_NAME =>] MECHANISM_NAME
9221
9222          --  MECHANISM_NAME ::=
9223          --    Value
9224          --  | Reference
9225          --  | Descriptor [([Class =>] CLASS_NAME)]
9226
9227          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9228
9229          when Pragma_Import_Procedure => Import_Procedure : declare
9230             Args  : Args_List (1 .. 5);
9231             Names : constant Name_List (1 .. 5) := (
9232                       Name_Internal,
9233                       Name_External,
9234                       Name_Parameter_Types,
9235                       Name_Mechanism,
9236                       Name_First_Optional_Parameter);
9237
9238             Internal                 : Node_Id renames Args (1);
9239             External                 : Node_Id renames Args (2);
9240             Parameter_Types          : Node_Id renames Args (3);
9241             Mechanism                : Node_Id renames Args (4);
9242             First_Optional_Parameter : Node_Id renames Args (5);
9243
9244          begin
9245             GNAT_Pragma;
9246             Gather_Associations (Names, Args);
9247             Process_Extended_Import_Export_Subprogram_Pragma (
9248               Arg_Internal                 => Internal,
9249               Arg_External                 => External,
9250               Arg_Parameter_Types          => Parameter_Types,
9251               Arg_Mechanism                => Mechanism,
9252               Arg_First_Optional_Parameter => First_Optional_Parameter);
9253          end Import_Procedure;
9254
9255          -----------------------------
9256          -- Import_Valued_Procedure --
9257          -----------------------------
9258
9259          --  pragma Import_Valued_Procedure (
9260          --        [Internal                 =>] LOCAL_NAME
9261          --     [, [External                 =>] EXTERNAL_SYMBOL]
9262          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9263          --     [, [Mechanism                =>] MECHANISM]
9264          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9265
9266          --  EXTERNAL_SYMBOL ::=
9267          --    IDENTIFIER
9268          --  | static_string_EXPRESSION
9269
9270          --  PARAMETER_TYPES ::=
9271          --    null
9272          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9273
9274          --  TYPE_DESIGNATOR ::=
9275          --    subtype_NAME
9276          --  | subtype_Name ' Access
9277
9278          --  MECHANISM ::=
9279          --    MECHANISM_NAME
9280          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9281
9282          --  MECHANISM_ASSOCIATION ::=
9283          --    [formal_parameter_NAME =>] MECHANISM_NAME
9284
9285          --  MECHANISM_NAME ::=
9286          --    Value
9287          --  | Reference
9288          --  | Descriptor [([Class =>] CLASS_NAME)]
9289
9290          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9291
9292          when Pragma_Import_Valued_Procedure =>
9293          Import_Valued_Procedure : declare
9294             Args  : Args_List (1 .. 5);
9295             Names : constant Name_List (1 .. 5) := (
9296                       Name_Internal,
9297                       Name_External,
9298                       Name_Parameter_Types,
9299                       Name_Mechanism,
9300                       Name_First_Optional_Parameter);
9301
9302             Internal                 : Node_Id renames Args (1);
9303             External                 : Node_Id renames Args (2);
9304             Parameter_Types          : Node_Id renames Args (3);
9305             Mechanism                : Node_Id renames Args (4);
9306             First_Optional_Parameter : Node_Id renames Args (5);
9307
9308          begin
9309             GNAT_Pragma;
9310             Gather_Associations (Names, Args);
9311             Process_Extended_Import_Export_Subprogram_Pragma (
9312               Arg_Internal                 => Internal,
9313               Arg_External                 => External,
9314               Arg_Parameter_Types          => Parameter_Types,
9315               Arg_Mechanism                => Mechanism,
9316               Arg_First_Optional_Parameter => First_Optional_Parameter);
9317          end Import_Valued_Procedure;
9318
9319          -----------------
9320          -- Independent --
9321          -----------------
9322
9323          --  pragma Independent (LOCAL_NAME);
9324
9325          when Pragma_Independent => Independent : declare
9326             E_Id : Node_Id;
9327             E    : Entity_Id;
9328             D    : Node_Id;
9329             K    : Node_Kind;
9330
9331          begin
9332             Check_Ada_83_Warning;
9333             Ada_2012_Pragma;
9334             Check_No_Identifiers;
9335             Check_Arg_Count (1);
9336             Check_Arg_Is_Local_Name (Arg1);
9337             E_Id := Get_Pragma_Arg (Arg1);
9338
9339             if Etype (E_Id) = Any_Type then
9340                return;
9341             end if;
9342
9343             E := Entity (E_Id);
9344             D := Declaration_Node (E);
9345             K := Nkind (D);
9346
9347             --  Check duplicate before we chain ourselves!
9348
9349             Check_Duplicate_Pragma (E);
9350
9351             --  Check appropriate entity
9352
9353             if Is_Type (E) then
9354                if Rep_Item_Too_Early (E, N)
9355                     or else
9356                   Rep_Item_Too_Late (E, N)
9357                then
9358                   return;
9359                else
9360                   Check_First_Subtype (Arg1);
9361                end if;
9362
9363             elsif K = N_Object_Declaration
9364               or else (K = N_Component_Declaration
9365                        and then Original_Record_Component (E) = E)
9366             then
9367                if Rep_Item_Too_Late (E, N) then
9368                   return;
9369                end if;
9370
9371             else
9372                Error_Pragma_Arg
9373                  ("inappropriate entity for pragma%", Arg1);
9374             end if;
9375
9376             Independence_Checks.Append ((N, E));
9377          end Independent;
9378
9379          ----------------------------
9380          -- Independent_Components --
9381          ----------------------------
9382
9383          --  pragma Atomic_Components (array_LOCAL_NAME);
9384
9385          --  This processing is shared by Volatile_Components
9386
9387          when Pragma_Independent_Components => Independent_Components : declare
9388             E_Id : Node_Id;
9389             E    : Entity_Id;
9390             D    : Node_Id;
9391             K    : Node_Kind;
9392
9393          begin
9394             Check_Ada_83_Warning;
9395             Ada_2012_Pragma;
9396             Check_No_Identifiers;
9397             Check_Arg_Count (1);
9398             Check_Arg_Is_Local_Name (Arg1);
9399             E_Id := Get_Pragma_Arg (Arg1);
9400
9401             if Etype (E_Id) = Any_Type then
9402                return;
9403             end if;
9404
9405             E := Entity (E_Id);
9406
9407             --  Check duplicate before we chain ourselves!
9408
9409             Check_Duplicate_Pragma (E);
9410
9411             --  Check appropriate entity
9412
9413             if Rep_Item_Too_Early (E, N)
9414                  or else
9415                Rep_Item_Too_Late (E, N)
9416             then
9417                return;
9418             end if;
9419
9420             D := Declaration_Node (E);
9421             K := Nkind (D);
9422
9423             if (K = N_Full_Type_Declaration
9424                  and then (Is_Array_Type (E) or else Is_Record_Type (E)))
9425               or else
9426                 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
9427                    and then Nkind (D) = N_Object_Declaration
9428                    and then Nkind (Object_Definition (D)) =
9429                                        N_Constrained_Array_Definition)
9430             then
9431                Independence_Checks.Append ((N, E));
9432
9433             else
9434                Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
9435             end if;
9436          end Independent_Components;
9437
9438          ------------------------
9439          -- Initialize_Scalars --
9440          ------------------------
9441
9442          --  pragma Initialize_Scalars;
9443
9444          when Pragma_Initialize_Scalars =>
9445             GNAT_Pragma;
9446             Check_Arg_Count (0);
9447             Check_Valid_Configuration_Pragma;
9448             Check_Restriction (No_Initialize_Scalars, N);
9449
9450             --  Initialize_Scalars creates false positives in CodePeer, and
9451             --  incorrect negative results in ALFA mode, so ignore this pragma
9452             --  in these modes.
9453
9454             if not Restriction_Active (No_Initialize_Scalars)
9455               and then not (CodePeer_Mode or ALFA_Mode)
9456             then
9457                Init_Or_Norm_Scalars := True;
9458                Initialize_Scalars := True;
9459             end if;
9460
9461          ------------
9462          -- Inline --
9463          ------------
9464
9465          --  pragma Inline ( NAME {, NAME} );
9466
9467          when Pragma_Inline =>
9468
9469             --  Pragma is active if inlining option is active
9470
9471             Process_Inline (Inline_Active);
9472
9473          -------------------
9474          -- Inline_Always --
9475          -------------------
9476
9477          --  pragma Inline_Always ( NAME {, NAME} );
9478
9479          when Pragma_Inline_Always =>
9480             GNAT_Pragma;
9481
9482             --  Pragma always active unless in CodePeer or ALFA mode, since
9483             --  this causes walk order issues.
9484
9485             if not (CodePeer_Mode or ALFA_Mode) then
9486                Process_Inline (True);
9487             end if;
9488
9489          --------------------
9490          -- Inline_Generic --
9491          --------------------
9492
9493          --  pragma Inline_Generic (NAME {, NAME});
9494
9495          when Pragma_Inline_Generic =>
9496             GNAT_Pragma;
9497             Process_Generic_List;
9498
9499          ----------------------
9500          -- Inspection_Point --
9501          ----------------------
9502
9503          --  pragma Inspection_Point [(object_NAME {, object_NAME})];
9504
9505          when Pragma_Inspection_Point => Inspection_Point : declare
9506             Arg : Node_Id;
9507             Exp : Node_Id;
9508
9509          begin
9510             if Arg_Count > 0 then
9511                Arg := Arg1;
9512                loop
9513                   Exp := Get_Pragma_Arg (Arg);
9514                   Analyze (Exp);
9515
9516                   if not Is_Entity_Name (Exp)
9517                     or else not Is_Object (Entity (Exp))
9518                   then
9519                      Error_Pragma_Arg ("object name required", Arg);
9520                   end if;
9521
9522                   Next (Arg);
9523                   exit when No (Arg);
9524                end loop;
9525             end if;
9526          end Inspection_Point;
9527
9528          ---------------
9529          -- Interface --
9530          ---------------
9531
9532          --  pragma Interface (
9533          --    [   Convention    =>] convention_IDENTIFIER,
9534          --    [   Entity        =>] local_NAME
9535          --    [, [External_Name =>] static_string_EXPRESSION ]
9536          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
9537
9538          when Pragma_Interface =>
9539             GNAT_Pragma;
9540             Check_Arg_Order
9541               ((Name_Convention,
9542                 Name_Entity,
9543                 Name_External_Name,
9544                 Name_Link_Name));
9545             Check_At_Least_N_Arguments (2);
9546             Check_At_Most_N_Arguments  (4);
9547             Process_Import_Or_Interface;
9548
9549             --  In Ada 2005, the permission to use Interface (a reserved word)
9550             --  as a pragma name is considered an obsolescent feature.
9551
9552             if Ada_Version >= Ada_2005 then
9553                Check_Restriction
9554                  (No_Obsolescent_Features, Pragma_Identifier (N));
9555             end if;
9556
9557          --------------------
9558          -- Interface_Name --
9559          --------------------
9560
9561          --  pragma Interface_Name (
9562          --    [  Entity        =>] local_NAME
9563          --    [,[External_Name =>] static_string_EXPRESSION ]
9564          --    [,[Link_Name     =>] static_string_EXPRESSION ]);
9565
9566          when Pragma_Interface_Name => Interface_Name : declare
9567             Id     : Node_Id;
9568             Def_Id : Entity_Id;
9569             Hom_Id : Entity_Id;
9570             Found  : Boolean;
9571
9572          begin
9573             GNAT_Pragma;
9574             Check_Arg_Order
9575               ((Name_Entity, Name_External_Name, Name_Link_Name));
9576             Check_At_Least_N_Arguments (2);
9577             Check_At_Most_N_Arguments  (3);
9578             Id := Get_Pragma_Arg (Arg1);
9579             Analyze (Id);
9580
9581             if not Is_Entity_Name (Id) then
9582                Error_Pragma_Arg
9583                  ("first argument for pragma% must be entity name", Arg1);
9584             elsif Etype (Id) = Any_Type then
9585                return;
9586             else
9587                Def_Id := Entity (Id);
9588             end if;
9589
9590             --  Special DEC-compatible processing for the object case, forces
9591             --  object to be imported.
9592
9593             if Ekind (Def_Id) = E_Variable then
9594                Kill_Size_Check_Code (Def_Id);
9595                Note_Possible_Modification (Id, Sure => False);
9596
9597                --  Initialization is not allowed for imported variable
9598
9599                if Present (Expression (Parent (Def_Id)))
9600                  and then Comes_From_Source (Expression (Parent (Def_Id)))
9601                then
9602                   Error_Msg_Sloc := Sloc (Def_Id);
9603                   Error_Pragma_Arg
9604                     ("no initialization allowed for declaration of& #",
9605                      Arg2);
9606
9607                else
9608                   --  For compatibility, support VADS usage of providing both
9609                   --  pragmas Interface and Interface_Name to obtain the effect
9610                   --  of a single Import pragma.
9611
9612                   if Is_Imported (Def_Id)
9613                     and then Present (First_Rep_Item (Def_Id))
9614                     and then Nkind (First_Rep_Item (Def_Id)) = N_Pragma
9615                     and then
9616                       Pragma_Name (First_Rep_Item (Def_Id)) = Name_Interface
9617                   then
9618                      null;
9619                   else
9620                      Set_Imported (Def_Id);
9621                   end if;
9622
9623                   Set_Is_Public (Def_Id);
9624                   Process_Interface_Name (Def_Id, Arg2, Arg3);
9625                end if;
9626
9627             --  Otherwise must be subprogram
9628
9629             elsif not Is_Subprogram (Def_Id) then
9630                Error_Pragma_Arg
9631                  ("argument of pragma% is not subprogram", Arg1);
9632
9633             else
9634                Check_At_Most_N_Arguments (3);
9635                Hom_Id := Def_Id;
9636                Found := False;
9637
9638                --  Loop through homonyms
9639
9640                loop
9641                   Def_Id := Get_Base_Subprogram (Hom_Id);
9642
9643                   if Is_Imported (Def_Id) then
9644                      Process_Interface_Name (Def_Id, Arg2, Arg3);
9645                      Found := True;
9646                   end if;
9647
9648                   exit when From_Aspect_Specification (N);
9649                   Hom_Id := Homonym (Hom_Id);
9650
9651                   exit when No (Hom_Id)
9652                     or else Scope (Hom_Id) /= Current_Scope;
9653                end loop;
9654
9655                if not Found then
9656                   Error_Pragma_Arg
9657                     ("argument of pragma% is not imported subprogram",
9658                      Arg1);
9659                end if;
9660             end if;
9661          end Interface_Name;
9662
9663          -----------------------
9664          -- Interrupt_Handler --
9665          -----------------------
9666
9667          --  pragma Interrupt_Handler (handler_NAME);
9668
9669          when Pragma_Interrupt_Handler =>
9670             Check_Ada_83_Warning;
9671             Check_Arg_Count (1);
9672             Check_No_Identifiers;
9673
9674             if No_Run_Time_Mode then
9675                Error_Msg_CRT ("Interrupt_Handler pragma", N);
9676             else
9677                Check_Interrupt_Or_Attach_Handler;
9678                Process_Interrupt_Or_Attach_Handler;
9679             end if;
9680
9681          ------------------------
9682          -- Interrupt_Priority --
9683          ------------------------
9684
9685          --  pragma Interrupt_Priority [(EXPRESSION)];
9686
9687          when Pragma_Interrupt_Priority => Interrupt_Priority : declare
9688             P   : constant Node_Id := Parent (N);
9689             Arg : Node_Id;
9690
9691          begin
9692             Check_Ada_83_Warning;
9693
9694             if Arg_Count /= 0 then
9695                Arg := Get_Pragma_Arg (Arg1);
9696                Check_Arg_Count (1);
9697                Check_No_Identifiers;
9698
9699                --  The expression must be analyzed in the special manner
9700                --  described in "Handling of Default and Per-Object
9701                --  Expressions" in sem.ads.
9702
9703                Preanalyze_Spec_Expression (Arg, RTE (RE_Interrupt_Priority));
9704             end if;
9705
9706             if not Nkind_In (P, N_Task_Definition, N_Protected_Definition) then
9707                Pragma_Misplaced;
9708                return;
9709
9710             elsif Has_Pragma_Priority (P) then
9711                Error_Pragma ("duplicate pragma% not allowed");
9712
9713             else
9714                Set_Has_Pragma_Priority (P, True);
9715                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
9716             end if;
9717          end Interrupt_Priority;
9718
9719          ---------------------
9720          -- Interrupt_State --
9721          ---------------------
9722
9723          --  pragma Interrupt_State (
9724          --    [Name  =>] INTERRUPT_ID,
9725          --    [State =>] INTERRUPT_STATE);
9726
9727          --  INTERRUPT_ID => IDENTIFIER | static_integer_EXPRESSION
9728          --  INTERRUPT_STATE => System | Runtime | User
9729
9730          --  Note: if the interrupt id is given as an identifier, then it must
9731          --  be one of the identifiers in Ada.Interrupts.Names. Otherwise it is
9732          --  given as a static integer expression which must be in the range of
9733          --  Ada.Interrupts.Interrupt_ID.
9734
9735          when Pragma_Interrupt_State => Interrupt_State : declare
9736
9737             Int_Id : constant Entity_Id := RTE (RE_Interrupt_ID);
9738             --  This is the entity Ada.Interrupts.Interrupt_ID;
9739
9740             State_Type : Character;
9741             --  Set to 's'/'r'/'u' for System/Runtime/User
9742
9743             IST_Num : Pos;
9744             --  Index to entry in Interrupt_States table
9745
9746             Int_Val : Uint;
9747             --  Value of interrupt
9748
9749             Arg1X : constant Node_Id := Get_Pragma_Arg (Arg1);
9750             --  The first argument to the pragma
9751
9752             Int_Ent : Entity_Id;
9753             --  Interrupt entity in Ada.Interrupts.Names
9754
9755          begin
9756             GNAT_Pragma;
9757             Check_Arg_Order ((Name_Name, Name_State));
9758             Check_Arg_Count (2);
9759
9760             Check_Optional_Identifier (Arg1, Name_Name);
9761             Check_Optional_Identifier (Arg2, Name_State);
9762             Check_Arg_Is_Identifier (Arg2);
9763
9764             --  First argument is identifier
9765
9766             if Nkind (Arg1X) = N_Identifier then
9767
9768                --  Search list of names in Ada.Interrupts.Names
9769
9770                Int_Ent := First_Entity (RTE (RE_Names));
9771                loop
9772                   if No (Int_Ent) then
9773                      Error_Pragma_Arg ("invalid interrupt name", Arg1);
9774
9775                   elsif Chars (Int_Ent) = Chars (Arg1X) then
9776                      Int_Val := Expr_Value (Constant_Value (Int_Ent));
9777                      exit;
9778                   end if;
9779
9780                   Next_Entity (Int_Ent);
9781                end loop;
9782
9783             --  First argument is not an identifier, so it must be a static
9784             --  expression of type Ada.Interrupts.Interrupt_ID.
9785
9786             else
9787                Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
9788                Int_Val := Expr_Value (Arg1X);
9789
9790                if Int_Val < Expr_Value (Type_Low_Bound (Int_Id))
9791                     or else
9792                   Int_Val > Expr_Value (Type_High_Bound (Int_Id))
9793                then
9794                   Error_Pragma_Arg
9795                     ("value not in range of type " &
9796                      """Ada.Interrupts.Interrupt_'I'D""", Arg1);
9797                end if;
9798             end if;
9799
9800             --  Check OK state
9801
9802             case Chars (Get_Pragma_Arg (Arg2)) is
9803                when Name_Runtime => State_Type := 'r';
9804                when Name_System  => State_Type := 's';
9805                when Name_User    => State_Type := 'u';
9806
9807                when others =>
9808                   Error_Pragma_Arg ("invalid interrupt state", Arg2);
9809             end case;
9810
9811             --  Check if entry is already stored
9812
9813             IST_Num := Interrupt_States.First;
9814             loop
9815                --  If entry not found, add it
9816
9817                if IST_Num > Interrupt_States.Last then
9818                   Interrupt_States.Append
9819                     ((Interrupt_Number => UI_To_Int (Int_Val),
9820                       Interrupt_State  => State_Type,
9821                       Pragma_Loc       => Loc));
9822                   exit;
9823
9824                --  Case of entry for the same entry
9825
9826                elsif Int_Val = Interrupt_States.Table (IST_Num).
9827                                                            Interrupt_Number
9828                then
9829                   --  If state matches, done, no need to make redundant entry
9830
9831                   exit when
9832                     State_Type = Interrupt_States.Table (IST_Num).
9833                                                            Interrupt_State;
9834
9835                   --  Otherwise if state does not match, error
9836
9837                   Error_Msg_Sloc :=
9838                     Interrupt_States.Table (IST_Num).Pragma_Loc;
9839                   Error_Pragma_Arg
9840                     ("state conflicts with that given #", Arg2);
9841                   exit;
9842                end if;
9843
9844                IST_Num := IST_Num + 1;
9845             end loop;
9846          end Interrupt_State;
9847
9848          ---------------
9849          -- Invariant --
9850          ---------------
9851
9852          --  pragma Invariant
9853          --    ([Entity =>]    type_LOCAL_NAME,
9854          --     [Check  =>]    EXPRESSION
9855          --     [,[Message =>] String_Expression]);
9856
9857          when Pragma_Invariant => Invariant : declare
9858             Type_Id : Node_Id;
9859             Typ     : Entity_Id;
9860
9861             Discard : Boolean;
9862             pragma Unreferenced (Discard);
9863
9864          begin
9865             GNAT_Pragma;
9866             Check_At_Least_N_Arguments (2);
9867             Check_At_Most_N_Arguments (3);
9868             Check_Optional_Identifier (Arg1, Name_Entity);
9869             Check_Optional_Identifier (Arg2, Name_Check);
9870
9871             if Arg_Count = 3 then
9872                Check_Optional_Identifier (Arg3, Name_Message);
9873                Check_Arg_Is_Static_Expression (Arg3, Standard_String);
9874             end if;
9875
9876             Check_Arg_Is_Local_Name (Arg1);
9877
9878             Type_Id := Get_Pragma_Arg (Arg1);
9879             Find_Type (Type_Id);
9880             Typ := Entity (Type_Id);
9881
9882             if Typ = Any_Type then
9883                return;
9884
9885             elsif not Ekind_In (Typ, E_Private_Type,
9886                                      E_Record_Type_With_Private,
9887                                      E_Limited_Private_Type)
9888             then
9889                Error_Pragma_Arg
9890                  ("pragma% only allowed for private type", Arg1);
9891             end if;
9892
9893             --  Note that the type has at least one invariant, and also that
9894             --  it has inheritable invariants if we have Invariant'Class.
9895
9896             Set_Has_Invariants (Typ);
9897
9898             if Class_Present (N) then
9899                Set_Has_Inheritable_Invariants (Typ);
9900             end if;
9901
9902             --  The remaining processing is simply to link the pragma on to
9903             --  the rep item chain, for processing when the type is frozen.
9904             --  This is accomplished by a call to Rep_Item_Too_Late.
9905
9906             Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
9907          end Invariant;
9908
9909          ----------------------
9910          -- Java_Constructor --
9911          ----------------------
9912
9913          --  pragma Java_Constructor ([Entity =>] LOCAL_NAME);
9914
9915          --  Also handles pragma CIL_Constructor
9916
9917          when Pragma_CIL_Constructor | Pragma_Java_Constructor =>
9918          Java_Constructor : declare
9919             Convention  : Convention_Id;
9920             Def_Id      : Entity_Id;
9921             Hom_Id      : Entity_Id;
9922             Id          : Entity_Id;
9923             This_Formal : Entity_Id;
9924
9925          begin
9926             GNAT_Pragma;
9927             Check_Arg_Count (1);
9928             Check_Optional_Identifier (Arg1, Name_Entity);
9929             Check_Arg_Is_Local_Name (Arg1);
9930
9931             Id := Get_Pragma_Arg (Arg1);
9932             Find_Program_Unit_Name (Id);
9933
9934             --  If we did not find the name, we are done
9935
9936             if Etype (Id) = Any_Type then
9937                return;
9938             end if;
9939
9940             --  Check wrong use of pragma in wrong VM target
9941
9942             if VM_Target = No_VM then
9943                return;
9944
9945             elsif VM_Target = CLI_Target
9946               and then Prag_Id = Pragma_Java_Constructor
9947             then
9948                Error_Pragma ("must use pragma 'C'I'L_'Constructor");
9949
9950             elsif VM_Target = JVM_Target
9951               and then Prag_Id = Pragma_CIL_Constructor
9952             then
9953                Error_Pragma ("must use pragma 'Java_'Constructor");
9954             end if;
9955
9956             case Prag_Id is
9957                when Pragma_CIL_Constructor  => Convention := Convention_CIL;
9958                when Pragma_Java_Constructor => Convention := Convention_Java;
9959                when others                  => null;
9960             end case;
9961
9962             Hom_Id := Entity (Id);
9963
9964             --  Loop through homonyms
9965
9966             loop
9967                Def_Id := Get_Base_Subprogram (Hom_Id);
9968
9969                --  The constructor is required to be a function
9970
9971                if Ekind (Def_Id) /= E_Function then
9972                   if VM_Target = JVM_Target then
9973                      Error_Pragma_Arg
9974                        ("pragma% requires function returning a " &
9975                         "'Java access type", Def_Id);
9976                   else
9977                      Error_Pragma_Arg
9978                        ("pragma% requires function returning a " &
9979                         "'C'I'L access type", Def_Id);
9980                   end if;
9981                end if;
9982
9983                --  Check arguments: For tagged type the first formal must be
9984                --  named "this" and its type must be a named access type
9985                --  designating a class-wide tagged type that has convention
9986                --  CIL/Java. The first formal must also have a null default
9987                --  value. For example:
9988
9989                --      type Typ is tagged ...
9990                --      type Ref is access all Typ;
9991                --      pragma Convention (CIL, Typ);
9992
9993                --      function New_Typ (This : Ref) return Ref;
9994                --      function New_Typ (This : Ref; I : Integer) return Ref;
9995                --      pragma Cil_Constructor (New_Typ);
9996
9997                --  Reason: The first formal must NOT be a primitive of the
9998                --  tagged type.
9999
10000                --  This rule also applies to constructors of delegates used
10001                --  to interface with standard target libraries. For example:
10002
10003                --      type Delegate is access procedure ...
10004                --      pragma Import (CIL, Delegate, ...);
10005
10006                --      function new_Delegate
10007                --        (This : Delegate := null; ... ) return Delegate;
10008
10009                --  For value-types this rule does not apply.
10010
10011                if not Is_Value_Type (Etype (Def_Id)) then
10012                   if No (First_Formal (Def_Id)) then
10013                      Error_Msg_Name_1 := Pname;
10014                      Error_Msg_N ("% function must have parameters", Def_Id);
10015                      return;
10016                   end if;
10017
10018                   --  In the JRE library we have several occurrences in which
10019                   --  the "this" parameter is not the first formal.
10020
10021                   This_Formal := First_Formal (Def_Id);
10022
10023                   --  In the JRE library we have several occurrences in which
10024                   --  the "this" parameter is not the first formal. Search for
10025                   --  it.
10026
10027                   if VM_Target = JVM_Target then
10028                      while Present (This_Formal)
10029                        and then Get_Name_String (Chars (This_Formal)) /= "this"
10030                      loop
10031                         Next_Formal (This_Formal);
10032                      end loop;
10033
10034                      if No (This_Formal) then
10035                         This_Formal := First_Formal (Def_Id);
10036                      end if;
10037                   end if;
10038
10039                   --  Warning: The first parameter should be named "this".
10040                   --  We temporarily allow it because we have the following
10041                   --  case in the Java runtime (file s-osinte.ads) ???
10042
10043                   --    function new_Thread
10044                   --      (Self_Id : System.Address) return Thread_Id;
10045                   --    pragma Java_Constructor (new_Thread);
10046
10047                   if VM_Target = JVM_Target
10048                     and then Get_Name_String (Chars (First_Formal (Def_Id)))
10049                                = "self_id"
10050                     and then Etype (First_Formal (Def_Id)) = RTE (RE_Address)
10051                   then
10052                      null;
10053
10054                   elsif Get_Name_String (Chars (This_Formal)) /= "this" then
10055                      Error_Msg_Name_1 := Pname;
10056                      Error_Msg_N
10057                        ("first formal of % function must be named `this`",
10058                         Parent (This_Formal));
10059
10060                   elsif not Is_Access_Type (Etype (This_Formal)) then
10061                      Error_Msg_Name_1 := Pname;
10062                      Error_Msg_N
10063                        ("first formal of % function must be an access type",
10064                         Parameter_Type (Parent (This_Formal)));
10065
10066                   --  For delegates the type of the first formal must be a
10067                   --  named access-to-subprogram type (see previous example)
10068
10069                   elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type
10070                     and then Ekind (Etype (This_Formal))
10071                                /= E_Access_Subprogram_Type
10072                   then
10073                      Error_Msg_Name_1 := Pname;
10074                      Error_Msg_N
10075                        ("first formal of % function must be a named access" &
10076                         " to subprogram type",
10077                         Parameter_Type (Parent (This_Formal)));
10078
10079                   --  Warning: We should reject anonymous access types because
10080                   --  the constructor must not be handled as a primitive of the
10081                   --  tagged type. We temporarily allow it because this profile
10082                   --  is currently generated by cil2ada???
10083
10084                   elsif Ekind (Etype (Def_Id)) /= E_Access_Subprogram_Type
10085                     and then not Ekind_In (Etype (This_Formal),
10086                                              E_Access_Type,
10087                                              E_General_Access_Type,
10088                                              E_Anonymous_Access_Type)
10089                   then
10090                      Error_Msg_Name_1 := Pname;
10091                      Error_Msg_N
10092                        ("first formal of % function must be a named access" &
10093                         " type",
10094                         Parameter_Type (Parent (This_Formal)));
10095
10096                   elsif Atree.Convention
10097                          (Designated_Type (Etype (This_Formal))) /= Convention
10098                   then
10099                      Error_Msg_Name_1 := Pname;
10100
10101                      if Convention = Convention_Java then
10102                         Error_Msg_N
10103                           ("pragma% requires convention 'Cil in designated" &
10104                            " type",
10105                            Parameter_Type (Parent (This_Formal)));
10106                      else
10107                         Error_Msg_N
10108                           ("pragma% requires convention 'Java in designated" &
10109                            " type",
10110                            Parameter_Type (Parent (This_Formal)));
10111                      end if;
10112
10113                   elsif No (Expression (Parent (This_Formal)))
10114                     or else Nkind (Expression (Parent (This_Formal))) /= N_Null
10115                   then
10116                      Error_Msg_Name_1 := Pname;
10117                      Error_Msg_N
10118                        ("pragma% requires first formal with default `null`",
10119                         Parameter_Type (Parent (This_Formal)));
10120                   end if;
10121                end if;
10122
10123                --  Check result type: the constructor must be a function
10124                --  returning:
10125                --   * a value type (only allowed in the CIL compiler)
10126                --   * an access-to-subprogram type with convention Java/CIL
10127                --   * an access-type designating a type that has convention
10128                --     Java/CIL.
10129
10130                if Is_Value_Type (Etype (Def_Id)) then
10131                   null;
10132
10133                --  Access-to-subprogram type with convention Java/CIL
10134
10135                elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type then
10136                   if Atree.Convention (Etype (Def_Id)) /= Convention then
10137                      if Convention = Convention_Java then
10138                         Error_Pragma_Arg
10139                           ("pragma% requires function returning a " &
10140                            "'Java access type", Arg1);
10141                      else
10142                         pragma Assert (Convention = Convention_CIL);
10143                         Error_Pragma_Arg
10144                           ("pragma% requires function returning a " &
10145                            "'C'I'L access type", Arg1);
10146                      end if;
10147                   end if;
10148
10149                elsif Ekind (Etype (Def_Id)) in Access_Kind then
10150                   if not Ekind_In (Etype (Def_Id), E_Access_Type,
10151                                                    E_General_Access_Type)
10152                     or else
10153                       Atree.Convention
10154                         (Designated_Type (Etype (Def_Id))) /= Convention
10155                   then
10156                      Error_Msg_Name_1 := Pname;
10157
10158                      if Convention = Convention_Java then
10159                         Error_Pragma_Arg
10160                           ("pragma% requires function returning a named" &
10161                            "'Java access type", Arg1);
10162                      else
10163                         Error_Pragma_Arg
10164                           ("pragma% requires function returning a named" &
10165                            "'C'I'L access type", Arg1);
10166                      end if;
10167                   end if;
10168                end if;
10169
10170                Set_Is_Constructor (Def_Id);
10171                Set_Convention     (Def_Id, Convention);
10172                Set_Is_Imported    (Def_Id);
10173
10174                exit when From_Aspect_Specification (N);
10175                Hom_Id := Homonym (Hom_Id);
10176
10177                exit when No (Hom_Id) or else Scope (Hom_Id) /= Current_Scope;
10178             end loop;
10179          end Java_Constructor;
10180
10181          ----------------------
10182          -- Java_Interface --
10183          ----------------------
10184
10185          --  pragma Java_Interface ([Entity =>] LOCAL_NAME);
10186
10187          when Pragma_Java_Interface => Java_Interface : declare
10188             Arg : Node_Id;
10189             Typ : Entity_Id;
10190
10191          begin
10192             GNAT_Pragma;
10193             Check_Arg_Count (1);
10194             Check_Optional_Identifier (Arg1, Name_Entity);
10195             Check_Arg_Is_Local_Name (Arg1);
10196
10197             Arg := Get_Pragma_Arg (Arg1);
10198             Analyze (Arg);
10199
10200             if Etype (Arg) = Any_Type then
10201                return;
10202             end if;
10203
10204             if not Is_Entity_Name (Arg)
10205               or else not Is_Type (Entity (Arg))
10206             then
10207                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
10208             end if;
10209
10210             Typ := Underlying_Type (Entity (Arg));
10211
10212             --  For now simply check some of the semantic constraints on the
10213             --  type. This currently leaves out some restrictions on interface
10214             --  types, namely that the parent type must be java.lang.Object.Typ
10215             --  and that all primitives of the type should be declared
10216             --  abstract. ???
10217
10218             if not Is_Tagged_Type (Typ) or else not Is_Abstract_Type (Typ) then
10219                Error_Pragma_Arg ("pragma% requires an abstract "
10220                  & "tagged type", Arg1);
10221
10222             elsif not Has_Discriminants (Typ)
10223               or else Ekind (Etype (First_Discriminant (Typ)))
10224                         /= E_Anonymous_Access_Type
10225               or else
10226                 not Is_Class_Wide_Type
10227                       (Designated_Type (Etype (First_Discriminant (Typ))))
10228             then
10229                Error_Pragma_Arg
10230                  ("type must have a class-wide access discriminant", Arg1);
10231             end if;
10232          end Java_Interface;
10233
10234          ----------------
10235          -- Keep_Names --
10236          ----------------
10237
10238          --  pragma Keep_Names ([On => ] local_NAME);
10239
10240          when Pragma_Keep_Names => Keep_Names : declare
10241             Arg : Node_Id;
10242
10243          begin
10244             GNAT_Pragma;
10245             Check_Arg_Count (1);
10246             Check_Optional_Identifier (Arg1, Name_On);
10247             Check_Arg_Is_Local_Name (Arg1);
10248
10249             Arg := Get_Pragma_Arg (Arg1);
10250             Analyze (Arg);
10251
10252             if Etype (Arg) = Any_Type then
10253                return;
10254             end if;
10255
10256             if not Is_Entity_Name (Arg)
10257               or else Ekind (Entity (Arg)) /= E_Enumeration_Type
10258             then
10259                Error_Pragma_Arg
10260                  ("pragma% requires a local enumeration type", Arg1);
10261             end if;
10262
10263             Set_Discard_Names (Entity (Arg), False);
10264          end Keep_Names;
10265
10266          -------------
10267          -- License --
10268          -------------
10269
10270          --  pragma License (RESTRICTED | UNRESTRICTED | GPL | MODIFIED_GPL);
10271
10272          when Pragma_License =>
10273             GNAT_Pragma;
10274             Check_Arg_Count (1);
10275             Check_No_Identifiers;
10276             Check_Valid_Configuration_Pragma;
10277             Check_Arg_Is_Identifier (Arg1);
10278
10279             declare
10280                Sind : constant Source_File_Index :=
10281                         Source_Index (Current_Sem_Unit);
10282
10283             begin
10284                case Chars (Get_Pragma_Arg (Arg1)) is
10285                   when Name_GPL =>
10286                      Set_License (Sind, GPL);
10287
10288                   when Name_Modified_GPL =>
10289                      Set_License (Sind, Modified_GPL);
10290
10291                   when Name_Restricted =>
10292                      Set_License (Sind, Restricted);
10293
10294                   when Name_Unrestricted =>
10295                      Set_License (Sind, Unrestricted);
10296
10297                   when others =>
10298                      Error_Pragma_Arg ("invalid license name", Arg1);
10299                end case;
10300             end;
10301
10302          ---------------
10303          -- Link_With --
10304          ---------------
10305
10306          --  pragma Link_With (string_EXPRESSION {, string_EXPRESSION});
10307
10308          when Pragma_Link_With => Link_With : declare
10309             Arg : Node_Id;
10310
10311          begin
10312             GNAT_Pragma;
10313
10314             if Operating_Mode = Generate_Code
10315               and then In_Extended_Main_Source_Unit (N)
10316             then
10317                Check_At_Least_N_Arguments (1);
10318                Check_No_Identifiers;
10319                Check_Is_In_Decl_Part_Or_Package_Spec;
10320                Check_Arg_Is_Static_Expression (Arg1, Standard_String);
10321                Start_String;
10322
10323                Arg := Arg1;
10324                while Present (Arg) loop
10325                   Check_Arg_Is_Static_Expression (Arg, Standard_String);
10326
10327                   --  Store argument, converting sequences of spaces to a
10328                   --  single null character (this is one of the differences
10329                   --  in processing between Link_With and Linker_Options).
10330
10331                   Arg_Store : declare
10332                      C : constant Char_Code := Get_Char_Code (' ');
10333                      S : constant String_Id :=
10334                            Strval (Expr_Value_S (Get_Pragma_Arg (Arg)));
10335                      L : constant Nat := String_Length (S);
10336                      F : Nat := 1;
10337
10338                      procedure Skip_Spaces;
10339                      --  Advance F past any spaces
10340
10341                      -----------------
10342                      -- Skip_Spaces --
10343                      -----------------
10344
10345                      procedure Skip_Spaces is
10346                      begin
10347                         while F <= L and then Get_String_Char (S, F) = C loop
10348                            F := F + 1;
10349                         end loop;
10350                      end Skip_Spaces;
10351
10352                   --  Start of processing for Arg_Store
10353
10354                   begin
10355                      Skip_Spaces; -- skip leading spaces
10356
10357                      --  Loop through characters, changing any embedded
10358                      --  sequence of spaces to a single null character (this
10359                      --  is how Link_With/Linker_Options differ)
10360
10361                      while F <= L loop
10362                         if Get_String_Char (S, F) = C then
10363                            Skip_Spaces;
10364                            exit when F > L;
10365                            Store_String_Char (ASCII.NUL);
10366
10367                         else
10368                            Store_String_Char (Get_String_Char (S, F));
10369                            F := F + 1;
10370                         end if;
10371                      end loop;
10372                   end Arg_Store;
10373
10374                   Arg := Next (Arg);
10375
10376                   if Present (Arg) then
10377                      Store_String_Char (ASCII.NUL);
10378                   end if;
10379                end loop;
10380
10381                Store_Linker_Option_String (End_String);
10382             end if;
10383          end Link_With;
10384
10385          ------------------
10386          -- Linker_Alias --
10387          ------------------
10388
10389          --  pragma Linker_Alias (
10390          --      [Entity =>]  LOCAL_NAME
10391          --      [Target =>]  static_string_EXPRESSION);
10392
10393          when Pragma_Linker_Alias =>
10394             GNAT_Pragma;
10395             Check_Arg_Order ((Name_Entity, Name_Target));
10396             Check_Arg_Count (2);
10397             Check_Optional_Identifier (Arg1, Name_Entity);
10398             Check_Optional_Identifier (Arg2, Name_Target);
10399             Check_Arg_Is_Library_Level_Local_Name (Arg1);
10400             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10401
10402             --  The only processing required is to link this item on to the
10403             --  list of rep items for the given entity. This is accomplished
10404             --  by the call to Rep_Item_Too_Late (when no error is detected
10405             --  and False is returned).
10406
10407             if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
10408                return;
10409             else
10410                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10411             end if;
10412
10413          ------------------------
10414          -- Linker_Constructor --
10415          ------------------------
10416
10417          --  pragma Linker_Constructor (procedure_LOCAL_NAME);
10418
10419          --  Code is shared with Linker_Destructor
10420
10421          -----------------------
10422          -- Linker_Destructor --
10423          -----------------------
10424
10425          --  pragma Linker_Destructor (procedure_LOCAL_NAME);
10426
10427          when Pragma_Linker_Constructor |
10428               Pragma_Linker_Destructor =>
10429          Linker_Constructor : declare
10430             Arg1_X : Node_Id;
10431             Proc   : Entity_Id;
10432
10433          begin
10434             GNAT_Pragma;
10435             Check_Arg_Count (1);
10436             Check_No_Identifiers;
10437             Check_Arg_Is_Local_Name (Arg1);
10438             Arg1_X := Get_Pragma_Arg (Arg1);
10439             Analyze (Arg1_X);
10440             Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
10441
10442             if not Is_Library_Level_Entity (Proc) then
10443                Error_Pragma_Arg
10444                 ("argument for pragma% must be library level entity", Arg1);
10445             end if;
10446
10447             --  The only processing required is to link this item on to the
10448             --  list of rep items for the given entity. This is accomplished
10449             --  by the call to Rep_Item_Too_Late (when no error is detected
10450             --  and False is returned).
10451
10452             if Rep_Item_Too_Late (Proc, N) then
10453                return;
10454             else
10455                Set_Has_Gigi_Rep_Item (Proc);
10456             end if;
10457          end Linker_Constructor;
10458
10459          --------------------
10460          -- Linker_Options --
10461          --------------------
10462
10463          --  pragma Linker_Options (string_EXPRESSION {, string_EXPRESSION});
10464
10465          when Pragma_Linker_Options => Linker_Options : declare
10466             Arg : Node_Id;
10467
10468          begin
10469             Check_Ada_83_Warning;
10470             Check_No_Identifiers;
10471             Check_Arg_Count (1);
10472             Check_Is_In_Decl_Part_Or_Package_Spec;
10473             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
10474             Start_String (Strval (Expr_Value_S (Get_Pragma_Arg (Arg1))));
10475
10476             Arg := Arg2;
10477             while Present (Arg) loop
10478                Check_Arg_Is_Static_Expression (Arg, Standard_String);
10479                Store_String_Char (ASCII.NUL);
10480                Store_String_Chars
10481                  (Strval (Expr_Value_S (Get_Pragma_Arg (Arg))));
10482                Arg := Next (Arg);
10483             end loop;
10484
10485             if Operating_Mode = Generate_Code
10486               and then In_Extended_Main_Source_Unit (N)
10487             then
10488                Store_Linker_Option_String (End_String);
10489             end if;
10490          end Linker_Options;
10491
10492          --------------------
10493          -- Linker_Section --
10494          --------------------
10495
10496          --  pragma Linker_Section (
10497          --      [Entity  =>]  LOCAL_NAME
10498          --      [Section =>]  static_string_EXPRESSION);
10499
10500          when Pragma_Linker_Section =>
10501             GNAT_Pragma;
10502             Check_Arg_Order ((Name_Entity, Name_Section));
10503             Check_Arg_Count (2);
10504             Check_Optional_Identifier (Arg1, Name_Entity);
10505             Check_Optional_Identifier (Arg2, Name_Section);
10506             Check_Arg_Is_Library_Level_Local_Name (Arg1);
10507             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10508
10509             --  This pragma applies only to objects
10510
10511             if not Is_Object (Entity (Get_Pragma_Arg (Arg1))) then
10512                Error_Pragma_Arg ("pragma% applies only to objects", Arg1);
10513             end if;
10514
10515             --  The only processing required is to link this item on to the
10516             --  list of rep items for the given entity. This is accomplished
10517             --  by the call to Rep_Item_Too_Late (when no error is detected
10518             --  and False is returned).
10519
10520             if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
10521                return;
10522             else
10523                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10524             end if;
10525
10526          ----------
10527          -- List --
10528          ----------
10529
10530          --  pragma List (On | Off)
10531
10532          --  There is nothing to do here, since we did all the processing for
10533          --  this pragma in Par.Prag (so that it works properly even in syntax
10534          --  only mode).
10535
10536          when Pragma_List =>
10537             null;
10538
10539          --------------------
10540          -- Locking_Policy --
10541          --------------------
10542
10543          --  pragma Locking_Policy (policy_IDENTIFIER);
10544
10545          when Pragma_Locking_Policy => declare
10546             LP : Character;
10547
10548          begin
10549             Check_Ada_83_Warning;
10550             Check_Arg_Count (1);
10551             Check_No_Identifiers;
10552             Check_Arg_Is_Locking_Policy (Arg1);
10553             Check_Valid_Configuration_Pragma;
10554             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
10555             LP := Fold_Upper (Name_Buffer (1));
10556
10557             if Locking_Policy /= ' '
10558               and then Locking_Policy /= LP
10559             then
10560                Error_Msg_Sloc := Locking_Policy_Sloc;
10561                Error_Pragma ("locking policy incompatible with policy#");
10562
10563             --  Set new policy, but always preserve System_Location since we
10564             --  like the error message with the run time name.
10565
10566             else
10567                Locking_Policy := LP;
10568
10569                if Locking_Policy_Sloc /= System_Location then
10570                   Locking_Policy_Sloc := Loc;
10571                end if;
10572             end if;
10573          end;
10574
10575          ----------------
10576          -- Long_Float --
10577          ----------------
10578
10579          --  pragma Long_Float (D_Float | G_Float);
10580
10581          when Pragma_Long_Float =>
10582             GNAT_Pragma;
10583             Check_Valid_Configuration_Pragma;
10584             Check_Arg_Count (1);
10585             Check_No_Identifier (Arg1);
10586             Check_Arg_Is_One_Of (Arg1, Name_D_Float, Name_G_Float);
10587
10588             if not OpenVMS_On_Target then
10589                Error_Pragma ("?pragma% ignored (applies only to Open'V'M'S)");
10590             end if;
10591
10592             --  D_Float case
10593
10594             if Chars (Get_Pragma_Arg (Arg1)) = Name_D_Float then
10595                if Opt.Float_Format_Long = 'G' then
10596                   Error_Pragma ("G_Float previously specified");
10597                end if;
10598
10599                Opt.Float_Format_Long := 'D';
10600
10601             --  G_Float case (this is the default, does not need overriding)
10602
10603             else
10604                if Opt.Float_Format_Long = 'D' then
10605                   Error_Pragma ("D_Float previously specified");
10606                end if;
10607
10608                Opt.Float_Format_Long := 'G';
10609             end if;
10610
10611             Set_Standard_Fpt_Formats;
10612
10613          -----------------------
10614          -- Machine_Attribute --
10615          -----------------------
10616
10617          --  pragma Machine_Attribute (
10618          --       [Entity         =>] LOCAL_NAME,
10619          --       [Attribute_Name =>] static_string_EXPRESSION
10620          --    [, [Info           =>] static_EXPRESSION] );
10621
10622          when Pragma_Machine_Attribute => Machine_Attribute : declare
10623             Def_Id : Entity_Id;
10624
10625          begin
10626             GNAT_Pragma;
10627             Check_Arg_Order ((Name_Entity, Name_Attribute_Name, Name_Info));
10628
10629             if Arg_Count = 3 then
10630                Check_Optional_Identifier (Arg3, Name_Info);
10631                Check_Arg_Is_Static_Expression (Arg3);
10632             else
10633                Check_Arg_Count (2);
10634             end if;
10635
10636             Check_Optional_Identifier (Arg1, Name_Entity);
10637             Check_Optional_Identifier (Arg2, Name_Attribute_Name);
10638             Check_Arg_Is_Local_Name (Arg1);
10639             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10640             Def_Id := Entity (Get_Pragma_Arg (Arg1));
10641
10642             if Is_Access_Type (Def_Id) then
10643                Def_Id := Designated_Type (Def_Id);
10644             end if;
10645
10646             if Rep_Item_Too_Early (Def_Id, N) then
10647                return;
10648             end if;
10649
10650             Def_Id := Underlying_Type (Def_Id);
10651
10652             --  The only processing required is to link this item on to the
10653             --  list of rep items for the given entity. This is accomplished
10654             --  by the call to Rep_Item_Too_Late (when no error is detected
10655             --  and False is returned).
10656
10657             if Rep_Item_Too_Late (Def_Id, N) then
10658                return;
10659             else
10660                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10661             end if;
10662          end Machine_Attribute;
10663
10664          ----------
10665          -- Main --
10666          ----------
10667
10668          --  pragma Main
10669          --   (MAIN_OPTION [, MAIN_OPTION]);
10670
10671          --  MAIN_OPTION ::=
10672          --    [STACK_SIZE              =>] static_integer_EXPRESSION
10673          --  | [TASK_STACK_SIZE_DEFAULT =>] static_integer_EXPRESSION
10674          --  | [TIME_SLICING_ENABLED    =>] static_boolean_EXPRESSION
10675
10676          when Pragma_Main => Main : declare
10677             Args  : Args_List (1 .. 3);
10678             Names : constant Name_List (1 .. 3) := (
10679                       Name_Stack_Size,
10680                       Name_Task_Stack_Size_Default,
10681                       Name_Time_Slicing_Enabled);
10682
10683             Nod : Node_Id;
10684
10685          begin
10686             GNAT_Pragma;
10687             Gather_Associations (Names, Args);
10688
10689             for J in 1 .. 2 loop
10690                if Present (Args (J)) then
10691                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
10692                end if;
10693             end loop;
10694
10695             if Present (Args (3)) then
10696                Check_Arg_Is_Static_Expression (Args (3), Standard_Boolean);
10697             end if;
10698
10699             Nod := Next (N);
10700             while Present (Nod) loop
10701                if Nkind (Nod) = N_Pragma
10702                  and then Pragma_Name (Nod) = Name_Main
10703                then
10704                   Error_Msg_Name_1 := Pname;
10705                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
10706                end if;
10707
10708                Next (Nod);
10709             end loop;
10710          end Main;
10711
10712          ------------------
10713          -- Main_Storage --
10714          ------------------
10715
10716          --  pragma Main_Storage
10717          --   (MAIN_STORAGE_OPTION [, MAIN_STORAGE_OPTION]);
10718
10719          --  MAIN_STORAGE_OPTION ::=
10720          --    [WORKING_STORAGE =>] static_SIMPLE_EXPRESSION
10721          --  | [TOP_GUARD =>] static_SIMPLE_EXPRESSION
10722
10723          when Pragma_Main_Storage => Main_Storage : declare
10724             Args  : Args_List (1 .. 2);
10725             Names : constant Name_List (1 .. 2) := (
10726                       Name_Working_Storage,
10727                       Name_Top_Guard);
10728
10729             Nod : Node_Id;
10730
10731          begin
10732             GNAT_Pragma;
10733             Gather_Associations (Names, Args);
10734
10735             for J in 1 .. 2 loop
10736                if Present (Args (J)) then
10737                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
10738                end if;
10739             end loop;
10740
10741             Check_In_Main_Program;
10742
10743             Nod := Next (N);
10744             while Present (Nod) loop
10745                if Nkind (Nod) = N_Pragma
10746                  and then Pragma_Name (Nod) = Name_Main_Storage
10747                then
10748                   Error_Msg_Name_1 := Pname;
10749                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
10750                end if;
10751
10752                Next (Nod);
10753             end loop;
10754          end Main_Storage;
10755
10756          -----------------
10757          -- Memory_Size --
10758          -----------------
10759
10760          --  pragma Memory_Size (NUMERIC_LITERAL)
10761
10762          when Pragma_Memory_Size =>
10763             GNAT_Pragma;
10764
10765             --  Memory size is simply ignored
10766
10767             Check_No_Identifiers;
10768             Check_Arg_Count (1);
10769             Check_Arg_Is_Integer_Literal (Arg1);
10770
10771          -------------
10772          -- No_Body --
10773          -------------
10774
10775          --  pragma No_Body;
10776
10777          --  The only correct use of this pragma is on its own in a file, in
10778          --  which case it is specially processed (see Gnat1drv.Check_Bad_Body
10779          --  and Frontend, which use Sinput.L.Source_File_Is_Pragma_No_Body to
10780          --  check for a file containing nothing but a No_Body pragma). If we
10781          --  attempt to process it during normal semantics processing, it means
10782          --  it was misplaced.
10783
10784          when Pragma_No_Body =>
10785             GNAT_Pragma;
10786             Pragma_Misplaced;
10787
10788          ---------------
10789          -- No_Return --
10790          ---------------
10791
10792          --  pragma No_Return (procedure_LOCAL_NAME {, procedure_Local_Name});
10793
10794          when Pragma_No_Return => No_Return : declare
10795             Id    : Node_Id;
10796             E     : Entity_Id;
10797             Found : Boolean;
10798             Arg   : Node_Id;
10799
10800          begin
10801             Ada_2005_Pragma;
10802             Check_At_Least_N_Arguments (1);
10803
10804             --  Loop through arguments of pragma
10805
10806             Arg := Arg1;
10807             while Present (Arg) loop
10808                Check_Arg_Is_Local_Name (Arg);
10809                Id := Get_Pragma_Arg (Arg);
10810                Analyze (Id);
10811
10812                if not Is_Entity_Name (Id) then
10813                   Error_Pragma_Arg ("entity name required", Arg);
10814                end if;
10815
10816                if Etype (Id) = Any_Type then
10817                   raise Pragma_Exit;
10818                end if;
10819
10820                --  Loop to find matching procedures
10821
10822                E := Entity (Id);
10823                Found := False;
10824                while Present (E)
10825                  and then Scope (E) = Current_Scope
10826                loop
10827                   if Ekind_In (E, E_Procedure, E_Generic_Procedure) then
10828                      Set_No_Return (E);
10829
10830                      --  Set flag on any alias as well
10831
10832                      if Is_Overloadable (E) and then Present (Alias (E)) then
10833                         Set_No_Return (Alias (E));
10834                      end if;
10835
10836                      Found := True;
10837                   end if;
10838
10839                   exit when From_Aspect_Specification (N);
10840                   E := Homonym (E);
10841                end loop;
10842
10843                if not Found then
10844                   Error_Pragma_Arg ("no procedure & found for pragma%", Arg);
10845                end if;
10846
10847                Next (Arg);
10848             end loop;
10849          end No_Return;
10850
10851          -----------------
10852          -- No_Run_Time --
10853          -----------------
10854
10855          --  pragma No_Run_Time;
10856
10857          --  Note: this pragma is retained for backwards compatibility. See
10858          --  body of Rtsfind for full details on its handling.
10859
10860          when Pragma_No_Run_Time =>
10861             GNAT_Pragma;
10862             Check_Valid_Configuration_Pragma;
10863             Check_Arg_Count (0);
10864
10865             No_Run_Time_Mode           := True;
10866             Configurable_Run_Time_Mode := True;
10867
10868             --  Set Duration to 32 bits if word size is 32
10869
10870             if Ttypes.System_Word_Size = 32 then
10871                Duration_32_Bits_On_Target := True;
10872             end if;
10873
10874             --  Set appropriate restrictions
10875
10876             Set_Restriction (No_Finalization, N);
10877             Set_Restriction (No_Exception_Handlers, N);
10878             Set_Restriction (Max_Tasks, N, 0);
10879             Set_Restriction (No_Tasking, N);
10880
10881          ------------------------
10882          -- No_Strict_Aliasing --
10883          ------------------------
10884
10885          --  pragma No_Strict_Aliasing [([Entity =>] type_LOCAL_NAME)];
10886
10887          when Pragma_No_Strict_Aliasing => No_Strict_Aliasing : declare
10888             E_Id : Entity_Id;
10889
10890          begin
10891             GNAT_Pragma;
10892             Check_At_Most_N_Arguments (1);
10893
10894             if Arg_Count = 0 then
10895                Check_Valid_Configuration_Pragma;
10896                Opt.No_Strict_Aliasing := True;
10897
10898             else
10899                Check_Optional_Identifier (Arg2, Name_Entity);
10900                Check_Arg_Is_Local_Name (Arg1);
10901                E_Id := Entity (Get_Pragma_Arg (Arg1));
10902
10903                if E_Id = Any_Type then
10904                   return;
10905                elsif No (E_Id) or else not Is_Access_Type (E_Id) then
10906                   Error_Pragma_Arg ("pragma% requires access type", Arg1);
10907                end if;
10908
10909                Set_No_Strict_Aliasing (Implementation_Base_Type (E_Id));
10910             end if;
10911          end No_Strict_Aliasing;
10912
10913          -----------------------
10914          -- Normalize_Scalars --
10915          -----------------------
10916
10917          --  pragma Normalize_Scalars;
10918
10919          when Pragma_Normalize_Scalars =>
10920             Check_Ada_83_Warning;
10921             Check_Arg_Count (0);
10922             Check_Valid_Configuration_Pragma;
10923
10924             --  Normalize_Scalars creates false positives in CodePeer, and
10925             --  incorrect negative results in ALFA mode, so ignore this pragma
10926             --  in these modes.
10927
10928             if not (CodePeer_Mode or ALFA_Mode) then
10929                Normalize_Scalars := True;
10930                Init_Or_Norm_Scalars := True;
10931             end if;
10932
10933          -----------------
10934          -- Obsolescent --
10935          -----------------
10936
10937          --  pragma Obsolescent;
10938
10939          --  pragma Obsolescent (
10940          --    [Message =>] static_string_EXPRESSION
10941          --  [,[Version =>] Ada_05]]);
10942
10943          --  pragma Obsolescent (
10944          --    [Entity  =>] NAME
10945          --  [,[Message =>] static_string_EXPRESSION
10946          --  [,[Version =>] Ada_05]] );
10947
10948          when Pragma_Obsolescent => Obsolescent : declare
10949             Ename : Node_Id;
10950             Decl  : Node_Id;
10951
10952             procedure Set_Obsolescent (E : Entity_Id);
10953             --  Given an entity Ent, mark it as obsolescent if appropriate
10954
10955             ---------------------
10956             -- Set_Obsolescent --
10957             ---------------------
10958
10959             procedure Set_Obsolescent (E : Entity_Id) is
10960                Active : Boolean;
10961                Ent    : Entity_Id;
10962                S      : String_Id;
10963
10964             begin
10965                Active := True;
10966                Ent    := E;
10967
10968                --  Entity name was given
10969
10970                if Present (Ename) then
10971
10972                   --  If entity name matches, we are fine. Save entity in
10973                   --  pragma argument, for ASIS use.
10974
10975                   if Chars (Ename) = Chars (Ent) then
10976                      Set_Entity (Ename, Ent);
10977                      Generate_Reference (Ent, Ename);
10978
10979                   --  If entity name does not match, only possibility is an
10980                   --  enumeration literal from an enumeration type declaration.
10981
10982                   elsif Ekind (Ent) /= E_Enumeration_Type then
10983                      Error_Pragma
10984                        ("pragma % entity name does not match declaration");
10985
10986                   else
10987                      Ent := First_Literal (E);
10988                      loop
10989                         if No (Ent) then
10990                            Error_Pragma
10991                              ("pragma % entity name does not match any " &
10992                               "enumeration literal");
10993
10994                         elsif Chars (Ent) = Chars (Ename) then
10995                            Set_Entity (Ename, Ent);
10996                            Generate_Reference (Ent, Ename);
10997                            exit;
10998
10999                         else
11000                            Ent := Next_Literal (Ent);
11001                         end if;
11002                      end loop;
11003                   end if;
11004                end if;
11005
11006                --  Ent points to entity to be marked
11007
11008                if Arg_Count >= 1 then
11009
11010                   --  Deal with static string argument
11011
11012                   Check_Arg_Is_Static_Expression (Arg1, Standard_String);
11013                   S := Strval (Get_Pragma_Arg (Arg1));
11014
11015                   for J in 1 .. String_Length (S) loop
11016                      if not In_Character_Range (Get_String_Char (S, J)) then
11017                         Error_Pragma_Arg
11018                           ("pragma% argument does not allow wide characters",
11019                            Arg1);
11020                      end if;
11021                   end loop;
11022
11023                   Obsolescent_Warnings.Append
11024                     ((Ent => Ent, Msg => Strval (Get_Pragma_Arg (Arg1))));
11025
11026                   --  Check for Ada_05 parameter
11027
11028                   if Arg_Count /= 1 then
11029                      Check_Arg_Count (2);
11030
11031                      declare
11032                         Argx : constant Node_Id := Get_Pragma_Arg (Arg2);
11033
11034                      begin
11035                         Check_Arg_Is_Identifier (Argx);
11036
11037                         if Chars (Argx) /= Name_Ada_05 then
11038                            Error_Msg_Name_2 := Name_Ada_05;
11039                            Error_Pragma_Arg
11040                              ("only allowed argument for pragma% is %", Argx);
11041                         end if;
11042
11043                         if Ada_Version_Explicit < Ada_2005
11044                           or else not Warn_On_Ada_2005_Compatibility
11045                         then
11046                            Active := False;
11047                         end if;
11048                      end;
11049                   end if;
11050                end if;
11051
11052                --  Set flag if pragma active
11053
11054                if Active then
11055                   Set_Is_Obsolescent (Ent);
11056                end if;
11057
11058                return;
11059             end Set_Obsolescent;
11060
11061          --  Start of processing for pragma Obsolescent
11062
11063          begin
11064             GNAT_Pragma;
11065
11066             Check_At_Most_N_Arguments (3);
11067
11068             --  See if first argument specifies an entity name
11069
11070             if Arg_Count >= 1
11071               and then
11072                 (Chars (Arg1) = Name_Entity
11073                    or else
11074                      Nkind_In (Get_Pragma_Arg (Arg1), N_Character_Literal,
11075                                                       N_Identifier,
11076                                                       N_Operator_Symbol))
11077             then
11078                Ename := Get_Pragma_Arg (Arg1);
11079
11080                --  Eliminate first argument, so we can share processing
11081
11082                Arg1 := Arg2;
11083                Arg2 := Arg3;
11084                Arg_Count := Arg_Count - 1;
11085
11086             --  No Entity name argument given
11087
11088             else
11089                Ename := Empty;
11090             end if;
11091
11092             if Arg_Count >= 1 then
11093                Check_Optional_Identifier (Arg1, Name_Message);
11094
11095                if Arg_Count = 2 then
11096                   Check_Optional_Identifier (Arg2, Name_Version);
11097                end if;
11098             end if;
11099
11100             --  Get immediately preceding declaration
11101
11102             Decl := Prev (N);
11103             while Present (Decl) and then Nkind (Decl) = N_Pragma loop
11104                Prev (Decl);
11105             end loop;
11106
11107             --  Cases where we do not follow anything other than another pragma
11108
11109             if No (Decl) then
11110
11111                --  First case: library level compilation unit declaration with
11112                --  the pragma immediately following the declaration.
11113
11114                if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
11115                   Set_Obsolescent
11116                     (Defining_Entity (Unit (Parent (Parent (N)))));
11117                   return;
11118
11119                --  Case 2: library unit placement for package
11120
11121                else
11122                   declare
11123                      Ent : constant Entity_Id := Find_Lib_Unit_Name;
11124                   begin
11125                      if Is_Package_Or_Generic_Package (Ent) then
11126                         Set_Obsolescent (Ent);
11127                         return;
11128                      end if;
11129                   end;
11130                end if;
11131
11132             --  Cases where we must follow a declaration
11133
11134             else
11135                if         Nkind (Decl) not in N_Declaration
11136                  and then Nkind (Decl) not in N_Later_Decl_Item
11137                  and then Nkind (Decl) not in N_Generic_Declaration
11138                  and then Nkind (Decl) not in N_Renaming_Declaration
11139                then
11140                   Error_Pragma
11141                     ("pragma% misplaced, "
11142                      & "must immediately follow a declaration");
11143
11144                else
11145                   Set_Obsolescent (Defining_Entity (Decl));
11146                   return;
11147                end if;
11148             end if;
11149          end Obsolescent;
11150
11151          --------------
11152          -- Optimize --
11153          --------------
11154
11155          --  pragma Optimize (Time | Space | Off);
11156
11157          --  The actual check for optimize is done in Gigi. Note that this
11158          --  pragma does not actually change the optimization setting, it
11159          --  simply checks that it is consistent with the pragma.
11160
11161          when Pragma_Optimize =>
11162             Check_No_Identifiers;
11163             Check_Arg_Count (1);
11164             Check_Arg_Is_One_Of (Arg1, Name_Time, Name_Space, Name_Off);
11165
11166          ------------------------
11167          -- Optimize_Alignment --
11168          ------------------------
11169
11170          --  pragma Optimize_Alignment (Time | Space | Off);
11171
11172          when Pragma_Optimize_Alignment => Optimize_Alignment : begin
11173             GNAT_Pragma;
11174             Check_No_Identifiers;
11175             Check_Arg_Count (1);
11176             Check_Valid_Configuration_Pragma;
11177
11178             declare
11179                Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
11180             begin
11181                case Nam is
11182                   when Name_Time =>
11183                      Opt.Optimize_Alignment := 'T';
11184                   when Name_Space =>
11185                      Opt.Optimize_Alignment := 'S';
11186                   when Name_Off =>
11187                      Opt.Optimize_Alignment := 'O';
11188                   when others =>
11189                      Error_Pragma_Arg ("invalid argument for pragma%", Arg1);
11190                end case;
11191             end;
11192
11193             --  Set indication that mode is set locally. If we are in fact in a
11194             --  configuration pragma file, this setting is harmless since the
11195             --  switch will get reset anyway at the start of each unit.
11196
11197             Optimize_Alignment_Local := True;
11198          end Optimize_Alignment;
11199
11200          -------------
11201          -- Ordered --
11202          -------------
11203
11204          --  pragma Ordered (first_enumeration_subtype_LOCAL_NAME);
11205
11206          when Pragma_Ordered => Ordered : declare
11207             Assoc   : constant Node_Id := Arg1;
11208             Type_Id : Node_Id;
11209             Typ     : Entity_Id;
11210
11211          begin
11212             GNAT_Pragma;
11213             Check_No_Identifiers;
11214             Check_Arg_Count (1);
11215             Check_Arg_Is_Local_Name (Arg1);
11216
11217             Type_Id := Get_Pragma_Arg (Assoc);
11218             Find_Type (Type_Id);
11219             Typ := Entity (Type_Id);
11220
11221             if Typ = Any_Type then
11222                return;
11223             else
11224                Typ := Underlying_Type (Typ);
11225             end if;
11226
11227             if not Is_Enumeration_Type (Typ) then
11228                Error_Pragma ("pragma% must specify enumeration type");
11229             end if;
11230
11231             Check_First_Subtype (Arg1);
11232             Set_Has_Pragma_Ordered (Base_Type (Typ));
11233          end Ordered;
11234
11235          ----------
11236          -- Pack --
11237          ----------
11238
11239          --  pragma Pack (first_subtype_LOCAL_NAME);
11240
11241          when Pragma_Pack => Pack : declare
11242             Assoc   : constant Node_Id := Arg1;
11243             Type_Id : Node_Id;
11244             Typ     : Entity_Id;
11245             Ctyp    : Entity_Id;
11246             Ignore  : Boolean := False;
11247
11248          begin
11249             Check_No_Identifiers;
11250             Check_Arg_Count (1);
11251             Check_Arg_Is_Local_Name (Arg1);
11252
11253             Type_Id := Get_Pragma_Arg (Assoc);
11254             Find_Type (Type_Id);
11255             Typ := Entity (Type_Id);
11256
11257             if Typ = Any_Type
11258               or else Rep_Item_Too_Early (Typ, N)
11259             then
11260                return;
11261             else
11262                Typ := Underlying_Type (Typ);
11263             end if;
11264
11265             if not Is_Array_Type (Typ) and then not Is_Record_Type (Typ) then
11266                Error_Pragma ("pragma% must specify array or record type");
11267             end if;
11268
11269             Check_First_Subtype (Arg1);
11270             Check_Duplicate_Pragma (Typ);
11271
11272             --  Array type
11273
11274             if Is_Array_Type (Typ) then
11275                Ctyp := Component_Type (Typ);
11276
11277                --  Ignore pack that does nothing
11278
11279                if Known_Static_Esize (Ctyp)
11280                  and then Known_Static_RM_Size (Ctyp)
11281                  and then Esize (Ctyp) = RM_Size (Ctyp)
11282                  and then Addressable (Esize (Ctyp))
11283                then
11284                   Ignore := True;
11285                end if;
11286
11287                --  Process OK pragma Pack. Note that if there is a separate
11288                --  component clause present, the Pack will be cancelled. This
11289                --  processing is in Freeze.
11290
11291                if not Rep_Item_Too_Late (Typ, N) then
11292
11293                   --  In the context of static code analysis, we do not need
11294                   --  complex front-end expansions related to pragma Pack,
11295                   --  so disable handling of pragma Pack in these cases.
11296
11297                   if CodePeer_Mode or ALFA_Mode then
11298                      null;
11299
11300                   --  Don't attempt any packing for VM targets. We possibly
11301                   --  could deal with some cases of array bit-packing, but we
11302                   --  don't bother, since this is not a typical kind of
11303                   --  representation in the VM context anyway (and would not
11304                   --  for example work nicely with the debugger).
11305
11306                   elsif VM_Target /= No_VM then
11307                      if not GNAT_Mode then
11308                         Error_Pragma
11309                           ("?pragma% ignored in this configuration");
11310                      end if;
11311
11312                   --  Normal case where we do the pack action
11313
11314                   else
11315                      if not Ignore then
11316                         Set_Is_Packed            (Base_Type (Typ));
11317                         Set_Has_Non_Standard_Rep (Base_Type (Typ));
11318                      end if;
11319
11320                      Set_Has_Pragma_Pack (Base_Type (Typ));
11321                   end if;
11322                end if;
11323
11324             --  For record types, the pack is always effective
11325
11326             else pragma Assert (Is_Record_Type (Typ));
11327                if not Rep_Item_Too_Late (Typ, N) then
11328
11329                   --  Ignore pack request with warning in VM mode (skip warning
11330                   --  if we are compiling GNAT run time library).
11331
11332                   if VM_Target /= No_VM then
11333                      if not GNAT_Mode then
11334                         Error_Pragma
11335                           ("?pragma% ignored in this configuration");
11336                      end if;
11337
11338                   --  Normal case of pack request active
11339
11340                   else
11341                      Set_Is_Packed            (Base_Type (Typ));
11342                      Set_Has_Pragma_Pack      (Base_Type (Typ));
11343                      Set_Has_Non_Standard_Rep (Base_Type (Typ));
11344                   end if;
11345                end if;
11346             end if;
11347          end Pack;
11348
11349          ----------
11350          -- Page --
11351          ----------
11352
11353          --  pragma Page;
11354
11355          --  There is nothing to do here, since we did all the processing for
11356          --  this pragma in Par.Prag (so that it works properly even in syntax
11357          --  only mode).
11358
11359          when Pragma_Page =>
11360             null;
11361
11362          -------------
11363          -- Passive --
11364          -------------
11365
11366          --  pragma Passive [(PASSIVE_FORM)];
11367
11368          --  PASSIVE_FORM ::= Semaphore | No
11369
11370          when Pragma_Passive =>
11371             GNAT_Pragma;
11372
11373             if Nkind (Parent (N)) /= N_Task_Definition then
11374                Error_Pragma ("pragma% must be within task definition");
11375             end if;
11376
11377             if Arg_Count /= 0 then
11378                Check_Arg_Count (1);
11379                Check_Arg_Is_One_Of (Arg1, Name_Semaphore, Name_No);
11380             end if;
11381
11382          ----------------------------------
11383          -- Preelaborable_Initialization --
11384          ----------------------------------
11385
11386          --  pragma Preelaborable_Initialization (DIRECT_NAME);
11387
11388          when Pragma_Preelaborable_Initialization => Preelab_Init : declare
11389             Ent : Entity_Id;
11390
11391          begin
11392             Ada_2005_Pragma;
11393             Check_Arg_Count (1);
11394             Check_No_Identifiers;
11395             Check_Arg_Is_Identifier (Arg1);
11396             Check_Arg_Is_Local_Name (Arg1);
11397             Check_First_Subtype (Arg1);
11398             Ent := Entity (Get_Pragma_Arg (Arg1));
11399
11400             if not (Is_Private_Type (Ent)
11401                       or else
11402                     Is_Protected_Type (Ent)
11403                       or else
11404                     (Is_Generic_Type (Ent) and then Is_Derived_Type (Ent)))
11405             then
11406                Error_Pragma_Arg
11407                  ("pragma % can only be applied to private, formal derived or "
11408                   & "protected type",
11409                   Arg1);
11410             end if;
11411
11412             --  Give an error if the pragma is applied to a protected type that
11413             --  does not qualify (due to having entries, or due to components
11414             --  that do not qualify).
11415
11416             if Is_Protected_Type (Ent)
11417               and then not Has_Preelaborable_Initialization (Ent)
11418             then
11419                Error_Msg_N
11420                  ("protected type & does not have preelaborable " &
11421                   "initialization", Ent);
11422
11423             --  Otherwise mark the type as definitely having preelaborable
11424             --  initialization.
11425
11426             else
11427                Set_Known_To_Have_Preelab_Init (Ent);
11428             end if;
11429
11430             if Has_Pragma_Preelab_Init (Ent)
11431               and then Warn_On_Redundant_Constructs
11432             then
11433                Error_Pragma ("?duplicate pragma%!");
11434             else
11435                Set_Has_Pragma_Preelab_Init (Ent);
11436             end if;
11437          end Preelab_Init;
11438
11439          --------------------
11440          -- Persistent_BSS --
11441          --------------------
11442
11443          --  pragma Persistent_BSS [(object_NAME)];
11444
11445          when Pragma_Persistent_BSS => Persistent_BSS :  declare
11446             Decl : Node_Id;
11447             Ent  : Entity_Id;
11448             Prag : Node_Id;
11449
11450          begin
11451             GNAT_Pragma;
11452             Check_At_Most_N_Arguments (1);
11453
11454             --  Case of application to specific object (one argument)
11455
11456             if Arg_Count = 1 then
11457                Check_Arg_Is_Library_Level_Local_Name (Arg1);
11458
11459                if not Is_Entity_Name (Get_Pragma_Arg (Arg1))
11460                  or else not
11461                   Ekind_In (Entity (Get_Pragma_Arg (Arg1)), E_Variable,
11462                                                             E_Constant)
11463                then
11464                   Error_Pragma_Arg ("pragma% only applies to objects", Arg1);
11465                end if;
11466
11467                Ent := Entity (Get_Pragma_Arg (Arg1));
11468                Decl := Parent (Ent);
11469
11470                if Rep_Item_Too_Late (Ent, N) then
11471                   return;
11472                end if;
11473
11474                if Present (Expression (Decl)) then
11475                   Error_Pragma_Arg
11476                     ("object for pragma% cannot have initialization", Arg1);
11477                end if;
11478
11479                if not Is_Potentially_Persistent_Type (Etype (Ent)) then
11480                   Error_Pragma_Arg
11481                     ("object type for pragma% is not potentially persistent",
11482                      Arg1);
11483                end if;
11484
11485                Check_Duplicate_Pragma (Ent);
11486
11487                Prag :=
11488                  Make_Linker_Section_Pragma
11489                    (Ent, Sloc (N), ".persistent.bss");
11490                Insert_After (N, Prag);
11491                Analyze (Prag);
11492
11493             --  Case of use as configuration pragma with no arguments
11494
11495             else
11496                Check_Valid_Configuration_Pragma;
11497                Persistent_BSS_Mode := True;
11498             end if;
11499          end Persistent_BSS;
11500
11501          -------------
11502          -- Polling --
11503          -------------
11504
11505          --  pragma Polling (ON | OFF);
11506
11507          when Pragma_Polling =>
11508             GNAT_Pragma;
11509             Check_Arg_Count (1);
11510             Check_No_Identifiers;
11511             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
11512             Polling_Required := (Chars (Get_Pragma_Arg (Arg1)) = Name_On);
11513
11514          -------------------
11515          -- Postcondition --
11516          -------------------
11517
11518          --  pragma Postcondition ([Check   =>] Boolean_EXPRESSION
11519          --                      [,[Message =>] String_EXPRESSION]);
11520
11521          when Pragma_Postcondition => Postcondition : declare
11522             In_Body : Boolean;
11523             pragma Warnings (Off, In_Body);
11524
11525          begin
11526             GNAT_Pragma;
11527             Check_At_Least_N_Arguments (1);
11528             Check_At_Most_N_Arguments (2);
11529             Check_Optional_Identifier (Arg1, Name_Check);
11530
11531             --  All we need to do here is call the common check procedure,
11532             --  the remainder of the processing is found in Sem_Ch6/Sem_Ch7.
11533
11534             Check_Precondition_Postcondition (In_Body);
11535          end Postcondition;
11536
11537          ------------------
11538          -- Precondition --
11539          ------------------
11540
11541          --  pragma Precondition ([Check   =>] Boolean_EXPRESSION
11542          --                     [,[Message =>] String_EXPRESSION]);
11543
11544          when Pragma_Precondition => Precondition : declare
11545             In_Body : Boolean;
11546
11547          begin
11548             GNAT_Pragma;
11549             Check_At_Least_N_Arguments (1);
11550             Check_At_Most_N_Arguments (2);
11551             Check_Optional_Identifier (Arg1, Name_Check);
11552             Check_Precondition_Postcondition (In_Body);
11553
11554             --  If in spec, nothing more to do. If in body, then we convert the
11555             --  pragma to pragma Check (Precondition, cond [, msg]). Note we do
11556             --  this whether or not precondition checks are enabled. That works
11557             --  fine since pragma Check will do this check, and will also
11558             --  analyze the condition itself in the proper context.
11559
11560             if In_Body then
11561                Rewrite (N,
11562                  Make_Pragma (Loc,
11563                    Chars => Name_Check,
11564                    Pragma_Argument_Associations => New_List (
11565                      Make_Pragma_Argument_Association (Loc,
11566                        Expression => Make_Identifier (Loc, Name_Precondition)),
11567
11568                      Make_Pragma_Argument_Association (Sloc (Arg1),
11569                        Expression => Relocate_Node (Get_Pragma_Arg (Arg1))))));
11570
11571                if Arg_Count = 2 then
11572                   Append_To (Pragma_Argument_Associations (N),
11573                     Make_Pragma_Argument_Association (Sloc (Arg2),
11574                       Expression => Relocate_Node (Get_Pragma_Arg (Arg2))));
11575                end if;
11576
11577                Analyze (N);
11578             end if;
11579          end Precondition;
11580
11581          ---------------
11582          -- Predicate --
11583          ---------------
11584
11585          --  pragma Predicate
11586          --    ([Entity =>] type_LOCAL_NAME,
11587          --     [Check  =>] EXPRESSION);
11588
11589          when Pragma_Predicate => Predicate : declare
11590             Type_Id : Node_Id;
11591             Typ     : Entity_Id;
11592
11593             Discard : Boolean;
11594             pragma Unreferenced (Discard);
11595
11596          begin
11597             GNAT_Pragma;
11598             Check_Arg_Count (2);
11599             Check_Optional_Identifier (Arg1, Name_Entity);
11600             Check_Optional_Identifier (Arg2, Name_Check);
11601
11602             Check_Arg_Is_Local_Name (Arg1);
11603
11604             Type_Id := Get_Pragma_Arg (Arg1);
11605             Find_Type (Type_Id);
11606             Typ := Entity (Type_Id);
11607
11608             if Typ = Any_Type then
11609                return;
11610             end if;
11611
11612             --  The remaining processing is simply to link the pragma on to
11613             --  the rep item chain, for processing when the type is frozen.
11614             --  This is accomplished by a call to Rep_Item_Too_Late. We also
11615             --  mark the type as having predicates.
11616
11617             Set_Has_Predicates (Typ);
11618             Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
11619          end Predicate;
11620
11621          ------------------
11622          -- Preelaborate --
11623          ------------------
11624
11625          --  pragma Preelaborate [(library_unit_NAME)];
11626
11627          --  Set the flag Is_Preelaborated of program unit name entity
11628
11629          when Pragma_Preelaborate => Preelaborate : declare
11630             Pa  : constant Node_Id   := Parent (N);
11631             Pk  : constant Node_Kind := Nkind (Pa);
11632             Ent : Entity_Id;
11633
11634          begin
11635             Check_Ada_83_Warning;
11636             Check_Valid_Library_Unit_Pragma;
11637
11638             if Nkind (N) = N_Null_Statement then
11639                return;
11640             end if;
11641
11642             Ent := Find_Lib_Unit_Name;
11643             Check_Duplicate_Pragma (Ent);
11644
11645             --  This filters out pragmas inside generic parent then
11646             --  show up inside instantiation
11647
11648             if Present (Ent)
11649               and then not (Pk = N_Package_Specification
11650                              and then Present (Generic_Parent (Pa)))
11651             then
11652                if not Debug_Flag_U then
11653                   Set_Is_Preelaborated (Ent);
11654                   Set_Suppress_Elaboration_Warnings (Ent);
11655                end if;
11656             end if;
11657          end Preelaborate;
11658
11659          ---------------------
11660          -- Preelaborate_05 --
11661          ---------------------
11662
11663          --  pragma Preelaborate_05 [(library_unit_NAME)];
11664
11665          --  This pragma is useable only in GNAT_Mode, where it is used like
11666          --  pragma Preelaborate but it is only effective in Ada 2005 mode
11667          --  (otherwise it is ignored). This is used to implement AI-362 which
11668          --  recategorizes some run-time packages in Ada 2005 mode.
11669
11670          when Pragma_Preelaborate_05 => Preelaborate_05 : declare
11671             Ent : Entity_Id;
11672
11673          begin
11674             GNAT_Pragma;
11675             Check_Valid_Library_Unit_Pragma;
11676
11677             if not GNAT_Mode then
11678                Error_Pragma ("pragma% only available in GNAT mode");
11679             end if;
11680
11681             if Nkind (N) = N_Null_Statement then
11682                return;
11683             end if;
11684
11685             --  This is one of the few cases where we need to test the value of
11686             --  Ada_Version_Explicit rather than Ada_Version (which is always
11687             --  set to Ada_2012 in a predefined unit), we need to know the
11688             --  explicit version set to know if this pragma is active.
11689
11690             if Ada_Version_Explicit >= Ada_2005 then
11691                Ent := Find_Lib_Unit_Name;
11692                Set_Is_Preelaborated (Ent);
11693                Set_Suppress_Elaboration_Warnings (Ent);
11694             end if;
11695          end Preelaborate_05;
11696
11697          --------------
11698          -- Priority --
11699          --------------
11700
11701          --  pragma Priority (EXPRESSION);
11702
11703          when Pragma_Priority => Priority : declare
11704             P   : constant Node_Id := Parent (N);
11705             Arg : Node_Id;
11706
11707          begin
11708             Check_No_Identifiers;
11709             Check_Arg_Count (1);
11710
11711             --  Subprogram case
11712
11713             if Nkind (P) = N_Subprogram_Body then
11714                Check_In_Main_Program;
11715
11716                Arg := Get_Pragma_Arg (Arg1);
11717                Analyze_And_Resolve (Arg, Standard_Integer);
11718
11719                --  Must be static
11720
11721                if not Is_Static_Expression (Arg) then
11722                   Flag_Non_Static_Expr
11723                     ("main subprogram priority is not static!", Arg);
11724                   raise Pragma_Exit;
11725
11726                --  If constraint error, then we already signalled an error
11727
11728                elsif Raises_Constraint_Error (Arg) then
11729                   null;
11730
11731                --  Otherwise check in range
11732
11733                else
11734                   declare
11735                      Val : constant Uint := Expr_Value (Arg);
11736
11737                   begin
11738                      if Val < 0
11739                        or else Val > Expr_Value (Expression
11740                                        (Parent (RTE (RE_Max_Priority))))
11741                      then
11742                         Error_Pragma_Arg
11743                           ("main subprogram priority is out of range", Arg1);
11744                      end if;
11745                   end;
11746                end if;
11747
11748                Set_Main_Priority
11749                     (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
11750
11751                --  Load an arbitrary entity from System.Tasking to make sure
11752                --  this package is implicitly with'ed, since we need to have
11753                --  the tasking run-time active for the pragma Priority to have
11754                --  any effect.
11755
11756                declare
11757                   Discard : Entity_Id;
11758                   pragma Warnings (Off, Discard);
11759                begin
11760                   Discard := RTE (RE_Task_List);
11761                end;
11762
11763             --  Task or Protected, must be of type Integer
11764
11765             elsif Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
11766                Arg := Get_Pragma_Arg (Arg1);
11767
11768                --  The expression must be analyzed in the special manner
11769                --  described in "Handling of Default and Per-Object
11770                --  Expressions" in sem.ads.
11771
11772                Preanalyze_Spec_Expression (Arg, Standard_Integer);
11773
11774                if not Is_Static_Expression (Arg) then
11775                   Check_Restriction (Static_Priorities, Arg);
11776                end if;
11777
11778             --  Anything else is incorrect
11779
11780             else
11781                Pragma_Misplaced;
11782             end if;
11783
11784             if Has_Pragma_Priority (P) then
11785                Error_Pragma ("duplicate pragma% not allowed");
11786             else
11787                Set_Has_Pragma_Priority (P, True);
11788
11789                if Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
11790                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
11791                   --  exp_ch9 should use this ???
11792                end if;
11793             end if;
11794          end Priority;
11795
11796          -----------------------------------
11797          -- Priority_Specific_Dispatching --
11798          -----------------------------------
11799
11800          --  pragma Priority_Specific_Dispatching (
11801          --    policy_IDENTIFIER,
11802          --    first_priority_EXPRESSION,
11803          --    last_priority_EXPRESSION);
11804
11805          when Pragma_Priority_Specific_Dispatching =>
11806          Priority_Specific_Dispatching : declare
11807             Prio_Id : constant Entity_Id := RTE (RE_Any_Priority);
11808             --  This is the entity System.Any_Priority;
11809
11810             DP          : Character;
11811             Lower_Bound : Node_Id;
11812             Upper_Bound : Node_Id;
11813             Lower_Val   : Uint;
11814             Upper_Val   : Uint;
11815
11816          begin
11817             Ada_2005_Pragma;
11818             Check_Arg_Count (3);
11819             Check_No_Identifiers;
11820             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
11821             Check_Valid_Configuration_Pragma;
11822             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
11823             DP := Fold_Upper (Name_Buffer (1));
11824
11825             Lower_Bound := Get_Pragma_Arg (Arg2);
11826             Check_Arg_Is_Static_Expression (Lower_Bound, Standard_Integer);
11827             Lower_Val := Expr_Value (Lower_Bound);
11828
11829             Upper_Bound := Get_Pragma_Arg (Arg3);
11830             Check_Arg_Is_Static_Expression (Upper_Bound, Standard_Integer);
11831             Upper_Val := Expr_Value (Upper_Bound);
11832
11833             --  It is not allowed to use Task_Dispatching_Policy and
11834             --  Priority_Specific_Dispatching in the same partition.
11835
11836             if Task_Dispatching_Policy /= ' ' then
11837                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
11838                Error_Pragma
11839                  ("pragma% incompatible with Task_Dispatching_Policy#");
11840
11841             --  Check lower bound in range
11842
11843             elsif Lower_Val < Expr_Value (Type_Low_Bound (Prio_Id))
11844                     or else
11845                   Lower_Val > Expr_Value (Type_High_Bound (Prio_Id))
11846             then
11847                Error_Pragma_Arg
11848                  ("first_priority is out of range", Arg2);
11849
11850             --  Check upper bound in range
11851
11852             elsif Upper_Val < Expr_Value (Type_Low_Bound (Prio_Id))
11853                     or else
11854                   Upper_Val > Expr_Value (Type_High_Bound (Prio_Id))
11855             then
11856                Error_Pragma_Arg
11857                  ("last_priority is out of range", Arg3);
11858
11859             --  Check that the priority range is valid
11860
11861             elsif Lower_Val > Upper_Val then
11862                Error_Pragma
11863                  ("last_priority_expression must be greater than" &
11864                   " or equal to first_priority_expression");
11865
11866             --  Store the new policy, but always preserve System_Location since
11867             --  we like the error message with the run-time name.
11868
11869             else
11870                --  Check overlapping in the priority ranges specified in other
11871                --  Priority_Specific_Dispatching pragmas within the same
11872                --  partition. We can only check those we know about!
11873
11874                for J in
11875                   Specific_Dispatching.First .. Specific_Dispatching.Last
11876                loop
11877                   if Specific_Dispatching.Table (J).First_Priority in
11878                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
11879                   or else Specific_Dispatching.Table (J).Last_Priority in
11880                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
11881                   then
11882                      Error_Msg_Sloc :=
11883                        Specific_Dispatching.Table (J).Pragma_Loc;
11884                         Error_Pragma
11885                           ("priority range overlaps with "
11886                            & "Priority_Specific_Dispatching#");
11887                   end if;
11888                end loop;
11889
11890                --  The use of Priority_Specific_Dispatching is incompatible
11891                --  with Task_Dispatching_Policy.
11892
11893                if Task_Dispatching_Policy /= ' ' then
11894                   Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
11895                      Error_Pragma
11896                        ("Priority_Specific_Dispatching incompatible "
11897                         & "with Task_Dispatching_Policy#");
11898                end if;
11899
11900                --  The use of Priority_Specific_Dispatching forces ceiling
11901                --  locking policy.
11902
11903                if Locking_Policy /= ' ' and then Locking_Policy /= 'C' then
11904                   Error_Msg_Sloc := Locking_Policy_Sloc;
11905                      Error_Pragma
11906                        ("Priority_Specific_Dispatching incompatible "
11907                         & "with Locking_Policy#");
11908
11909                --  Set the Ceiling_Locking policy, but preserve System_Location
11910                --  since we like the error message with the run time name.
11911
11912                else
11913                   Locking_Policy := 'C';
11914
11915                   if Locking_Policy_Sloc /= System_Location then
11916                      Locking_Policy_Sloc := Loc;
11917                   end if;
11918                end if;
11919
11920                --  Add entry in the table
11921
11922                Specific_Dispatching.Append
11923                     ((Dispatching_Policy => DP,
11924                       First_Priority     => UI_To_Int (Lower_Val),
11925                       Last_Priority      => UI_To_Int (Upper_Val),
11926                       Pragma_Loc         => Loc));
11927             end if;
11928          end Priority_Specific_Dispatching;
11929
11930          -------------
11931          -- Profile --
11932          -------------
11933
11934          --  pragma Profile (profile_IDENTIFIER);
11935
11936          --  profile_IDENTIFIER => Restricted | Ravenscar
11937
11938          when Pragma_Profile =>
11939             Ada_2005_Pragma;
11940             Check_Arg_Count (1);
11941             Check_Valid_Configuration_Pragma;
11942             Check_No_Identifiers;
11943
11944             declare
11945                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
11946             begin
11947                if Chars (Argx) = Name_Ravenscar then
11948                   Set_Ravenscar_Profile (N);
11949                elsif Chars (Argx) = Name_Restricted then
11950                   Set_Profile_Restrictions
11951                     (Restricted, N, Warn => Treat_Restrictions_As_Warnings);
11952                else
11953                   Error_Pragma_Arg ("& is not a valid profile", Argx);
11954                end if;
11955             end;
11956
11957          ----------------------
11958          -- Profile_Warnings --
11959          ----------------------
11960
11961          --  pragma Profile_Warnings (profile_IDENTIFIER);
11962
11963          --  profile_IDENTIFIER => Restricted | Ravenscar
11964
11965          when Pragma_Profile_Warnings =>
11966             GNAT_Pragma;
11967             Check_Arg_Count (1);
11968             Check_Valid_Configuration_Pragma;
11969             Check_No_Identifiers;
11970
11971             declare
11972                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
11973             begin
11974                if Chars (Argx) = Name_Ravenscar then
11975                   Set_Profile_Restrictions (Ravenscar, N, Warn => True);
11976                elsif Chars (Argx) = Name_Restricted then
11977                   Set_Profile_Restrictions (Restricted, N, Warn => True);
11978                else
11979                   Error_Pragma_Arg ("& is not a valid profile", Argx);
11980                end if;
11981             end;
11982
11983          --------------------------
11984          -- Propagate_Exceptions --
11985          --------------------------
11986
11987          --  pragma Propagate_Exceptions;
11988
11989          --  Note: this pragma is obsolete and has no effect
11990
11991          when Pragma_Propagate_Exceptions =>
11992             GNAT_Pragma;
11993             Check_Arg_Count (0);
11994
11995             if In_Extended_Main_Source_Unit (N) then
11996                Propagate_Exceptions := True;
11997             end if;
11998
11999          ------------------
12000          -- Psect_Object --
12001          ------------------
12002
12003          --  pragma Psect_Object (
12004          --        [Internal =>] LOCAL_NAME,
12005          --     [, [External =>] EXTERNAL_SYMBOL]
12006          --     [, [Size     =>] EXTERNAL_SYMBOL]);
12007
12008          when Pragma_Psect_Object | Pragma_Common_Object =>
12009          Psect_Object : declare
12010             Args  : Args_List (1 .. 3);
12011             Names : constant Name_List (1 .. 3) := (
12012                       Name_Internal,
12013                       Name_External,
12014                       Name_Size);
12015
12016             Internal : Node_Id renames Args (1);
12017             External : Node_Id renames Args (2);
12018             Size     : Node_Id renames Args (3);
12019
12020             Def_Id : Entity_Id;
12021
12022             procedure Check_Too_Long (Arg : Node_Id);
12023             --  Posts message if the argument is an identifier with more
12024             --  than 31 characters, or a string literal with more than
12025             --  31 characters, and we are operating under VMS
12026
12027             --------------------
12028             -- Check_Too_Long --
12029             --------------------
12030
12031             procedure Check_Too_Long (Arg : Node_Id) is
12032                X : constant Node_Id := Original_Node (Arg);
12033
12034             begin
12035                if not Nkind_In (X, N_String_Literal, N_Identifier) then
12036                   Error_Pragma_Arg
12037                     ("inappropriate argument for pragma %", Arg);
12038                end if;
12039
12040                if OpenVMS_On_Target then
12041                   if (Nkind (X) = N_String_Literal
12042                        and then String_Length (Strval (X)) > 31)
12043                     or else
12044                      (Nkind (X) = N_Identifier
12045                        and then Length_Of_Name (Chars (X)) > 31)
12046                   then
12047                      Error_Pragma_Arg
12048                        ("argument for pragma % is longer than 31 characters",
12049                         Arg);
12050                   end if;
12051                end if;
12052             end Check_Too_Long;
12053
12054          --  Start of processing for Common_Object/Psect_Object
12055
12056          begin
12057             GNAT_Pragma;
12058             Gather_Associations (Names, Args);
12059             Process_Extended_Import_Export_Internal_Arg (Internal);
12060
12061             Def_Id := Entity (Internal);
12062
12063             if not Ekind_In (Def_Id, E_Constant, E_Variable) then
12064                Error_Pragma_Arg
12065                  ("pragma% must designate an object", Internal);
12066             end if;
12067
12068             Check_Too_Long (Internal);
12069
12070             if Is_Imported (Def_Id) or else Is_Exported (Def_Id) then
12071                Error_Pragma_Arg
12072                  ("cannot use pragma% for imported/exported object",
12073                   Internal);
12074             end if;
12075
12076             if Is_Concurrent_Type (Etype (Internal)) then
12077                Error_Pragma_Arg
12078                  ("cannot specify pragma % for task/protected object",
12079                   Internal);
12080             end if;
12081
12082             if Has_Rep_Pragma (Def_Id, Name_Common_Object)
12083                  or else
12084                Has_Rep_Pragma (Def_Id, Name_Psect_Object)
12085             then
12086                Error_Msg_N ("?duplicate Common/Psect_Object pragma", N);
12087             end if;
12088
12089             if Ekind (Def_Id) = E_Constant then
12090                Error_Pragma_Arg
12091                  ("cannot specify pragma % for a constant", Internal);
12092             end if;
12093
12094             if Is_Record_Type (Etype (Internal)) then
12095                declare
12096                   Ent  : Entity_Id;
12097                   Decl : Entity_Id;
12098
12099                begin
12100                   Ent := First_Entity (Etype (Internal));
12101                   while Present (Ent) loop
12102                      Decl := Declaration_Node (Ent);
12103
12104                      if Ekind (Ent) = E_Component
12105                        and then Nkind (Decl) = N_Component_Declaration
12106                        and then Present (Expression (Decl))
12107                        and then Warn_On_Export_Import
12108                      then
12109                         Error_Msg_N
12110                           ("?object for pragma % has defaults", Internal);
12111                         exit;
12112
12113                      else
12114                         Next_Entity (Ent);
12115                      end if;
12116                   end loop;
12117                end;
12118             end if;
12119
12120             if Present (Size) then
12121                Check_Too_Long (Size);
12122             end if;
12123
12124             if Present (External) then
12125                Check_Arg_Is_External_Name (External);
12126                Check_Too_Long (External);
12127             end if;
12128
12129             --  If all error tests pass, link pragma on to the rep item chain
12130
12131             Record_Rep_Item (Def_Id, N);
12132          end Psect_Object;
12133
12134          ----------
12135          -- Pure --
12136          ----------
12137
12138          --  pragma Pure [(library_unit_NAME)];
12139
12140          when Pragma_Pure => Pure : declare
12141             Ent : Entity_Id;
12142
12143          begin
12144             Check_Ada_83_Warning;
12145             Check_Valid_Library_Unit_Pragma;
12146
12147             if Nkind (N) = N_Null_Statement then
12148                return;
12149             end if;
12150
12151             Ent := Find_Lib_Unit_Name;
12152             Set_Is_Pure (Ent);
12153             Set_Has_Pragma_Pure (Ent);
12154             Set_Suppress_Elaboration_Warnings (Ent);
12155          end Pure;
12156
12157          -------------
12158          -- Pure_05 --
12159          -------------
12160
12161          --  pragma Pure_05 [(library_unit_NAME)];
12162
12163          --  This pragma is useable only in GNAT_Mode, where it is used like
12164          --  pragma Pure but it is only effective in Ada 2005 mode (otherwise
12165          --  it is ignored). It may be used after a pragma Preelaborate, in
12166          --  which case it overrides the effect of the pragma Preelaborate.
12167          --  This is used to implement AI-362 which recategorizes some run-time
12168          --  packages in Ada 2005 mode.
12169
12170          when Pragma_Pure_05 => Pure_05 : declare
12171             Ent : Entity_Id;
12172
12173          begin
12174             GNAT_Pragma;
12175             Check_Valid_Library_Unit_Pragma;
12176
12177             if not GNAT_Mode then
12178                Error_Pragma ("pragma% only available in GNAT mode");
12179             end if;
12180
12181             if Nkind (N) = N_Null_Statement then
12182                return;
12183             end if;
12184
12185             --  This is one of the few cases where we need to test the value of
12186             --  Ada_Version_Explicit rather than Ada_Version (which is always
12187             --  set to Ada_2012 in a predefined unit), we need to know the
12188             --  explicit version set to know if this pragma is active.
12189
12190             if Ada_Version_Explicit >= Ada_2005 then
12191                Ent := Find_Lib_Unit_Name;
12192                Set_Is_Preelaborated (Ent, False);
12193                Set_Is_Pure (Ent);
12194                Set_Suppress_Elaboration_Warnings (Ent);
12195             end if;
12196          end Pure_05;
12197
12198          -------------------
12199          -- Pure_Function --
12200          -------------------
12201
12202          --  pragma Pure_Function ([Entity =>] function_LOCAL_NAME);
12203
12204          when Pragma_Pure_Function => Pure_Function : declare
12205             E_Id      : Node_Id;
12206             E         : Entity_Id;
12207             Def_Id    : Entity_Id;
12208             Effective : Boolean := False;
12209
12210          begin
12211             GNAT_Pragma;
12212             Check_Arg_Count (1);
12213             Check_Optional_Identifier (Arg1, Name_Entity);
12214             Check_Arg_Is_Local_Name (Arg1);
12215             E_Id := Get_Pragma_Arg (Arg1);
12216
12217             if Error_Posted (E_Id) then
12218                return;
12219             end if;
12220
12221             --  Loop through homonyms (overloadings) of referenced entity
12222
12223             E := Entity (E_Id);
12224
12225             if Present (E) then
12226                loop
12227                   Def_Id := Get_Base_Subprogram (E);
12228
12229                   if not Ekind_In (Def_Id, E_Function,
12230                                            E_Generic_Function,
12231                                            E_Operator)
12232                   then
12233                      Error_Pragma_Arg
12234                        ("pragma% requires a function name", Arg1);
12235                   end if;
12236
12237                   Set_Is_Pure (Def_Id);
12238
12239                   if not Has_Pragma_Pure_Function (Def_Id) then
12240                      Set_Has_Pragma_Pure_Function (Def_Id);
12241                      Effective := True;
12242                   end if;
12243
12244                   exit when From_Aspect_Specification (N);
12245                   E := Homonym (E);
12246                   exit when No (E) or else Scope (E) /= Current_Scope;
12247                end loop;
12248
12249                if not Effective
12250                  and then Warn_On_Redundant_Constructs
12251                then
12252                   Error_Msg_NE
12253                     ("pragma Pure_Function on& is redundant?",
12254                      N, Entity (E_Id));
12255                end if;
12256             end if;
12257          end Pure_Function;
12258
12259          --------------------
12260          -- Queuing_Policy --
12261          --------------------
12262
12263          --  pragma Queuing_Policy (policy_IDENTIFIER);
12264
12265          when Pragma_Queuing_Policy => declare
12266             QP : Character;
12267
12268          begin
12269             Check_Ada_83_Warning;
12270             Check_Arg_Count (1);
12271             Check_No_Identifiers;
12272             Check_Arg_Is_Queuing_Policy (Arg1);
12273             Check_Valid_Configuration_Pragma;
12274             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
12275             QP := Fold_Upper (Name_Buffer (1));
12276
12277             if Queuing_Policy /= ' '
12278               and then Queuing_Policy /= QP
12279             then
12280                Error_Msg_Sloc := Queuing_Policy_Sloc;
12281                Error_Pragma ("queuing policy incompatible with policy#");
12282
12283             --  Set new policy, but always preserve System_Location since we
12284             --  like the error message with the run time name.
12285
12286             else
12287                Queuing_Policy := QP;
12288
12289                if Queuing_Policy_Sloc /= System_Location then
12290                   Queuing_Policy_Sloc := Loc;
12291                end if;
12292             end if;
12293          end;
12294
12295          -----------------------
12296          -- Relative_Deadline --
12297          -----------------------
12298
12299          --  pragma Relative_Deadline (time_span_EXPRESSION);
12300
12301          when Pragma_Relative_Deadline => Relative_Deadline : declare
12302             P   : constant Node_Id := Parent (N);
12303             Arg : Node_Id;
12304
12305          begin
12306             Ada_2005_Pragma;
12307             Check_No_Identifiers;
12308             Check_Arg_Count (1);
12309
12310             Arg := Get_Pragma_Arg (Arg1);
12311
12312             --  The expression must be analyzed in the special manner described
12313             --  in "Handling of Default and Per-Object Expressions" in sem.ads.
12314
12315             Preanalyze_Spec_Expression (Arg, RTE (RE_Time_Span));
12316
12317             --  Subprogram case
12318
12319             if Nkind (P) = N_Subprogram_Body then
12320                Check_In_Main_Program;
12321
12322             --  Tasks
12323
12324             elsif Nkind (P) = N_Task_Definition then
12325                null;
12326
12327             --  Anything else is incorrect
12328
12329             else
12330                Pragma_Misplaced;
12331             end if;
12332
12333             if Has_Relative_Deadline_Pragma (P) then
12334                Error_Pragma ("duplicate pragma% not allowed");
12335             else
12336                Set_Has_Relative_Deadline_Pragma (P, True);
12337
12338                if Nkind (P) = N_Task_Definition then
12339                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
12340                end if;
12341             end if;
12342          end Relative_Deadline;
12343
12344          ---------------------------
12345          -- Remote_Call_Interface --
12346          ---------------------------
12347
12348          --  pragma Remote_Call_Interface [(library_unit_NAME)];
12349
12350          when Pragma_Remote_Call_Interface => Remote_Call_Interface : declare
12351             Cunit_Node : Node_Id;
12352             Cunit_Ent  : Entity_Id;
12353             K          : Node_Kind;
12354
12355          begin
12356             Check_Ada_83_Warning;
12357             Check_Valid_Library_Unit_Pragma;
12358
12359             if Nkind (N) = N_Null_Statement then
12360                return;
12361             end if;
12362
12363             Cunit_Node := Cunit (Current_Sem_Unit);
12364             K          := Nkind (Unit (Cunit_Node));
12365             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12366
12367             if K = N_Package_Declaration
12368               or else K = N_Generic_Package_Declaration
12369               or else K = N_Subprogram_Declaration
12370               or else K = N_Generic_Subprogram_Declaration
12371               or else (K = N_Subprogram_Body
12372                          and then Acts_As_Spec (Unit (Cunit_Node)))
12373             then
12374                null;
12375             else
12376                Error_Pragma (
12377                  "pragma% must apply to package or subprogram declaration");
12378             end if;
12379
12380             Set_Is_Remote_Call_Interface (Cunit_Ent);
12381          end Remote_Call_Interface;
12382
12383          ------------------
12384          -- Remote_Types --
12385          ------------------
12386
12387          --  pragma Remote_Types [(library_unit_NAME)];
12388
12389          when Pragma_Remote_Types => Remote_Types : declare
12390             Cunit_Node : Node_Id;
12391             Cunit_Ent  : Entity_Id;
12392
12393          begin
12394             Check_Ada_83_Warning;
12395             Check_Valid_Library_Unit_Pragma;
12396
12397             if Nkind (N) = N_Null_Statement then
12398                return;
12399             end if;
12400
12401             Cunit_Node := Cunit (Current_Sem_Unit);
12402             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12403
12404             if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
12405                                                 N_Generic_Package_Declaration)
12406             then
12407                Error_Pragma
12408                  ("pragma% can only apply to a package declaration");
12409             end if;
12410
12411             Set_Is_Remote_Types (Cunit_Ent);
12412          end Remote_Types;
12413
12414          ---------------
12415          -- Ravenscar --
12416          ---------------
12417
12418          --  pragma Ravenscar;
12419
12420          when Pragma_Ravenscar =>
12421             GNAT_Pragma;
12422             Check_Arg_Count (0);
12423             Check_Valid_Configuration_Pragma;
12424             Set_Ravenscar_Profile (N);
12425
12426             if Warn_On_Obsolescent_Feature then
12427                Error_Msg_N ("pragma Ravenscar is an obsolescent feature?", N);
12428                Error_Msg_N ("|use pragma Profile (Ravenscar) instead", N);
12429             end if;
12430
12431          -------------------------
12432          -- Restricted_Run_Time --
12433          -------------------------
12434
12435          --  pragma Restricted_Run_Time;
12436
12437          when Pragma_Restricted_Run_Time =>
12438             GNAT_Pragma;
12439             Check_Arg_Count (0);
12440             Check_Valid_Configuration_Pragma;
12441             Set_Profile_Restrictions
12442               (Restricted, N, Warn => Treat_Restrictions_As_Warnings);
12443
12444             if Warn_On_Obsolescent_Feature then
12445                Error_Msg_N
12446                  ("pragma Restricted_Run_Time is an obsolescent feature?", N);
12447                Error_Msg_N ("|use pragma Profile (Restricted) instead", N);
12448             end if;
12449
12450          ------------------
12451          -- Restrictions --
12452          ------------------
12453
12454          --  pragma Restrictions (RESTRICTION {, RESTRICTION});
12455
12456          --  RESTRICTION ::=
12457          --    restriction_IDENTIFIER
12458          --  | restriction_parameter_IDENTIFIER => EXPRESSION
12459
12460          when Pragma_Restrictions =>
12461             Process_Restrictions_Or_Restriction_Warnings
12462               (Warn => Treat_Restrictions_As_Warnings);
12463
12464          --------------------------
12465          -- Restriction_Warnings --
12466          --------------------------
12467
12468          --  pragma Restriction_Warnings (RESTRICTION {, RESTRICTION});
12469
12470          --  RESTRICTION ::=
12471          --    restriction_IDENTIFIER
12472          --  | restriction_parameter_IDENTIFIER => EXPRESSION
12473
12474          when Pragma_Restriction_Warnings =>
12475             GNAT_Pragma;
12476             Process_Restrictions_Or_Restriction_Warnings (Warn => True);
12477
12478          ----------------
12479          -- Reviewable --
12480          ----------------
12481
12482          --  pragma Reviewable;
12483
12484          when Pragma_Reviewable =>
12485             Check_Ada_83_Warning;
12486             Check_Arg_Count (0);
12487
12488             --  Call dummy debugging function rv. This is done to assist front
12489             --  end debugging. By placing a Reviewable pragma in the source
12490             --  program, a breakpoint on rv catches this place in the source,
12491             --  allowing convenient stepping to the point of interest.
12492
12493             rv;
12494
12495          --------------------------
12496          -- Short_Circuit_And_Or --
12497          --------------------------
12498
12499          when Pragma_Short_Circuit_And_Or =>
12500             GNAT_Pragma;
12501             Check_Arg_Count (0);
12502             Check_Valid_Configuration_Pragma;
12503             Short_Circuit_And_Or := True;
12504
12505          -------------------
12506          -- Share_Generic --
12507          -------------------
12508
12509          --  pragma Share_Generic (NAME {, NAME});
12510
12511          when Pragma_Share_Generic =>
12512             GNAT_Pragma;
12513             Process_Generic_List;
12514
12515          ------------
12516          -- Shared --
12517          ------------
12518
12519          --  pragma Shared (LOCAL_NAME);
12520
12521          when Pragma_Shared =>
12522             GNAT_Pragma;
12523             Process_Atomic_Shared_Volatile;
12524
12525          --------------------
12526          -- Shared_Passive --
12527          --------------------
12528
12529          --  pragma Shared_Passive [(library_unit_NAME)];
12530
12531          --  Set the flag Is_Shared_Passive of program unit name entity
12532
12533          when Pragma_Shared_Passive => Shared_Passive : declare
12534             Cunit_Node : Node_Id;
12535             Cunit_Ent  : Entity_Id;
12536
12537          begin
12538             Check_Ada_83_Warning;
12539             Check_Valid_Library_Unit_Pragma;
12540
12541             if Nkind (N) = N_Null_Statement then
12542                return;
12543             end if;
12544
12545             Cunit_Node := Cunit (Current_Sem_Unit);
12546             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12547
12548             if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
12549                                                 N_Generic_Package_Declaration)
12550             then
12551                Error_Pragma
12552                  ("pragma% can only apply to a package declaration");
12553             end if;
12554
12555             Set_Is_Shared_Passive (Cunit_Ent);
12556          end Shared_Passive;
12557
12558          -----------------------
12559          -- Short_Descriptors --
12560          -----------------------
12561
12562          --  pragma Short_Descriptors;
12563
12564          when Pragma_Short_Descriptors =>
12565             GNAT_Pragma;
12566             Check_Arg_Count (0);
12567             Check_Valid_Configuration_Pragma;
12568             Short_Descriptors := True;
12569
12570          ----------------------
12571          -- Source_File_Name --
12572          ----------------------
12573
12574          --  There are five forms for this pragma:
12575
12576          --  pragma Source_File_Name (
12577          --    [UNIT_NAME      =>] unit_NAME,
12578          --     BODY_FILE_NAME =>  STRING_LITERAL
12579          --    [, [INDEX =>] INTEGER_LITERAL]);
12580
12581          --  pragma Source_File_Name (
12582          --    [UNIT_NAME      =>] unit_NAME,
12583          --     SPEC_FILE_NAME =>  STRING_LITERAL
12584          --    [, [INDEX =>] INTEGER_LITERAL]);
12585
12586          --  pragma Source_File_Name (
12587          --     BODY_FILE_NAME  => STRING_LITERAL
12588          --  [, DOT_REPLACEMENT => STRING_LITERAL]
12589          --  [, CASING          => CASING_SPEC]);
12590
12591          --  pragma Source_File_Name (
12592          --     SPEC_FILE_NAME  => STRING_LITERAL
12593          --  [, DOT_REPLACEMENT => STRING_LITERAL]
12594          --  [, CASING          => CASING_SPEC]);
12595
12596          --  pragma Source_File_Name (
12597          --     SUBUNIT_FILE_NAME  => STRING_LITERAL
12598          --  [, DOT_REPLACEMENT    => STRING_LITERAL]
12599          --  [, CASING             => CASING_SPEC]);
12600
12601          --  CASING_SPEC ::= Uppercase | Lowercase | Mixedcase
12602
12603          --  Pragma Source_File_Name_Project (SFNP) is equivalent to pragma
12604          --  Source_File_Name (SFN), however their usage is exclusive: SFN can
12605          --  only be used when no project file is used, while SFNP can only be
12606          --  used when a project file is used.
12607
12608          --  No processing here. Processing was completed during parsing, since
12609          --  we need to have file names set as early as possible. Units are
12610          --  loaded well before semantic processing starts.
12611
12612          --  The only processing we defer to this point is the check for
12613          --  correct placement.
12614
12615          when Pragma_Source_File_Name =>
12616             GNAT_Pragma;
12617             Check_Valid_Configuration_Pragma;
12618
12619          ------------------------------
12620          -- Source_File_Name_Project --
12621          ------------------------------
12622
12623          --  See Source_File_Name for syntax
12624
12625          --  No processing here. Processing was completed during parsing, since
12626          --  we need to have file names set as early as possible. Units are
12627          --  loaded well before semantic processing starts.
12628
12629          --  The only processing we defer to this point is the check for
12630          --  correct placement.
12631
12632          when Pragma_Source_File_Name_Project =>
12633             GNAT_Pragma;
12634             Check_Valid_Configuration_Pragma;
12635
12636             --  Check that a pragma Source_File_Name_Project is used only in a
12637             --  configuration pragmas file.
12638
12639             --  Pragmas Source_File_Name_Project should only be generated by
12640             --  the Project Manager in configuration pragmas files.
12641
12642             --  This is really an ugly test. It seems to depend on some
12643             --  accidental and undocumented property. At the very least it
12644             --  needs to be documented, but it would be better to have a
12645             --  clean way of testing if we are in a configuration file???
12646
12647             if Present (Parent (N)) then
12648                Error_Pragma
12649                  ("pragma% can only appear in a configuration pragmas file");
12650             end if;
12651
12652          ----------------------
12653          -- Source_Reference --
12654          ----------------------
12655
12656          --  pragma Source_Reference (INTEGER_LITERAL [, STRING_LITERAL]);
12657
12658          --  Nothing to do, all processing completed in Par.Prag, since we need
12659          --  the information for possible parser messages that are output.
12660
12661          when Pragma_Source_Reference =>
12662             GNAT_Pragma;
12663
12664          --------------------------------
12665          -- Static_Elaboration_Desired --
12666          --------------------------------
12667
12668          --  pragma Static_Elaboration_Desired (DIRECT_NAME);
12669
12670          when Pragma_Static_Elaboration_Desired =>
12671             GNAT_Pragma;
12672             Check_At_Most_N_Arguments (1);
12673
12674             if Is_Compilation_Unit (Current_Scope)
12675               and then Ekind (Current_Scope) = E_Package
12676             then
12677                Set_Static_Elaboration_Desired (Current_Scope, True);
12678             else
12679                Error_Pragma ("pragma% must apply to a library-level package");
12680             end if;
12681
12682          ------------------
12683          -- Storage_Size --
12684          ------------------
12685
12686          --  pragma Storage_Size (EXPRESSION);
12687
12688          when Pragma_Storage_Size => Storage_Size : declare
12689             P   : constant Node_Id := Parent (N);
12690             Arg : Node_Id;
12691
12692          begin
12693             Check_No_Identifiers;
12694             Check_Arg_Count (1);
12695
12696             --  The expression must be analyzed in the special manner described
12697             --  in "Handling of Default Expressions" in sem.ads.
12698
12699             Arg := Get_Pragma_Arg (Arg1);
12700             Preanalyze_Spec_Expression (Arg, Any_Integer);
12701
12702             if not Is_Static_Expression (Arg) then
12703                Check_Restriction (Static_Storage_Size, Arg);
12704             end if;
12705
12706             if Nkind (P) /= N_Task_Definition then
12707                Pragma_Misplaced;
12708                return;
12709
12710             else
12711                if Has_Storage_Size_Pragma (P) then
12712                   Error_Pragma ("duplicate pragma% not allowed");
12713                else
12714                   Set_Has_Storage_Size_Pragma (P, True);
12715                end if;
12716
12717                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
12718                --  ???  exp_ch9 should use this!
12719             end if;
12720          end Storage_Size;
12721
12722          ------------------
12723          -- Storage_Unit --
12724          ------------------
12725
12726          --  pragma Storage_Unit (NUMERIC_LITERAL);
12727
12728          --  Only permitted argument is System'Storage_Unit value
12729
12730          when Pragma_Storage_Unit =>
12731             Check_No_Identifiers;
12732             Check_Arg_Count (1);
12733             Check_Arg_Is_Integer_Literal (Arg1);
12734
12735             if Intval (Get_Pragma_Arg (Arg1)) /=
12736               UI_From_Int (Ttypes.System_Storage_Unit)
12737             then
12738                Error_Msg_Uint_1 := UI_From_Int (Ttypes.System_Storage_Unit);
12739                Error_Pragma_Arg
12740                  ("the only allowed argument for pragma% is ^", Arg1);
12741             end if;
12742
12743          --------------------
12744          -- Stream_Convert --
12745          --------------------
12746
12747          --  pragma Stream_Convert (
12748          --    [Entity =>] type_LOCAL_NAME,
12749          --    [Read   =>] function_NAME,
12750          --    [Write  =>] function NAME);
12751
12752          when Pragma_Stream_Convert => Stream_Convert : declare
12753
12754             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id);
12755             --  Check that the given argument is the name of a local function
12756             --  of one argument that is not overloaded earlier in the current
12757             --  local scope. A check is also made that the argument is a
12758             --  function with one parameter.
12759
12760             --------------------------------------
12761             -- Check_OK_Stream_Convert_Function --
12762             --------------------------------------
12763
12764             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id) is
12765                Ent : Entity_Id;
12766
12767             begin
12768                Check_Arg_Is_Local_Name (Arg);
12769                Ent := Entity (Get_Pragma_Arg (Arg));
12770
12771                if Has_Homonym (Ent) then
12772                   Error_Pragma_Arg
12773                     ("argument for pragma% may not be overloaded", Arg);
12774                end if;
12775
12776                if Ekind (Ent) /= E_Function
12777                  or else No (First_Formal (Ent))
12778                  or else Present (Next_Formal (First_Formal (Ent)))
12779                then
12780                   Error_Pragma_Arg
12781                     ("argument for pragma% must be" &
12782                      " function of one argument", Arg);
12783                end if;
12784             end Check_OK_Stream_Convert_Function;
12785
12786          --  Start of processing for Stream_Convert
12787
12788          begin
12789             GNAT_Pragma;
12790             Check_Arg_Order ((Name_Entity, Name_Read, Name_Write));
12791             Check_Arg_Count (3);
12792             Check_Optional_Identifier (Arg1, Name_Entity);
12793             Check_Optional_Identifier (Arg2, Name_Read);
12794             Check_Optional_Identifier (Arg3, Name_Write);
12795             Check_Arg_Is_Local_Name (Arg1);
12796             Check_OK_Stream_Convert_Function (Arg2);
12797             Check_OK_Stream_Convert_Function (Arg3);
12798
12799             declare
12800                Typ   : constant Entity_Id :=
12801                          Underlying_Type (Entity (Get_Pragma_Arg (Arg1)));
12802                Read  : constant Entity_Id := Entity (Get_Pragma_Arg (Arg2));
12803                Write : constant Entity_Id := Entity (Get_Pragma_Arg (Arg3));
12804
12805             begin
12806                Check_First_Subtype (Arg1);
12807
12808                --  Check for too early or too late. Note that we don't enforce
12809                --  the rule about primitive operations in this case, since, as
12810                --  is the case for explicit stream attributes themselves, these
12811                --  restrictions are not appropriate. Note that the chaining of
12812                --  the pragma by Rep_Item_Too_Late is actually the critical
12813                --  processing done for this pragma.
12814
12815                if Rep_Item_Too_Early (Typ, N)
12816                     or else
12817                   Rep_Item_Too_Late (Typ, N, FOnly => True)
12818                then
12819                   return;
12820                end if;
12821
12822                --  Return if previous error
12823
12824                if Etype (Typ) = Any_Type
12825                     or else
12826                   Etype (Read) = Any_Type
12827                     or else
12828                   Etype (Write) = Any_Type
12829                then
12830                   return;
12831                end if;
12832
12833                --  Error checks
12834
12835                if Underlying_Type (Etype (Read)) /= Typ then
12836                   Error_Pragma_Arg
12837                     ("incorrect return type for function&", Arg2);
12838                end if;
12839
12840                if Underlying_Type (Etype (First_Formal (Write))) /= Typ then
12841                   Error_Pragma_Arg
12842                     ("incorrect parameter type for function&", Arg3);
12843                end if;
12844
12845                if Underlying_Type (Etype (First_Formal (Read))) /=
12846                   Underlying_Type (Etype (Write))
12847                then
12848                   Error_Pragma_Arg
12849                     ("result type of & does not match Read parameter type",
12850                      Arg3);
12851                end if;
12852             end;
12853          end Stream_Convert;
12854
12855          -------------------------
12856          -- Style_Checks (GNAT) --
12857          -------------------------
12858
12859          --  pragma Style_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
12860
12861          --  This is processed by the parser since some of the style checks
12862          --  take place during source scanning and parsing. This means that
12863          --  we don't need to issue error messages here.
12864
12865          when Pragma_Style_Checks => Style_Checks : declare
12866             A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
12867             S  : String_Id;
12868             C  : Char_Code;
12869
12870          begin
12871             GNAT_Pragma;
12872             Check_No_Identifiers;
12873
12874             --  Two argument form
12875
12876             if Arg_Count = 2 then
12877                Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
12878
12879                declare
12880                   E_Id : Node_Id;
12881                   E    : Entity_Id;
12882
12883                begin
12884                   E_Id := Get_Pragma_Arg (Arg2);
12885                   Analyze (E_Id);
12886
12887                   if not Is_Entity_Name (E_Id) then
12888                      Error_Pragma_Arg
12889                        ("second argument of pragma% must be entity name",
12890                         Arg2);
12891                   end if;
12892
12893                   E := Entity (E_Id);
12894
12895                   if E = Any_Id then
12896                      return;
12897                   else
12898                      loop
12899                         Set_Suppress_Style_Checks (E,
12900                           (Chars (Get_Pragma_Arg (Arg1)) = Name_Off));
12901                         exit when No (Homonym (E));
12902                         E := Homonym (E);
12903                      end loop;
12904                   end if;
12905                end;
12906
12907             --  One argument form
12908
12909             else
12910                Check_Arg_Count (1);
12911
12912                if Nkind (A) = N_String_Literal then
12913                   S   := Strval (A);
12914
12915                   declare
12916                      Slen    : constant Natural := Natural (String_Length (S));
12917                      Options : String (1 .. Slen);
12918                      J       : Natural;
12919
12920                   begin
12921                      J := 1;
12922                      loop
12923                         C := Get_String_Char (S, Int (J));
12924                         exit when not In_Character_Range (C);
12925                         Options (J) := Get_Character (C);
12926
12927                         --  If at end of string, set options. As per discussion
12928                         --  above, no need to check for errors, since we issued
12929                         --  them in the parser.
12930
12931                         if J = Slen then
12932                            Set_Style_Check_Options (Options);
12933                            exit;
12934                         end if;
12935
12936                         J := J + 1;
12937                      end loop;
12938                   end;
12939
12940                elsif Nkind (A) = N_Identifier then
12941                   if Chars (A) = Name_All_Checks then
12942                      if GNAT_Mode then
12943                         Set_GNAT_Style_Check_Options;
12944                      else
12945                         Set_Default_Style_Check_Options;
12946                      end if;
12947
12948                   elsif Chars (A) = Name_On then
12949                      Style_Check := True;
12950
12951                   elsif Chars (A) = Name_Off then
12952                      Style_Check := False;
12953                   end if;
12954                end if;
12955             end if;
12956          end Style_Checks;
12957
12958          --------------
12959          -- Subtitle --
12960          --------------
12961
12962          --  pragma Subtitle ([Subtitle =>] STRING_LITERAL);
12963
12964          when Pragma_Subtitle =>
12965             GNAT_Pragma;
12966             Check_Arg_Count (1);
12967             Check_Optional_Identifier (Arg1, Name_Subtitle);
12968             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
12969             Store_Note (N);
12970
12971          --------------
12972          -- Suppress --
12973          --------------
12974
12975          --  pragma Suppress (IDENTIFIER [, [On =>] NAME]);
12976
12977          when Pragma_Suppress =>
12978             Process_Suppress_Unsuppress (True);
12979
12980          ------------------
12981          -- Suppress_All --
12982          ------------------
12983
12984          --  pragma Suppress_All;
12985
12986          --  The only check made here is that the pragma has no arguments.
12987          --  There are no placement rules, and the processing required (setting
12988          --  the Has_Pragma_Suppress_All flag in the compilation unit node was
12989          --  taken care of by the parser). Process_Compilation_Unit_Pragmas
12990          --  then creates and inserts a pragma Suppress (All_Checks).
12991
12992          when Pragma_Suppress_All =>
12993             GNAT_Pragma;
12994             Check_Arg_Count (0);
12995
12996          -------------------------
12997          -- Suppress_Debug_Info --
12998          -------------------------
12999
13000          --  pragma Suppress_Debug_Info ([Entity =>] LOCAL_NAME);
13001
13002          when Pragma_Suppress_Debug_Info =>
13003             GNAT_Pragma;
13004             Check_Arg_Count (1);
13005             Check_Optional_Identifier (Arg1, Name_Entity);
13006             Check_Arg_Is_Local_Name (Arg1);
13007             Set_Debug_Info_Off (Entity (Get_Pragma_Arg (Arg1)));
13008
13009          ----------------------------------
13010          -- Suppress_Exception_Locations --
13011          ----------------------------------
13012
13013          --  pragma Suppress_Exception_Locations;
13014
13015          when Pragma_Suppress_Exception_Locations =>
13016             GNAT_Pragma;
13017             Check_Arg_Count (0);
13018             Check_Valid_Configuration_Pragma;
13019             Exception_Locations_Suppressed := True;
13020
13021          -----------------------------
13022          -- Suppress_Initialization --
13023          -----------------------------
13024
13025          --  pragma Suppress_Initialization ([Entity =>] type_Name);
13026
13027          when Pragma_Suppress_Initialization => Suppress_Init : declare
13028             E_Id : Node_Id;
13029             E    : Entity_Id;
13030
13031          begin
13032             GNAT_Pragma;
13033             Check_Arg_Count (1);
13034             Check_Optional_Identifier (Arg1, Name_Entity);
13035             Check_Arg_Is_Local_Name (Arg1);
13036
13037             E_Id := Get_Pragma_Arg (Arg1);
13038
13039             if Etype (E_Id) = Any_Type then
13040                return;
13041             end if;
13042
13043             E := Entity (E_Id);
13044
13045             if not Is_Type (E) then
13046                Error_Pragma_Arg ("pragma% requires type or subtype", Arg1);
13047             end if;
13048
13049             if Rep_Item_Too_Early (E, N)
13050                  or else
13051                Rep_Item_Too_Late (E, N, FOnly => True)
13052             then
13053                return;
13054             end if;
13055
13056             --  For incomplete/private type, set flag on full view
13057
13058             if Is_Incomplete_Or_Private_Type (E) then
13059                if No (Full_View (Base_Type (E))) then
13060                   Error_Pragma_Arg
13061                     ("argument of pragma% cannot be an incomplete type", Arg1);
13062                else
13063                   Set_Suppress_Initialization (Full_View (Base_Type (E)));
13064                end if;
13065
13066             --  For first subtype, set flag on base type
13067
13068             elsif Is_First_Subtype (E) then
13069                Set_Suppress_Initialization (Base_Type (E));
13070
13071             --  For other than first subtype, set flag on subtype itself
13072
13073             else
13074                Set_Suppress_Initialization (E);
13075             end if;
13076          end Suppress_Init;
13077
13078          -----------------
13079          -- System_Name --
13080          -----------------
13081
13082          --  pragma System_Name (DIRECT_NAME);
13083
13084          --  Syntax check: one argument, which must be the identifier GNAT or
13085          --  the identifier GCC, no other identifiers are acceptable.
13086
13087          when Pragma_System_Name =>
13088             GNAT_Pragma;
13089             Check_No_Identifiers;
13090             Check_Arg_Count (1);
13091             Check_Arg_Is_One_Of (Arg1, Name_Gcc, Name_Gnat);
13092
13093          -----------------------------
13094          -- Task_Dispatching_Policy --
13095          -----------------------------
13096
13097          --  pragma Task_Dispatching_Policy (policy_IDENTIFIER);
13098
13099          when Pragma_Task_Dispatching_Policy => declare
13100             DP : Character;
13101
13102          begin
13103             Check_Ada_83_Warning;
13104             Check_Arg_Count (1);
13105             Check_No_Identifiers;
13106             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
13107             Check_Valid_Configuration_Pragma;
13108             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
13109             DP := Fold_Upper (Name_Buffer (1));
13110
13111             if Task_Dispatching_Policy /= ' '
13112               and then Task_Dispatching_Policy /= DP
13113             then
13114                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
13115                Error_Pragma
13116                  ("task dispatching policy incompatible with policy#");
13117
13118             --  Set new policy, but always preserve System_Location since we
13119             --  like the error message with the run time name.
13120
13121             else
13122                Task_Dispatching_Policy := DP;
13123
13124                if Task_Dispatching_Policy_Sloc /= System_Location then
13125                   Task_Dispatching_Policy_Sloc := Loc;
13126                end if;
13127             end if;
13128          end;
13129
13130          ---------------
13131          -- Task_Info --
13132          ---------------
13133
13134          --  pragma Task_Info (EXPRESSION);
13135
13136          when Pragma_Task_Info => Task_Info : declare
13137             P : constant Node_Id := Parent (N);
13138
13139          begin
13140             GNAT_Pragma;
13141
13142             if Nkind (P) /= N_Task_Definition then
13143                Error_Pragma ("pragma% must appear in task definition");
13144             end if;
13145
13146             Check_No_Identifiers;
13147             Check_Arg_Count (1);
13148
13149             Analyze_And_Resolve
13150               (Get_Pragma_Arg (Arg1), RTE (RE_Task_Info_Type));
13151
13152             if Etype (Get_Pragma_Arg (Arg1)) = Any_Type then
13153                return;
13154             end if;
13155
13156             if Has_Task_Info_Pragma (P) then
13157                Error_Pragma ("duplicate pragma% not allowed");
13158             else
13159                Set_Has_Task_Info_Pragma (P, True);
13160             end if;
13161          end Task_Info;
13162
13163          ---------------
13164          -- Task_Name --
13165          ---------------
13166
13167          --  pragma Task_Name (string_EXPRESSION);
13168
13169          when Pragma_Task_Name => Task_Name : declare
13170             P   : constant Node_Id := Parent (N);
13171             Arg : Node_Id;
13172
13173          begin
13174             Check_No_Identifiers;
13175             Check_Arg_Count (1);
13176
13177             Arg := Get_Pragma_Arg (Arg1);
13178
13179             --  The expression is used in the call to Create_Task, and must be
13180             --  expanded there, not in the context of the current spec. It must
13181             --  however be analyzed to capture global references, in case it
13182             --  appears in a generic context.
13183
13184             Preanalyze_And_Resolve (Arg, Standard_String);
13185
13186             if Nkind (P) /= N_Task_Definition then
13187                Pragma_Misplaced;
13188             end if;
13189
13190             if Has_Task_Name_Pragma (P) then
13191                Error_Pragma ("duplicate pragma% not allowed");
13192             else
13193                Set_Has_Task_Name_Pragma (P, True);
13194                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
13195             end if;
13196          end Task_Name;
13197
13198          ------------------
13199          -- Task_Storage --
13200          ------------------
13201
13202          --  pragma Task_Storage (
13203          --     [Task_Type =>] LOCAL_NAME,
13204          --     [Top_Guard =>] static_integer_EXPRESSION);
13205
13206          when Pragma_Task_Storage => Task_Storage : declare
13207             Args  : Args_List (1 .. 2);
13208             Names : constant Name_List (1 .. 2) := (
13209                       Name_Task_Type,
13210                       Name_Top_Guard);
13211
13212             Task_Type : Node_Id renames Args (1);
13213             Top_Guard : Node_Id renames Args (2);
13214
13215             Ent : Entity_Id;
13216
13217          begin
13218             GNAT_Pragma;
13219             Gather_Associations (Names, Args);
13220
13221             if No (Task_Type) then
13222                Error_Pragma
13223                  ("missing task_type argument for pragma%");
13224             end if;
13225
13226             Check_Arg_Is_Local_Name (Task_Type);
13227
13228             Ent := Entity (Task_Type);
13229
13230             if not Is_Task_Type (Ent) then
13231                Error_Pragma_Arg
13232                  ("argument for pragma% must be task type", Task_Type);
13233             end if;
13234
13235             if No (Top_Guard) then
13236                Error_Pragma_Arg
13237                  ("pragma% takes two arguments", Task_Type);
13238             else
13239                Check_Arg_Is_Static_Expression (Top_Guard, Any_Integer);
13240             end if;
13241
13242             Check_First_Subtype (Task_Type);
13243
13244             if Rep_Item_Too_Late (Ent, N) then
13245                raise Pragma_Exit;
13246             end if;
13247          end Task_Storage;
13248
13249          ---------------
13250          -- Test_Case --
13251          ---------------
13252
13253          --  pragma Test_Case ([Name     =>] Static_String_EXPRESSION
13254          --                   ,[Mode     =>] MODE_TYPE
13255          --                  [, Requires =>  Boolean_EXPRESSION]
13256          --                  [, Ensures  =>  Boolean_EXPRESSION]);
13257
13258          --  MODE_TYPE ::= Normal | Robustness
13259
13260          when Pragma_Test_Case => Test_Case : declare
13261          begin
13262             GNAT_Pragma;
13263             Check_At_Least_N_Arguments (3);
13264             Check_At_Most_N_Arguments (4);
13265             Check_Arg_Order
13266                  ((Name_Name, Name_Mode, Name_Requires, Name_Ensures));
13267
13268             Check_Optional_Identifier (Arg1, Name_Name);
13269             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
13270             Check_Optional_Identifier (Arg2, Name_Mode);
13271             Check_Arg_Is_One_Of (Arg2, Name_Normal, Name_Robustness);
13272
13273             if Arg_Count = 4 then
13274                Check_Identifier (Arg3, Name_Requires);
13275                Check_Identifier (Arg4, Name_Ensures);
13276             else
13277                Check_Identifier_Is_One_Of (Arg3, Name_Requires, Name_Ensures);
13278             end if;
13279
13280             Check_Test_Case;
13281          end Test_Case;
13282
13283          --------------------------
13284          -- Thread_Local_Storage --
13285          --------------------------
13286
13287          --  pragma Thread_Local_Storage ([Entity =>] LOCAL_NAME);
13288
13289          when Pragma_Thread_Local_Storage => Thread_Local_Storage : declare
13290             Id : Node_Id;
13291             E  : Entity_Id;
13292
13293          begin
13294             GNAT_Pragma;
13295             Check_Arg_Count (1);
13296             Check_Optional_Identifier (Arg1, Name_Entity);
13297             Check_Arg_Is_Library_Level_Local_Name (Arg1);
13298
13299             Id := Get_Pragma_Arg (Arg1);
13300             Analyze (Id);
13301
13302             if not Is_Entity_Name (Id)
13303               or else Ekind (Entity (Id)) /= E_Variable
13304             then
13305                Error_Pragma_Arg ("local variable name required", Arg1);
13306             end if;
13307
13308             E := Entity (Id);
13309
13310             if Rep_Item_Too_Early (E, N)
13311               or else Rep_Item_Too_Late (E, N)
13312             then
13313                raise Pragma_Exit;
13314             end if;
13315
13316             Set_Has_Pragma_Thread_Local_Storage (E);
13317             Set_Has_Gigi_Rep_Item (E);
13318          end Thread_Local_Storage;
13319
13320          ----------------
13321          -- Time_Slice --
13322          ----------------
13323
13324          --  pragma Time_Slice (static_duration_EXPRESSION);
13325
13326          when Pragma_Time_Slice => Time_Slice : declare
13327             Val : Ureal;
13328             Nod : Node_Id;
13329
13330          begin
13331             GNAT_Pragma;
13332             Check_Arg_Count (1);
13333             Check_No_Identifiers;
13334             Check_In_Main_Program;
13335             Check_Arg_Is_Static_Expression (Arg1, Standard_Duration);
13336
13337             if not Error_Posted (Arg1) then
13338                Nod := Next (N);
13339                while Present (Nod) loop
13340                   if Nkind (Nod) = N_Pragma
13341                     and then Pragma_Name (Nod) = Name_Time_Slice
13342                   then
13343                      Error_Msg_Name_1 := Pname;
13344                      Error_Msg_N ("duplicate pragma% not permitted", Nod);
13345                   end if;
13346
13347                   Next (Nod);
13348                end loop;
13349             end if;
13350
13351             --  Process only if in main unit
13352
13353             if Get_Source_Unit (Loc) = Main_Unit then
13354                Opt.Time_Slice_Set := True;
13355                Val := Expr_Value_R (Get_Pragma_Arg (Arg1));
13356
13357                if Val <= Ureal_0 then
13358                   Opt.Time_Slice_Value := 0;
13359
13360                elsif Val > UR_From_Uint (UI_From_Int (1000)) then
13361                   Opt.Time_Slice_Value := 1_000_000_000;
13362
13363                else
13364                   Opt.Time_Slice_Value :=
13365                     UI_To_Int (UR_To_Uint (Val * UI_From_Int (1_000_000)));
13366                end if;
13367             end if;
13368          end Time_Slice;
13369
13370          -----------
13371          -- Title --
13372          -----------
13373
13374          --  pragma Title (TITLING_OPTION [, TITLING OPTION]);
13375
13376          --   TITLING_OPTION ::=
13377          --     [Title =>] STRING_LITERAL
13378          --   | [Subtitle =>] STRING_LITERAL
13379
13380          when Pragma_Title => Title : declare
13381             Args  : Args_List (1 .. 2);
13382             Names : constant Name_List (1 .. 2) := (
13383                       Name_Title,
13384                       Name_Subtitle);
13385
13386          begin
13387             GNAT_Pragma;
13388             Gather_Associations (Names, Args);
13389             Store_Note (N);
13390
13391             for J in 1 .. 2 loop
13392                if Present (Args (J)) then
13393                   Check_Arg_Is_Static_Expression (Args (J), Standard_String);
13394                end if;
13395             end loop;
13396          end Title;
13397
13398          ---------------------
13399          -- Unchecked_Union --
13400          ---------------------
13401
13402          --  pragma Unchecked_Union (first_subtype_LOCAL_NAME)
13403
13404          when Pragma_Unchecked_Union => Unchecked_Union : declare
13405             Assoc   : constant Node_Id := Arg1;
13406             Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
13407             Typ     : Entity_Id;
13408             Discr   : Entity_Id;
13409             Tdef    : Node_Id;
13410             Clist   : Node_Id;
13411             Vpart   : Node_Id;
13412             Comp    : Node_Id;
13413             Variant : Node_Id;
13414
13415          begin
13416             Ada_2005_Pragma;
13417             Check_No_Identifiers;
13418             Check_Arg_Count (1);
13419             Check_Arg_Is_Local_Name (Arg1);
13420
13421             Find_Type (Type_Id);
13422             Typ := Entity (Type_Id);
13423
13424             if Typ = Any_Type
13425               or else Rep_Item_Too_Early (Typ, N)
13426             then
13427                return;
13428             else
13429                Typ := Underlying_Type (Typ);
13430             end if;
13431
13432             if Rep_Item_Too_Late (Typ, N) then
13433                return;
13434             end if;
13435
13436             Check_First_Subtype (Arg1);
13437
13438             --  Note remaining cases are references to a type in the current
13439             --  declarative part. If we find an error, we post the error on
13440             --  the relevant type declaration at an appropriate point.
13441
13442             if not Is_Record_Type (Typ) then
13443                Error_Msg_N ("Unchecked_Union must be record type", Typ);
13444                return;
13445
13446             elsif Is_Tagged_Type (Typ) then
13447                Error_Msg_N ("Unchecked_Union must not be tagged", Typ);
13448                return;
13449
13450             elsif Is_Limited_Type (Typ) then
13451                Error_Msg_N
13452                  ("Unchecked_Union must not be limited record type", Typ);
13453                Explain_Limited_Type (Typ, Typ);
13454                return;
13455
13456             else
13457                if not Has_Discriminants (Typ) then
13458                   Error_Msg_N
13459                     ("Unchecked_Union must have one discriminant", Typ);
13460                   return;
13461                end if;
13462
13463                Discr := First_Discriminant (Typ);
13464                while Present (Discr) loop
13465                   if No (Discriminant_Default_Value (Discr)) then
13466                      Error_Msg_N
13467                        ("Unchecked_Union discriminant must have default value",
13468                         Discr);
13469                   end if;
13470
13471                   Next_Discriminant (Discr);
13472                end loop;
13473
13474                Tdef  := Type_Definition (Declaration_Node (Typ));
13475                Clist := Component_List (Tdef);
13476
13477                Comp := First (Component_Items (Clist));
13478                while Present (Comp) loop
13479                   Check_Component (Comp, Typ);
13480                   Next (Comp);
13481                end loop;
13482
13483                if No (Clist) or else No (Variant_Part (Clist)) then
13484                   Error_Msg_N
13485                     ("Unchecked_Union must have variant part",
13486                      Tdef);
13487                   return;
13488                end if;
13489
13490                Vpart := Variant_Part (Clist);
13491
13492                Variant := First (Variants (Vpart));
13493                while Present (Variant) loop
13494                   Check_Variant (Variant, Typ);
13495                   Next (Variant);
13496                end loop;
13497             end if;
13498
13499             Set_Is_Unchecked_Union  (Typ);
13500             Set_Convention (Typ, Convention_C);
13501             Set_Has_Unchecked_Union (Base_Type (Typ));
13502             Set_Is_Unchecked_Union  (Base_Type (Typ));
13503          end Unchecked_Union;
13504
13505          ------------------------
13506          -- Unimplemented_Unit --
13507          ------------------------
13508
13509          --  pragma Unimplemented_Unit;
13510
13511          --  Note: this only gives an error if we are generating code, or if
13512          --  we are in a generic library unit (where the pragma appears in the
13513          --  body, not in the spec).
13514
13515          when Pragma_Unimplemented_Unit => Unimplemented_Unit : declare
13516             Cunitent : constant Entity_Id :=
13517                          Cunit_Entity (Get_Source_Unit (Loc));
13518             Ent_Kind : constant Entity_Kind :=
13519                          Ekind (Cunitent);
13520
13521          begin
13522             GNAT_Pragma;
13523             Check_Arg_Count (0);
13524
13525             if Operating_Mode = Generate_Code
13526               or else Ent_Kind = E_Generic_Function
13527               or else Ent_Kind = E_Generic_Procedure
13528               or else Ent_Kind = E_Generic_Package
13529             then
13530                Get_Name_String (Chars (Cunitent));
13531                Set_Casing (Mixed_Case);
13532                Write_Str (Name_Buffer (1 .. Name_Len));
13533                Write_Str (" is not supported in this configuration");
13534                Write_Eol;
13535                raise Unrecoverable_Error;
13536             end if;
13537          end Unimplemented_Unit;
13538
13539          ------------------------
13540          -- Universal_Aliasing --
13541          ------------------------
13542
13543          --  pragma Universal_Aliasing [([Entity =>] type_LOCAL_NAME)];
13544
13545          when Pragma_Universal_Aliasing => Universal_Alias : declare
13546             E_Id : Entity_Id;
13547
13548          begin
13549             GNAT_Pragma;
13550             Check_Arg_Count (1);
13551             Check_Optional_Identifier (Arg2, Name_Entity);
13552             Check_Arg_Is_Local_Name (Arg1);
13553             E_Id := Entity (Get_Pragma_Arg (Arg1));
13554
13555             if E_Id = Any_Type then
13556                return;
13557             elsif No (E_Id) or else not Is_Type (E_Id) then
13558                Error_Pragma_Arg ("pragma% requires type", Arg1);
13559             end if;
13560
13561             Set_Universal_Aliasing (Implementation_Base_Type (E_Id));
13562          end Universal_Alias;
13563
13564          --------------------
13565          -- Universal_Data --
13566          --------------------
13567
13568          --  pragma Universal_Data [(library_unit_NAME)];
13569
13570          when Pragma_Universal_Data =>
13571             GNAT_Pragma;
13572
13573             --  If this is a configuration pragma, then set the universal
13574             --  addressing option, otherwise confirm that the pragma satisfies
13575             --  the requirements of library unit pragma placement and leave it
13576             --  to the GNAAMP back end to detect the pragma (avoids transitive
13577             --  setting of the option due to withed units).
13578
13579             if Is_Configuration_Pragma then
13580                Universal_Addressing_On_AAMP := True;
13581             else
13582                Check_Valid_Library_Unit_Pragma;
13583             end if;
13584
13585             if not AAMP_On_Target then
13586                Error_Pragma ("?pragma% ignored (applies only to AAMP)");
13587             end if;
13588
13589          ----------------
13590          -- Unmodified --
13591          ----------------
13592
13593          --  pragma Unmodified (local_Name {, local_Name});
13594
13595          when Pragma_Unmodified => Unmodified : declare
13596             Arg_Node : Node_Id;
13597             Arg_Expr : Node_Id;
13598             Arg_Ent  : Entity_Id;
13599
13600          begin
13601             GNAT_Pragma;
13602             Check_At_Least_N_Arguments (1);
13603
13604             --  Loop through arguments
13605
13606             Arg_Node := Arg1;
13607             while Present (Arg_Node) loop
13608                Check_No_Identifier (Arg_Node);
13609
13610                --  Note: the analyze call done by Check_Arg_Is_Local_Name will
13611                --  in fact generate reference, so that the entity will have a
13612                --  reference, which will inhibit any warnings about it not
13613                --  being referenced, and also properly show up in the ali file
13614                --  as a reference. But this reference is recorded before the
13615                --  Has_Pragma_Unreferenced flag is set, so that no warning is
13616                --  generated for this reference.
13617
13618                Check_Arg_Is_Local_Name (Arg_Node);
13619                Arg_Expr := Get_Pragma_Arg (Arg_Node);
13620
13621                if Is_Entity_Name (Arg_Expr) then
13622                   Arg_Ent := Entity (Arg_Expr);
13623
13624                   if not Is_Assignable (Arg_Ent) then
13625                      Error_Pragma_Arg
13626                        ("pragma% can only be applied to a variable",
13627                         Arg_Expr);
13628                   else
13629                      Set_Has_Pragma_Unmodified (Arg_Ent);
13630                   end if;
13631                end if;
13632
13633                Next (Arg_Node);
13634             end loop;
13635          end Unmodified;
13636
13637          ------------------
13638          -- Unreferenced --
13639          ------------------
13640
13641          --  pragma Unreferenced (local_Name {, local_Name});
13642
13643          --    or when used in a context clause:
13644
13645          --  pragma Unreferenced (library_unit_NAME {, library_unit_NAME}
13646
13647          when Pragma_Unreferenced => Unreferenced : declare
13648             Arg_Node : Node_Id;
13649             Arg_Expr : Node_Id;
13650             Arg_Ent  : Entity_Id;
13651             Citem    : Node_Id;
13652
13653          begin
13654             GNAT_Pragma;
13655             Check_At_Least_N_Arguments (1);
13656
13657             --  Check case of appearing within context clause
13658
13659             if Is_In_Context_Clause then
13660
13661                --  The arguments must all be units mentioned in a with clause
13662                --  in the same context clause. Note we already checked (in
13663                --  Par.Prag) that the arguments are either identifiers or
13664                --  selected components.
13665
13666                Arg_Node := Arg1;
13667                while Present (Arg_Node) loop
13668                   Citem := First (List_Containing (N));
13669                   while Citem /= N loop
13670                      if Nkind (Citem) = N_With_Clause
13671                        and then
13672                          Same_Name (Name (Citem), Get_Pragma_Arg (Arg_Node))
13673                      then
13674                         Set_Has_Pragma_Unreferenced
13675                           (Cunit_Entity
13676                              (Get_Source_Unit
13677                                 (Library_Unit (Citem))));
13678                         Set_Unit_Name
13679                           (Get_Pragma_Arg (Arg_Node), Name (Citem));
13680                         exit;
13681                      end if;
13682
13683                      Next (Citem);
13684                   end loop;
13685
13686                   if Citem = N then
13687                      Error_Pragma_Arg
13688                        ("argument of pragma% is not with'ed unit", Arg_Node);
13689                   end if;
13690
13691                   Next (Arg_Node);
13692                end loop;
13693
13694             --  Case of not in list of context items
13695
13696             else
13697                Arg_Node := Arg1;
13698                while Present (Arg_Node) loop
13699                   Check_No_Identifier (Arg_Node);
13700
13701                   --  Note: the analyze call done by Check_Arg_Is_Local_Name
13702                   --  will in fact generate reference, so that the entity will
13703                   --  have a reference, which will inhibit any warnings about
13704                   --  it not being referenced, and also properly show up in the
13705                   --  ali file as a reference. But this reference is recorded
13706                   --  before the Has_Pragma_Unreferenced flag is set, so that
13707                   --  no warning is generated for this reference.
13708
13709                   Check_Arg_Is_Local_Name (Arg_Node);
13710                   Arg_Expr := Get_Pragma_Arg (Arg_Node);
13711
13712                   if Is_Entity_Name (Arg_Expr) then
13713                      Arg_Ent := Entity (Arg_Expr);
13714
13715                      --  If the entity is overloaded, the pragma applies to the
13716                      --  most recent overloading, as documented. In this case,
13717                      --  name resolution does not generate a reference, so it
13718                      --  must be done here explicitly.
13719
13720                      if Is_Overloaded (Arg_Expr) then
13721                         Generate_Reference (Arg_Ent, N);
13722                      end if;
13723
13724                      Set_Has_Pragma_Unreferenced (Arg_Ent);
13725                   end if;
13726
13727                   Next (Arg_Node);
13728                end loop;
13729             end if;
13730          end Unreferenced;
13731
13732          --------------------------
13733          -- Unreferenced_Objects --
13734          --------------------------
13735
13736          --  pragma Unreferenced_Objects (local_Name {, local_Name});
13737
13738          when Pragma_Unreferenced_Objects => Unreferenced_Objects : declare
13739             Arg_Node : Node_Id;
13740             Arg_Expr : Node_Id;
13741
13742          begin
13743             GNAT_Pragma;
13744             Check_At_Least_N_Arguments (1);
13745
13746             Arg_Node := Arg1;
13747             while Present (Arg_Node) loop
13748                Check_No_Identifier (Arg_Node);
13749                Check_Arg_Is_Local_Name (Arg_Node);
13750                Arg_Expr := Get_Pragma_Arg (Arg_Node);
13751
13752                if not Is_Entity_Name (Arg_Expr)
13753                  or else not Is_Type (Entity (Arg_Expr))
13754                then
13755                   Error_Pragma_Arg
13756                     ("argument for pragma% must be type or subtype", Arg_Node);
13757                end if;
13758
13759                Set_Has_Pragma_Unreferenced_Objects (Entity (Arg_Expr));
13760                Next (Arg_Node);
13761             end loop;
13762          end Unreferenced_Objects;
13763
13764          ------------------------------
13765          -- Unreserve_All_Interrupts --
13766          ------------------------------
13767
13768          --  pragma Unreserve_All_Interrupts;
13769
13770          when Pragma_Unreserve_All_Interrupts =>
13771             GNAT_Pragma;
13772             Check_Arg_Count (0);
13773
13774             if In_Extended_Main_Code_Unit (Main_Unit_Entity) then
13775                Unreserve_All_Interrupts := True;
13776             end if;
13777
13778          ----------------
13779          -- Unsuppress --
13780          ----------------
13781
13782          --  pragma Unsuppress (IDENTIFIER [, [On =>] NAME]);
13783
13784          when Pragma_Unsuppress =>
13785             Ada_2005_Pragma;
13786             Process_Suppress_Unsuppress (False);
13787
13788          -------------------
13789          -- Use_VADS_Size --
13790          -------------------
13791
13792          --  pragma Use_VADS_Size;
13793
13794          when Pragma_Use_VADS_Size =>
13795             GNAT_Pragma;
13796             Check_Arg_Count (0);
13797             Check_Valid_Configuration_Pragma;
13798             Use_VADS_Size := True;
13799
13800          ---------------------
13801          -- Validity_Checks --
13802          ---------------------
13803
13804          --  pragma Validity_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
13805
13806          when Pragma_Validity_Checks => Validity_Checks : declare
13807             A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
13808             S  : String_Id;
13809             C  : Char_Code;
13810
13811          begin
13812             GNAT_Pragma;
13813             Check_Arg_Count (1);
13814             Check_No_Identifiers;
13815
13816             if Nkind (A) = N_String_Literal then
13817                S   := Strval (A);
13818
13819                declare
13820                   Slen    : constant Natural := Natural (String_Length (S));
13821                   Options : String (1 .. Slen);
13822                   J       : Natural;
13823
13824                begin
13825                   J := 1;
13826                   loop
13827                      C := Get_String_Char (S, Int (J));
13828                      exit when not In_Character_Range (C);
13829                      Options (J) := Get_Character (C);
13830
13831                      if J = Slen then
13832                         Set_Validity_Check_Options (Options);
13833                         exit;
13834                      else
13835                         J := J + 1;
13836                      end if;
13837                   end loop;
13838                end;
13839
13840             elsif Nkind (A) = N_Identifier then
13841
13842                if Chars (A) = Name_All_Checks then
13843                   Set_Validity_Check_Options ("a");
13844
13845                elsif Chars (A) = Name_On then
13846                   Validity_Checks_On := True;
13847
13848                elsif Chars (A) = Name_Off then
13849                   Validity_Checks_On := False;
13850
13851                end if;
13852             end if;
13853          end Validity_Checks;
13854
13855          --------------
13856          -- Volatile --
13857          --------------
13858
13859          --  pragma Volatile (LOCAL_NAME);
13860
13861          when Pragma_Volatile =>
13862             Process_Atomic_Shared_Volatile;
13863
13864          -------------------------
13865          -- Volatile_Components --
13866          -------------------------
13867
13868          --  pragma Volatile_Components (array_LOCAL_NAME);
13869
13870          --  Volatile is handled by the same circuit as Atomic_Components
13871
13872          --------------
13873          -- Warnings --
13874          --------------
13875
13876          --  pragma Warnings (On | Off);
13877          --  pragma Warnings (On | Off, LOCAL_NAME);
13878          --  pragma Warnings (static_string_EXPRESSION);
13879          --  pragma Warnings (On | Off, STRING_LITERAL);
13880
13881          when Pragma_Warnings => Warnings : begin
13882             GNAT_Pragma;
13883             Check_At_Least_N_Arguments (1);
13884             Check_No_Identifiers;
13885
13886             --  If debug flag -gnatd.i is set, pragma is ignored
13887
13888             if Debug_Flag_Dot_I then
13889                return;
13890             end if;
13891
13892             --  Process various forms of the pragma
13893
13894             declare
13895                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
13896
13897             begin
13898                --  One argument case
13899
13900                if Arg_Count = 1 then
13901
13902                   --  On/Off one argument case was processed by parser
13903
13904                   if Nkind (Argx) = N_Identifier
13905                     and then
13906                       (Chars (Argx) = Name_On
13907                          or else
13908                        Chars (Argx) = Name_Off)
13909                   then
13910                      null;
13911
13912                   --  One argument case must be ON/OFF or static string expr
13913
13914                   elsif not Is_Static_String_Expression (Arg1) then
13915                      Error_Pragma_Arg
13916                        ("argument of pragma% must be On/Off or " &
13917                         "static string expression", Arg1);
13918
13919                   --  One argument string expression case
13920
13921                   else
13922                      declare
13923                         Lit : constant Node_Id   := Expr_Value_S (Argx);
13924                         Str : constant String_Id := Strval (Lit);
13925                         Len : constant Nat       := String_Length (Str);
13926                         C   : Char_Code;
13927                         J   : Nat;
13928                         OK  : Boolean;
13929                         Chr : Character;
13930
13931                      begin
13932                         J := 1;
13933                         while J <= Len loop
13934                            C := Get_String_Char (Str, J);
13935                            OK := In_Character_Range (C);
13936
13937                            if OK then
13938                               Chr := Get_Character (C);
13939
13940                               --  Dot case
13941
13942                               if J < Len and then Chr = '.' then
13943                                  J := J + 1;
13944                                  C := Get_String_Char (Str, J);
13945                                  Chr := Get_Character (C);
13946
13947                                  if not Set_Dot_Warning_Switch (Chr) then
13948                                     Error_Pragma_Arg
13949                                       ("invalid warning switch character " &
13950                                        '.' & Chr, Arg1);
13951                                  end if;
13952
13953                               --  Non-Dot case
13954
13955                               else
13956                                  OK := Set_Warning_Switch (Chr);
13957                               end if;
13958                            end if;
13959
13960                            if not OK then
13961                               Error_Pragma_Arg
13962                                 ("invalid warning switch character " & Chr,
13963                                  Arg1);
13964                            end if;
13965
13966                            J := J + 1;
13967                         end loop;
13968                      end;
13969                   end if;
13970
13971                   --  Two or more arguments (must be two)
13972
13973                else
13974                   Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
13975                   Check_At_Most_N_Arguments (2);
13976
13977                   declare
13978                      E_Id : Node_Id;
13979                      E    : Entity_Id;
13980                      Err  : Boolean;
13981
13982                   begin
13983                      E_Id := Get_Pragma_Arg (Arg2);
13984                      Analyze (E_Id);
13985
13986                      --  In the expansion of an inlined body, a reference to
13987                      --  the formal may be wrapped in a conversion if the
13988                      --  actual is a conversion. Retrieve the real entity name.
13989
13990                      if (In_Instance_Body
13991                          or else In_Inlined_Body)
13992                        and then Nkind (E_Id) = N_Unchecked_Type_Conversion
13993                      then
13994                         E_Id := Expression (E_Id);
13995                      end if;
13996
13997                      --  Entity name case
13998
13999                      if Is_Entity_Name (E_Id) then
14000                         E := Entity (E_Id);
14001
14002                         if E = Any_Id then
14003                            return;
14004                         else
14005                            loop
14006                               Set_Warnings_Off
14007                                 (E, (Chars (Get_Pragma_Arg (Arg1)) =
14008                                                               Name_Off));
14009
14010                               if Chars (Get_Pragma_Arg (Arg1)) = Name_Off
14011                                 and then Warn_On_Warnings_Off
14012                               then
14013                                  Warnings_Off_Pragmas.Append ((N, E));
14014                               end if;
14015
14016                               if Is_Enumeration_Type (E) then
14017                                  declare
14018                                     Lit : Entity_Id;
14019                                  begin
14020                                     Lit := First_Literal (E);
14021                                     while Present (Lit) loop
14022                                        Set_Warnings_Off (Lit);
14023                                        Next_Literal (Lit);
14024                                     end loop;
14025                                  end;
14026                               end if;
14027
14028                               exit when No (Homonym (E));
14029                               E := Homonym (E);
14030                            end loop;
14031                         end if;
14032
14033                      --  Error if not entity or static string literal case
14034
14035                      elsif not Is_Static_String_Expression (Arg2) then
14036                         Error_Pragma_Arg
14037                           ("second argument of pragma% must be entity " &
14038                            "name or static string expression", Arg2);
14039
14040                      --  String literal case
14041
14042                      else
14043                         String_To_Name_Buffer
14044                           (Strval (Expr_Value_S (Get_Pragma_Arg (Arg2))));
14045
14046                         --  Note on configuration pragma case: If this is a
14047                         --  configuration pragma, then for an OFF pragma, we
14048                         --  just set Config True in the call, which is all
14049                         --  that needs to be done. For the case of ON, this
14050                         --  is normally an error, unless it is canceling the
14051                         --  effect of a previous OFF pragma in the same file.
14052                         --  In any other case, an error will be signalled (ON
14053                         --  with no matching OFF).
14054
14055                         if Chars (Argx) = Name_Off then
14056                            Set_Specific_Warning_Off
14057                              (Loc, Name_Buffer (1 .. Name_Len),
14058                               Config => Is_Configuration_Pragma);
14059
14060                         elsif Chars (Argx) = Name_On then
14061                            Set_Specific_Warning_On
14062                              (Loc, Name_Buffer (1 .. Name_Len), Err);
14063
14064                            if Err then
14065                               Error_Msg
14066                                 ("?pragma Warnings On with no " &
14067                                  "matching Warnings Off",
14068                                  Loc);
14069                            end if;
14070                         end if;
14071                      end if;
14072                   end;
14073                end if;
14074             end;
14075          end Warnings;
14076
14077          -------------------
14078          -- Weak_External --
14079          -------------------
14080
14081          --  pragma Weak_External ([Entity =>] LOCAL_NAME);
14082
14083          when Pragma_Weak_External => Weak_External : declare
14084             Ent : Entity_Id;
14085
14086          begin
14087             GNAT_Pragma;
14088             Check_Arg_Count (1);
14089             Check_Optional_Identifier (Arg1, Name_Entity);
14090             Check_Arg_Is_Library_Level_Local_Name (Arg1);
14091             Ent := Entity (Get_Pragma_Arg (Arg1));
14092
14093             if Rep_Item_Too_Early (Ent, N) then
14094                return;
14095             else
14096                Ent := Underlying_Type (Ent);
14097             end if;
14098
14099             --  The only processing required is to link this item on to the
14100             --  list of rep items for the given entity. This is accomplished
14101             --  by the call to Rep_Item_Too_Late (when no error is detected
14102             --  and False is returned).
14103
14104             if Rep_Item_Too_Late (Ent, N) then
14105                return;
14106             else
14107                Set_Has_Gigi_Rep_Item (Ent);
14108             end if;
14109          end Weak_External;
14110
14111          -----------------------------
14112          -- Wide_Character_Encoding --
14113          -----------------------------
14114
14115          --  pragma Wide_Character_Encoding (IDENTIFIER);
14116
14117          when Pragma_Wide_Character_Encoding =>
14118             GNAT_Pragma;
14119
14120             --  Nothing to do, handled in parser. Note that we do not enforce
14121             --  configuration pragma placement, this pragma can appear at any
14122             --  place in the source, allowing mixed encodings within a single
14123             --  source program.
14124
14125             null;
14126
14127          --------------------
14128          -- Unknown_Pragma --
14129          --------------------
14130
14131          --  Should be impossible, since the case of an unknown pragma is
14132          --  separately processed before the case statement is entered.
14133
14134          when Unknown_Pragma =>
14135             raise Program_Error;
14136       end case;
14137
14138       --  AI05-0144: detect dangerous order dependence. Disabled for now,
14139       --  until AI is formally approved.
14140
14141       --  Check_Order_Dependence;
14142
14143    exception
14144       when Pragma_Exit => null;
14145    end Analyze_Pragma;
14146
14147    -----------------------------
14148    -- Analyze_TC_In_Decl_Part --
14149    -----------------------------
14150
14151    procedure Analyze_TC_In_Decl_Part (N : Node_Id; S : Entity_Id) is
14152    begin
14153       --  Install formals and push subprogram spec onto scope stack so that we
14154       --  can see the formals from the pragma.
14155
14156       Install_Formals (S);
14157       Push_Scope (S);
14158
14159       --  Preanalyze the boolean expressions, we treat these as spec
14160       --  expressions (i.e. similar to a default expression).
14161
14162       Preanalyze_TC_Args (Get_Requires_From_Test_Case_Pragma (N),
14163                           Get_Ensures_From_Test_Case_Pragma (N));
14164
14165       --  Remove the subprogram from the scope stack now that the pre-analysis
14166       --  of the expressions in the test-case is done.
14167
14168       End_Scope;
14169    end Analyze_TC_In_Decl_Part;
14170
14171    -------------------
14172    -- Check_Enabled --
14173    -------------------
14174
14175    function Check_Enabled (Nam : Name_Id) return Boolean is
14176       PP : Node_Id;
14177
14178    begin
14179       --  Loop through entries in check policy list
14180
14181       PP := Opt.Check_Policy_List;
14182       loop
14183          --  If there are no specific entries that matched, then we let the
14184          --  setting of assertions govern. Note that this provides the needed
14185          --  compatibility with the RM for the cases of assertion, invariant,
14186          --  precondition, predicate, and postcondition.
14187
14188          if No (PP) then
14189             return Assertions_Enabled;
14190
14191          --  Here we have an entry see if it matches
14192
14193          else
14194             declare
14195                PPA : constant List_Id := Pragma_Argument_Associations (PP);
14196
14197             begin
14198                if Nam = Chars (Get_Pragma_Arg (First (PPA))) then
14199                   case (Chars (Get_Pragma_Arg (Last (PPA)))) is
14200                      when Name_On | Name_Check =>
14201                         return True;
14202                      when Name_Off | Name_Ignore =>
14203                         return False;
14204                      when others =>
14205                         raise Program_Error;
14206                   end case;
14207
14208                else
14209                   PP := Next_Pragma (PP);
14210                end if;
14211             end;
14212          end if;
14213       end loop;
14214    end Check_Enabled;
14215
14216    ---------------------------------
14217    -- Delay_Config_Pragma_Analyze --
14218    ---------------------------------
14219
14220    function Delay_Config_Pragma_Analyze (N : Node_Id) return Boolean is
14221    begin
14222       return Pragma_Name (N) = Name_Interrupt_State
14223                or else
14224              Pragma_Name (N) = Name_Priority_Specific_Dispatching;
14225    end Delay_Config_Pragma_Analyze;
14226
14227    -------------------------
14228    -- Get_Base_Subprogram --
14229    -------------------------
14230
14231    function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id is
14232       Result : Entity_Id;
14233
14234    begin
14235       --  Follow subprogram renaming chain
14236
14237       Result := Def_Id;
14238       while Is_Subprogram (Result)
14239         and then
14240           Nkind (Parent (Declaration_Node (Result))) =
14241                                          N_Subprogram_Renaming_Declaration
14242         and then Present (Alias (Result))
14243       loop
14244          Result := Alias (Result);
14245       end loop;
14246
14247       return Result;
14248    end Get_Base_Subprogram;
14249
14250    ----------------
14251    -- Initialize --
14252    ----------------
14253
14254    procedure Initialize is
14255    begin
14256       Externals.Init;
14257    end Initialize;
14258
14259    -----------------------------
14260    -- Is_Config_Static_String --
14261    -----------------------------
14262
14263    function Is_Config_Static_String (Arg : Node_Id) return Boolean is
14264
14265       function Add_Config_Static_String (Arg : Node_Id) return Boolean;
14266       --  This is an internal recursive function that is just like the outer
14267       --  function except that it adds the string to the name buffer rather
14268       --  than placing the string in the name buffer.
14269
14270       ------------------------------
14271       -- Add_Config_Static_String --
14272       ------------------------------
14273
14274       function Add_Config_Static_String (Arg : Node_Id) return Boolean is
14275          N : Node_Id;
14276          C : Char_Code;
14277
14278       begin
14279          N := Arg;
14280
14281          if Nkind (N) = N_Op_Concat then
14282             if Add_Config_Static_String (Left_Opnd (N)) then
14283                N := Right_Opnd (N);
14284             else
14285                return False;
14286             end if;
14287          end if;
14288
14289          if Nkind (N) /= N_String_Literal then
14290             Error_Msg_N ("string literal expected for pragma argument", N);
14291             return False;
14292
14293          else
14294             for J in 1 .. String_Length (Strval (N)) loop
14295                C := Get_String_Char (Strval (N), J);
14296
14297                if not In_Character_Range (C) then
14298                   Error_Msg
14299                     ("string literal contains invalid wide character",
14300                      Sloc (N) + 1 + Source_Ptr (J));
14301                   return False;
14302                end if;
14303
14304                Add_Char_To_Name_Buffer (Get_Character (C));
14305             end loop;
14306          end if;
14307
14308          return True;
14309       end Add_Config_Static_String;
14310
14311    --  Start of processing for Is_Config_Static_String
14312
14313    begin
14314
14315       Name_Len := 0;
14316       return Add_Config_Static_String (Arg);
14317    end Is_Config_Static_String;
14318
14319    -----------------------------------------
14320    -- Is_Non_Significant_Pragma_Reference --
14321    -----------------------------------------
14322
14323    --  This function makes use of the following static table which indicates
14324    --  whether a given pragma is significant.
14325
14326    --  -1  indicates that references in any argument position are significant
14327    --  0   indicates that appearance in any argument is not significant
14328    --  +n  indicates that appearance as argument n is significant, but all
14329    --      other arguments are not significant
14330    --  99  special processing required (e.g. for pragma Check)
14331
14332    Sig_Flags : constant array (Pragma_Id) of Int :=
14333      (Pragma_AST_Entry                     => -1,
14334       Pragma_Abort_Defer                   => -1,
14335       Pragma_Ada_83                        => -1,
14336       Pragma_Ada_95                        => -1,
14337       Pragma_Ada_05                        => -1,
14338       Pragma_Ada_2005                      => -1,
14339       Pragma_Ada_12                        => -1,
14340       Pragma_Ada_2012                      => -1,
14341       Pragma_All_Calls_Remote              => -1,
14342       Pragma_Annotate                      => -1,
14343       Pragma_Assert                        => -1,
14344       Pragma_Assertion_Policy              =>  0,
14345       Pragma_Assume_No_Invalid_Values      =>  0,
14346       Pragma_Asynchronous                  => -1,
14347       Pragma_Atomic                        =>  0,
14348       Pragma_Atomic_Components             =>  0,
14349       Pragma_Attach_Handler                => -1,
14350       Pragma_Check                         => 99,
14351       Pragma_Check_Name                    =>  0,
14352       Pragma_Check_Policy                  =>  0,
14353       Pragma_CIL_Constructor               => -1,
14354       Pragma_CPP_Class                     =>  0,
14355       Pragma_CPP_Constructor               =>  0,
14356       Pragma_CPP_Virtual                   =>  0,
14357       Pragma_CPP_Vtable                    =>  0,
14358       Pragma_CPU                           => -1,
14359       Pragma_C_Pass_By_Copy                =>  0,
14360       Pragma_Comment                       =>  0,
14361       Pragma_Common_Object                 => -1,
14362       Pragma_Compile_Time_Error            => -1,
14363       Pragma_Compile_Time_Warning          => -1,
14364       Pragma_Compiler_Unit                 =>  0,
14365       Pragma_Complete_Representation       =>  0,
14366       Pragma_Complex_Representation        =>  0,
14367       Pragma_Component_Alignment           => -1,
14368       Pragma_Controlled                    =>  0,
14369       Pragma_Convention                    =>  0,
14370       Pragma_Convention_Identifier         =>  0,
14371       Pragma_Debug                         => -1,
14372       Pragma_Debug_Policy                  =>  0,
14373       Pragma_Detect_Blocking               => -1,
14374       Pragma_Default_Storage_Pool          => -1,
14375       Pragma_Dimension                     => -1,
14376       Pragma_Discard_Names                 =>  0,
14377       Pragma_Elaborate                     => -1,
14378       Pragma_Elaborate_All                 => -1,
14379       Pragma_Elaborate_Body                => -1,
14380       Pragma_Elaboration_Checks            => -1,
14381       Pragma_Eliminate                     => -1,
14382       Pragma_Export                        => -1,
14383       Pragma_Export_Exception              => -1,
14384       Pragma_Export_Function               => -1,
14385       Pragma_Export_Object                 => -1,
14386       Pragma_Export_Procedure              => -1,
14387       Pragma_Export_Value                  => -1,
14388       Pragma_Export_Valued_Procedure       => -1,
14389       Pragma_Extend_System                 => -1,
14390       Pragma_Extensions_Allowed            => -1,
14391       Pragma_External                      => -1,
14392       Pragma_Favor_Top_Level               => -1,
14393       Pragma_External_Name_Casing          => -1,
14394       Pragma_Fast_Math                     => -1,
14395       Pragma_Finalize_Storage_Only         =>  0,
14396       Pragma_Float_Representation          =>  0,
14397       Pragma_Ident                         => -1,
14398       Pragma_Implemented                   => -1,
14399       Pragma_Implicit_Packing              =>  0,
14400       Pragma_Import                        => +2,
14401       Pragma_Import_Exception              =>  0,
14402       Pragma_Import_Function               =>  0,
14403       Pragma_Import_Object                 =>  0,
14404       Pragma_Import_Procedure              =>  0,
14405       Pragma_Import_Valued_Procedure       =>  0,
14406       Pragma_Independent                   =>  0,
14407       Pragma_Independent_Components        =>  0,
14408       Pragma_Initialize_Scalars            => -1,
14409       Pragma_Inline                        =>  0,
14410       Pragma_Inline_Always                 =>  0,
14411       Pragma_Inline_Generic                =>  0,
14412       Pragma_Inspection_Point              => -1,
14413       Pragma_Interface                     => +2,
14414       Pragma_Interface_Name                => +2,
14415       Pragma_Interrupt_Handler             => -1,
14416       Pragma_Interrupt_Priority            => -1,
14417       Pragma_Interrupt_State               => -1,
14418       Pragma_Invariant                     => -1,
14419       Pragma_Java_Constructor              => -1,
14420       Pragma_Java_Interface                => -1,
14421       Pragma_Keep_Names                    =>  0,
14422       Pragma_License                       => -1,
14423       Pragma_Link_With                     => -1,
14424       Pragma_Linker_Alias                  => -1,
14425       Pragma_Linker_Constructor            => -1,
14426       Pragma_Linker_Destructor             => -1,
14427       Pragma_Linker_Options                => -1,
14428       Pragma_Linker_Section                => -1,
14429       Pragma_List                          => -1,
14430       Pragma_Locking_Policy                => -1,
14431       Pragma_Long_Float                    => -1,
14432       Pragma_Machine_Attribute             => -1,
14433       Pragma_Main                          => -1,
14434       Pragma_Main_Storage                  => -1,
14435       Pragma_Memory_Size                   => -1,
14436       Pragma_No_Return                     =>  0,
14437       Pragma_No_Body                       =>  0,
14438       Pragma_No_Run_Time                   => -1,
14439       Pragma_No_Strict_Aliasing            => -1,
14440       Pragma_Normalize_Scalars             => -1,
14441       Pragma_Obsolescent                   =>  0,
14442       Pragma_Optimize                      => -1,
14443       Pragma_Optimize_Alignment            => -1,
14444       Pragma_Ordered                       =>  0,
14445       Pragma_Pack                          =>  0,
14446       Pragma_Page                          => -1,
14447       Pragma_Passive                       => -1,
14448       Pragma_Preelaborable_Initialization  => -1,
14449       Pragma_Polling                       => -1,
14450       Pragma_Persistent_BSS                =>  0,
14451       Pragma_Postcondition                 => -1,
14452       Pragma_Precondition                  => -1,
14453       Pragma_Predicate                     => -1,
14454       Pragma_Preelaborate                  => -1,
14455       Pragma_Preelaborate_05               => -1,
14456       Pragma_Priority                      => -1,
14457       Pragma_Priority_Specific_Dispatching => -1,
14458       Pragma_Profile                       =>  0,
14459       Pragma_Profile_Warnings              =>  0,
14460       Pragma_Propagate_Exceptions          => -1,
14461       Pragma_Psect_Object                  => -1,
14462       Pragma_Pure                          => -1,
14463       Pragma_Pure_05                       => -1,
14464       Pragma_Pure_Function                 => -1,
14465       Pragma_Queuing_Policy                => -1,
14466       Pragma_Ravenscar                     => -1,
14467       Pragma_Relative_Deadline             => -1,
14468       Pragma_Remote_Call_Interface         => -1,
14469       Pragma_Remote_Types                  => -1,
14470       Pragma_Restricted_Run_Time           => -1,
14471       Pragma_Restriction_Warnings          => -1,
14472       Pragma_Restrictions                  => -1,
14473       Pragma_Reviewable                    => -1,
14474       Pragma_Short_Circuit_And_Or          => -1,
14475       Pragma_Share_Generic                 => -1,
14476       Pragma_Shared                        => -1,
14477       Pragma_Shared_Passive                => -1,
14478       Pragma_Short_Descriptors             =>  0,
14479       Pragma_Source_File_Name              => -1,
14480       Pragma_Source_File_Name_Project      => -1,
14481       Pragma_Source_Reference              => -1,
14482       Pragma_Storage_Size                  => -1,
14483       Pragma_Storage_Unit                  => -1,
14484       Pragma_Static_Elaboration_Desired    => -1,
14485       Pragma_Stream_Convert                => -1,
14486       Pragma_Style_Checks                  => -1,
14487       Pragma_Subtitle                      => -1,
14488       Pragma_Suppress                      =>  0,
14489       Pragma_Suppress_Exception_Locations  =>  0,
14490       Pragma_Suppress_All                  => -1,
14491       Pragma_Suppress_Debug_Info           =>  0,
14492       Pragma_Suppress_Initialization       =>  0,
14493       Pragma_System_Name                   => -1,
14494       Pragma_Task_Dispatching_Policy       => -1,
14495       Pragma_Task_Info                     => -1,
14496       Pragma_Task_Name                     => -1,
14497       Pragma_Task_Storage                  =>  0,
14498       Pragma_Test_Case                     => -1,
14499       Pragma_Thread_Local_Storage          =>  0,
14500       Pragma_Time_Slice                    => -1,
14501       Pragma_Title                         => -1,
14502       Pragma_Unchecked_Union               =>  0,
14503       Pragma_Unimplemented_Unit            => -1,
14504       Pragma_Universal_Aliasing            => -1,
14505       Pragma_Universal_Data                => -1,
14506       Pragma_Unmodified                    => -1,
14507       Pragma_Unreferenced                  => -1,
14508       Pragma_Unreferenced_Objects          => -1,
14509       Pragma_Unreserve_All_Interrupts      => -1,
14510       Pragma_Unsuppress                    =>  0,
14511       Pragma_Use_VADS_Size                 => -1,
14512       Pragma_Validity_Checks               => -1,
14513       Pragma_Volatile                      =>  0,
14514       Pragma_Volatile_Components           =>  0,
14515       Pragma_Warnings                      => -1,
14516       Pragma_Weak_External                 => -1,
14517       Pragma_Wide_Character_Encoding       =>  0,
14518       Unknown_Pragma                       =>  0);
14519
14520    function Is_Non_Significant_Pragma_Reference (N : Node_Id) return Boolean is
14521       Id : Pragma_Id;
14522       P  : Node_Id;
14523       C  : Int;
14524       A  : Node_Id;
14525
14526    begin
14527       P := Parent (N);
14528
14529       if Nkind (P) /= N_Pragma_Argument_Association then
14530          return False;
14531
14532       else
14533          Id := Get_Pragma_Id (Parent (P));
14534          C := Sig_Flags (Id);
14535
14536          case C is
14537             when -1 =>
14538                return False;
14539
14540             when 0 =>
14541                return True;
14542
14543             when 99 =>
14544                case Id is
14545
14546                   --  For pragma Check, the first argument is not significant,
14547                   --  the second and the third (if present) arguments are
14548                   --  significant.
14549
14550                   when Pragma_Check =>
14551                      return
14552                        P = First (Pragma_Argument_Associations (Parent (P)));
14553
14554                   when others =>
14555                      raise Program_Error;
14556                end case;
14557
14558             when others =>
14559                A := First (Pragma_Argument_Associations (Parent (P)));
14560                for J in 1 .. C - 1 loop
14561                   if No (A) then
14562                      return False;
14563                   end if;
14564
14565                   Next (A);
14566                end loop;
14567
14568                return A = P; -- is this wrong way round ???
14569          end case;
14570       end if;
14571    end Is_Non_Significant_Pragma_Reference;
14572
14573    ------------------------------
14574    -- Is_Pragma_String_Literal --
14575    ------------------------------
14576
14577    --  This function returns true if the corresponding pragma argument is a
14578    --  static string expression. These are the only cases in which string
14579    --  literals can appear as pragma arguments. We also allow a string literal
14580    --  as the first argument to pragma Assert (although it will of course
14581    --  always generate a type error).
14582
14583    function Is_Pragma_String_Literal (Par : Node_Id) return Boolean is
14584       Pragn : constant Node_Id := Parent (Par);
14585       Assoc : constant List_Id := Pragma_Argument_Associations (Pragn);
14586       Pname : constant Name_Id := Pragma_Name (Pragn);
14587       Argn  : Natural;
14588       N     : Node_Id;
14589
14590    begin
14591       Argn := 1;
14592       N := First (Assoc);
14593       loop
14594          exit when N = Par;
14595          Argn := Argn + 1;
14596          Next (N);
14597       end loop;
14598
14599       if Pname = Name_Assert then
14600          return True;
14601
14602       elsif Pname = Name_Export then
14603          return Argn > 2;
14604
14605       elsif Pname = Name_Ident then
14606          return Argn = 1;
14607
14608       elsif Pname = Name_Import then
14609          return Argn > 2;
14610
14611       elsif Pname = Name_Interface_Name then
14612          return Argn > 1;
14613
14614       elsif Pname = Name_Linker_Alias then
14615          return Argn = 2;
14616
14617       elsif Pname = Name_Linker_Section then
14618          return Argn = 2;
14619
14620       elsif Pname = Name_Machine_Attribute then
14621          return Argn = 2;
14622
14623       elsif Pname = Name_Source_File_Name then
14624          return True;
14625
14626       elsif Pname = Name_Source_Reference then
14627          return Argn = 2;
14628
14629       elsif Pname = Name_Title then
14630          return True;
14631
14632       elsif Pname = Name_Subtitle then
14633          return True;
14634
14635       else
14636          return False;
14637       end if;
14638    end Is_Pragma_String_Literal;
14639
14640    ------------------------
14641    -- Preanalyze_TC_Args --
14642    ------------------------
14643
14644    procedure Preanalyze_TC_Args (Arg_Req, Arg_Ens : Node_Id) is
14645    begin
14646       --  Preanalyze the boolean expressions, we treat these as spec
14647       --  expressions (i.e. similar to a default expression).
14648
14649       if Present (Arg_Req) then
14650          Preanalyze_Spec_Expression
14651            (Get_Pragma_Arg (Arg_Req), Standard_Boolean);
14652       end if;
14653
14654       if Present (Arg_Ens) then
14655          Preanalyze_Spec_Expression
14656            (Get_Pragma_Arg (Arg_Ens), Standard_Boolean);
14657       end if;
14658    end Preanalyze_TC_Args;
14659
14660    --------------------------------------
14661    -- Process_Compilation_Unit_Pragmas --
14662    --------------------------------------
14663
14664    procedure Process_Compilation_Unit_Pragmas (N : Node_Id) is
14665    begin
14666       --  A special check for pragma Suppress_All, a very strange DEC pragma,
14667       --  strange because it comes at the end of the unit. Rational has the
14668       --  same name for a pragma, but treats it as a program unit pragma, In
14669       --  GNAT we just decide to allow it anywhere at all. If it appeared then
14670       --  the flag Has_Pragma_Suppress_All was set on the compilation unit
14671       --  node, and we insert a pragma Suppress (All_Checks) at the start of
14672       --  the context clause to ensure the correct processing.
14673
14674       if Has_Pragma_Suppress_All (N) then
14675          Prepend_To (Context_Items (N),
14676            Make_Pragma (Sloc (N),
14677              Chars                        => Name_Suppress,
14678              Pragma_Argument_Associations => New_List (
14679                Make_Pragma_Argument_Association (Sloc (N),
14680                  Expression => Make_Identifier (Sloc (N), Name_All_Checks)))));
14681       end if;
14682
14683       --  Nothing else to do at the current time!
14684
14685    end Process_Compilation_Unit_Pragmas;
14686
14687    --------
14688    -- rv --
14689    --------
14690
14691    procedure rv is
14692    begin
14693       null;
14694    end rv;
14695
14696    --------------------------------
14697    -- Set_Encoded_Interface_Name --
14698    --------------------------------
14699
14700    procedure Set_Encoded_Interface_Name (E : Entity_Id; S : Node_Id) is
14701       Str : constant String_Id := Strval (S);
14702       Len : constant Int       := String_Length (Str);
14703       CC  : Char_Code;
14704       C   : Character;
14705       J   : Int;
14706
14707       Hex : constant array (0 .. 15) of Character := "0123456789abcdef";
14708
14709       procedure Encode;
14710       --  Stores encoded value of character code CC. The encoding we use an
14711       --  underscore followed by four lower case hex digits.
14712
14713       ------------
14714       -- Encode --
14715       ------------
14716
14717       procedure Encode is
14718       begin
14719          Store_String_Char (Get_Char_Code ('_'));
14720          Store_String_Char
14721            (Get_Char_Code (Hex (Integer (CC / 2 ** 12))));
14722          Store_String_Char
14723            (Get_Char_Code (Hex (Integer (CC / 2 ** 8 and 16#0F#))));
14724          Store_String_Char
14725            (Get_Char_Code (Hex (Integer (CC / 2 ** 4 and 16#0F#))));
14726          Store_String_Char
14727            (Get_Char_Code (Hex (Integer (CC and 16#0F#))));
14728       end Encode;
14729
14730    --  Start of processing for Set_Encoded_Interface_Name
14731
14732    begin
14733       --  If first character is asterisk, this is a link name, and we leave it
14734       --  completely unmodified. We also ignore null strings (the latter case
14735       --  happens only in error cases) and no encoding should occur for Java or
14736       --  AAMP interface names.
14737
14738       if Len = 0
14739         or else Get_String_Char (Str, 1) = Get_Char_Code ('*')
14740         or else VM_Target /= No_VM
14741         or else AAMP_On_Target
14742       then
14743          Set_Interface_Name (E, S);
14744
14745       else
14746          J := 1;
14747          loop
14748             CC := Get_String_Char (Str, J);
14749
14750             exit when not In_Character_Range (CC);
14751
14752             C := Get_Character (CC);
14753
14754             exit when C /= '_' and then C /= '$'
14755               and then C not in '0' .. '9'
14756               and then C not in 'a' .. 'z'
14757               and then C not in 'A' .. 'Z';
14758
14759             if J = Len then
14760                Set_Interface_Name (E, S);
14761                return;
14762
14763             else
14764                J := J + 1;
14765             end if;
14766          end loop;
14767
14768          --  Here we need to encode. The encoding we use as follows:
14769          --     three underscores  + four hex digits (lower case)
14770
14771          Start_String;
14772
14773          for J in 1 .. String_Length (Str) loop
14774             CC := Get_String_Char (Str, J);
14775
14776             if not In_Character_Range (CC) then
14777                Encode;
14778             else
14779                C := Get_Character (CC);
14780
14781                if C = '_' or else C = '$'
14782                  or else C in '0' .. '9'
14783                  or else C in 'a' .. 'z'
14784                  or else C in 'A' .. 'Z'
14785                then
14786                   Store_String_Char (CC);
14787                else
14788                   Encode;
14789                end if;
14790             end if;
14791          end loop;
14792
14793          Set_Interface_Name (E,
14794            Make_String_Literal (Sloc (S),
14795              Strval => End_String));
14796       end if;
14797    end Set_Encoded_Interface_Name;
14798
14799    -------------------
14800    -- Set_Unit_Name --
14801    -------------------
14802
14803    procedure Set_Unit_Name (N : Node_Id; With_Item : Node_Id) is
14804       Pref : Node_Id;
14805       Scop : Entity_Id;
14806
14807    begin
14808       if Nkind (N) = N_Identifier
14809         and then Nkind (With_Item) = N_Identifier
14810       then
14811          Set_Entity (N, Entity (With_Item));
14812
14813       elsif Nkind (N) = N_Selected_Component then
14814          Change_Selected_Component_To_Expanded_Name (N);
14815          Set_Entity (N, Entity (With_Item));
14816          Set_Entity (Selector_Name (N), Entity (N));
14817
14818          Pref := Prefix (N);
14819          Scop := Scope (Entity (N));
14820          while Nkind (Pref) = N_Selected_Component loop
14821             Change_Selected_Component_To_Expanded_Name (Pref);
14822             Set_Entity (Selector_Name (Pref), Scop);
14823             Set_Entity (Pref, Scop);
14824             Pref := Prefix (Pref);
14825             Scop := Scope (Scop);
14826          end loop;
14827
14828          Set_Entity (Pref, Scop);
14829       end if;
14830    end Set_Unit_Name;
14831
14832 end Sem_Prag;