OSDN Git Service

ad989d2784af90c37c01705e33dbc6ae8f8c48e5
[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 Aspects;  use Aspects;
33 with Atree;    use Atree;
34 with Casing;   use Casing;
35 with Checks;   use Checks;
36 with Csets;    use Csets;
37 with Debug;    use Debug;
38 with Einfo;    use Einfo;
39 with Elists;   use Elists;
40 with Errout;   use Errout;
41 with Exp_Dist; use Exp_Dist;
42 with Exp_Util; use Exp_Util;
43 with Freeze;   use Freeze;
44 with Lib;      use Lib;
45 with Lib.Writ; use Lib.Writ;
46 with Lib.Xref; use Lib.Xref;
47 with Namet.Sp; use Namet.Sp;
48 with Nlists;   use Nlists;
49 with Nmake;    use Nmake;
50 with Opt;      use Opt;
51 with Output;   use Output;
52 with Par_SCO;  use Par_SCO;
53 with Restrict; use Restrict;
54 with Rident;   use Rident;
55 with Rtsfind;  use Rtsfind;
56 with Sem;      use Sem;
57 with Sem_Aux;  use Sem_Aux;
58 with Sem_Ch3;  use Sem_Ch3;
59 with Sem_Ch6;  use Sem_Ch6;
60 with Sem_Ch8;  use Sem_Ch8;
61 with Sem_Ch12; use Sem_Ch12;
62 with Sem_Ch13; use Sem_Ch13;
63 with Sem_Disp; use Sem_Disp;
64 with Sem_Dist; use Sem_Dist;
65 with Sem_Elim; use Sem_Elim;
66 with Sem_Eval; use Sem_Eval;
67 with Sem_Intr; use Sem_Intr;
68 with Sem_Mech; use Sem_Mech;
69 with Sem_Res;  use Sem_Res;
70 with Sem_Type; use Sem_Type;
71 with Sem_Util; use Sem_Util;
72 with Sem_VFpt; use Sem_VFpt;
73 with Sem_Warn; use Sem_Warn;
74 with Stand;    use Stand;
75 with Sinfo;    use Sinfo;
76 with Sinfo.CN; use Sinfo.CN;
77 with Sinput;   use Sinput;
78 with Snames;   use Snames;
79 with Stringt;  use Stringt;
80 with Stylesw;  use Stylesw;
81 with Table;
82 with Targparm; use Targparm;
83 with Tbuild;   use Tbuild;
84 with Ttypes;
85 with Uintp;    use Uintp;
86 with Uname;    use Uname;
87 with Urealp;   use Urealp;
88 with Validsw;  use Validsw;
89 with Warnsw;   use Warnsw;
90
91 package body Sem_Prag is
92
93    ----------------------------------------------
94    -- Common Handling of Import-Export Pragmas --
95    ----------------------------------------------
96
97    --  In the following section, a number of Import_xxx and Export_xxx pragmas
98    --  are defined by GNAT. These are compatible with the DEC pragmas of the
99    --  same name, and all have the following common form and processing:
100
101    --  pragma Export_xxx
102    --        [Internal                 =>] LOCAL_NAME
103    --     [, [External                 =>] EXTERNAL_SYMBOL]
104    --     [, other optional parameters   ]);
105
106    --  pragma Import_xxx
107    --        [Internal                 =>] LOCAL_NAME
108    --     [, [External                 =>] EXTERNAL_SYMBOL]
109    --     [, other optional parameters   ]);
110
111    --   EXTERNAL_SYMBOL ::=
112    --     IDENTIFIER
113    --   | static_string_EXPRESSION
114
115    --  The internal LOCAL_NAME designates the entity that is imported or
116    --  exported, and must refer to an entity in the current declarative
117    --  part (as required by the rules for LOCAL_NAME).
118
119    --  The external linker name is designated by the External parameter if
120    --  given, or the Internal parameter if not (if there is no External
121    --  parameter, the External parameter is a copy of the Internal name).
122
123    --  If the External parameter is given as a string, then this string is
124    --  treated as an external name (exactly as though it had been given as an
125    --  External_Name parameter for a normal Import pragma).
126
127    --  If the External parameter is given as an identifier (or there is no
128    --  External parameter, so that the Internal identifier is used), then
129    --  the external name is the characters of the identifier, translated
130    --  to all upper case letters for OpenVMS versions of GNAT, and to all
131    --  lower case letters for all other versions
132
133    --  Note: the external name specified or implied by any of these special
134    --  Import_xxx or Export_xxx pragmas override an external or link name
135    --  specified in a previous Import or Export pragma.
136
137    --  Note: these and all other DEC-compatible GNAT pragmas allow full use of
138    --  named notation, following the standard rules for subprogram calls, i.e.
139    --  parameters can be given in any order if named notation is used, and
140    --  positional and named notation can be mixed, subject to the rule that all
141    --  positional parameters must appear first.
142
143    --  Note: All these pragmas are implemented exactly following the DEC design
144    --  and implementation and are intended to be fully compatible with the use
145    --  of these pragmas in the DEC Ada compiler.
146
147    --------------------------------------------
148    -- Checking for Duplicated External Names --
149    --------------------------------------------
150
151    --  It is suspicious if two separate Export pragmas use the same external
152    --  name. The following table is used to diagnose this situation so that
153    --  an appropriate warning can be issued.
154
155    --  The Node_Id stored is for the N_String_Literal node created to hold
156    --  the value of the external name. The Sloc of this node is used to
157    --  cross-reference the location of the duplication.
158
159    package Externals is new Table.Table (
160      Table_Component_Type => Node_Id,
161      Table_Index_Type     => Int,
162      Table_Low_Bound      => 0,
163      Table_Initial        => 100,
164      Table_Increment      => 100,
165      Table_Name           => "Name_Externals");
166
167    -------------------------------------
168    -- Local Subprograms and Variables --
169    -------------------------------------
170
171    function Adjust_External_Name_Case (N : Node_Id) return Node_Id;
172    --  This routine is used for possible casing adjustment of an explicit
173    --  external name supplied as a string literal (the node N), according to
174    --  the casing requirement of Opt.External_Name_Casing. If this is set to
175    --  As_Is, then the string literal is returned unchanged, but if it is set
176    --  to Uppercase or Lowercase, then a new string literal with appropriate
177    --  casing is constructed.
178
179    function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id;
180    --  If Def_Id refers to a renamed subprogram, then the base subprogram (the
181    --  original one, following the renaming chain) is returned. Otherwise the
182    --  entity is returned unchanged. Should be in Einfo???
183
184    procedure Preanalyze_TC_Args (N, Arg_Req, Arg_Ens : Node_Id);
185    --  Preanalyze the boolean expressions in the Requires and Ensures arguments
186    --  of a Test_Case pragma if present (possibly Empty). We treat these as
187    --  spec expressions (i.e. similar to a default expression).
188
189    procedure rv;
190    --  This is a dummy function called by the processing for pragma Reviewable.
191    --  It is there for assisting front end debugging. By placing a Reviewable
192    --  pragma in the source program, a breakpoint on rv catches this place in
193    --  the source, allowing convenient stepping to the point of interest.
194
195    procedure Set_Unit_Name (N : Node_Id; With_Item : Node_Id);
196    --  Place semantic information on the argument of an Elaborate/Elaborate_All
197    --  pragma. Entity name for unit and its parents is taken from item in
198    --  previous with_clause that mentions the unit.
199
200    -------------------------------
201    -- Adjust_External_Name_Case --
202    -------------------------------
203
204    function Adjust_External_Name_Case (N : Node_Id) return Node_Id is
205       CC : Char_Code;
206
207    begin
208       --  Adjust case of literal if required
209
210       if Opt.External_Name_Exp_Casing = As_Is then
211          return N;
212
213       else
214          --  Copy existing string
215
216          Start_String;
217
218          --  Set proper casing
219
220          for J in 1 .. String_Length (Strval (N)) loop
221             CC := Get_String_Char (Strval (N), J);
222
223             if Opt.External_Name_Exp_Casing = Uppercase
224               and then CC >= Get_Char_Code ('a')
225               and then CC <= Get_Char_Code ('z')
226             then
227                Store_String_Char (CC - 32);
228
229             elsif Opt.External_Name_Exp_Casing = Lowercase
230               and then CC >= Get_Char_Code ('A')
231               and then CC <= Get_Char_Code ('Z')
232             then
233                Store_String_Char (CC + 32);
234
235             else
236                Store_String_Char (CC);
237             end if;
238          end loop;
239
240          return
241            Make_String_Literal (Sloc (N),
242              Strval => End_String);
243       end if;
244    end Adjust_External_Name_Case;
245
246    ------------------------------
247    -- Analyze_PPC_In_Decl_Part --
248    ------------------------------
249
250    procedure Analyze_PPC_In_Decl_Part (N : Node_Id; S : Entity_Id) is
251       Arg1 : constant Node_Id := First (Pragma_Argument_Associations (N));
252
253    begin
254       --  Install formals and push subprogram spec onto scope stack so that we
255       --  can see the formals from the pragma.
256
257       Install_Formals (S);
258       Push_Scope (S);
259
260       --  Preanalyze the boolean expression, we treat this as a spec expression
261       --  (i.e. similar to a default expression).
262
263       Preanalyze_Spec_Expression (Get_Pragma_Arg (Arg1), Standard_Boolean);
264
265       --  In ASIS mode, for a pragma generated from a source aspect, also
266       --  analyze the original aspect expression.
267
268       if ASIS_Mode
269         and then Present (Corresponding_Aspect (N))
270       then
271          Preanalyze_Spec_Expression
272            (Expression (Corresponding_Aspect (N)), Standard_Boolean);
273       end if;
274
275       --  For a class-wide condition, a reference to a controlling formal must
276       --  be interpreted as having the class-wide type (or an access to such)
277       --  so that the inherited condition can be properly applied to any
278       --  overriding operation (see ARM12 6.6.1 (7)).
279
280       if Class_Present (N) then
281          declare
282             T   : constant Entity_Id := Find_Dispatching_Type (S);
283
284             ACW : Entity_Id := Empty;
285             --  Access to T'class, created if there is a controlling formal
286             --  that is an access parameter.
287
288             function Get_ACW return Entity_Id;
289             --  If the expression has a reference to an controlling access
290             --  parameter, create an access to T'class for the necessary
291             --  conversions if one does not exist.
292
293             function Process (N : Node_Id) return Traverse_Result;
294             --  ARM 6.1.1: Within the expression for a Pre'Class or Post'Class
295             --  aspect for a primitive subprogram of a tagged type T, a name
296             --  that denotes a formal parameter of type T is interpreted as
297             --  having type T'Class. Similarly, a name that denotes a formal
298             --  accessparameter of type access-to-T is interpreted as having
299             --  type access-to-T'Class. This ensures the expression is well-
300             --  defined for a primitive subprogram of a type descended from T.
301
302             -------------
303             -- Get_ACW --
304             -------------
305
306             function Get_ACW return Entity_Id is
307                Loc  : constant Source_Ptr := Sloc (N);
308                Decl : Node_Id;
309
310             begin
311                if No (ACW) then
312                   Decl := Make_Full_Type_Declaration (Loc,
313                     Defining_Identifier => Make_Temporary (Loc, 'T'),
314                     Type_Definition =>
315                        Make_Access_To_Object_Definition (Loc,
316                        Subtype_Indication =>
317                          New_Occurrence_Of (Class_Wide_Type (T), Loc),
318                        All_Present => True));
319
320                   Insert_Before (Unit_Declaration_Node (S), Decl);
321                   Analyze (Decl);
322                   ACW := Defining_Identifier (Decl);
323                   Freeze_Before (Unit_Declaration_Node (S), ACW);
324                end if;
325
326                return ACW;
327             end Get_ACW;
328
329             -------------
330             -- Process --
331             -------------
332
333             function Process (N : Node_Id) return Traverse_Result is
334                Loc : constant Source_Ptr := Sloc (N);
335                Typ : Entity_Id;
336
337             begin
338                if Is_Entity_Name (N)
339                  and then Is_Formal (Entity (N))
340                  and then Nkind (Parent (N)) /= N_Type_Conversion
341                then
342                   if Etype (Entity (N)) = T then
343                      Typ := Class_Wide_Type (T);
344
345                   elsif Is_Access_Type (Etype (Entity (N)))
346                     and then Designated_Type (Etype (Entity (N))) = T
347                   then
348                      Typ := Get_ACW;
349                   else
350                      Typ := Empty;
351                   end if;
352
353                   if Present (Typ) then
354                      Rewrite (N,
355                        Make_Type_Conversion (Loc,
356                          Subtype_Mark =>
357                            New_Occurrence_Of (Typ, Loc),
358                          Expression  => New_Occurrence_Of (Entity (N), Loc)));
359                      Set_Etype (N, Typ);
360                   end if;
361                end if;
362
363                return OK;
364             end Process;
365
366             procedure Replace_Type is new Traverse_Proc (Process);
367
368          begin
369             Replace_Type (Get_Pragma_Arg (Arg1));
370          end;
371       end if;
372
373       --  Remove the subprogram from the scope stack now that the pre-analysis
374       --  of the precondition/postcondition is done.
375
376       End_Scope;
377    end Analyze_PPC_In_Decl_Part;
378
379    --------------------
380    -- Analyze_Pragma --
381    --------------------
382
383    procedure Analyze_Pragma (N : Node_Id) is
384       Loc     : constant Source_Ptr := Sloc (N);
385       Prag_Id : Pragma_Id;
386
387       Pname : Name_Id;
388       --  Name of the source pragma, or name of the corresponding aspect for
389       --  pragmas which originate in a source aspect. In the latter case, the
390       --  name may be different from the pragma name.
391
392       Pragma_Exit : exception;
393       --  This exception is used to exit pragma processing completely. It is
394       --  used when an error is detected, and no further processing is
395       --  required. It is also used if an earlier error has left the tree in
396       --  a state where the pragma should not be processed.
397
398       Arg_Count : Nat;
399       --  Number of pragma argument associations
400
401       Arg1 : Node_Id;
402       Arg2 : Node_Id;
403       Arg3 : Node_Id;
404       Arg4 : Node_Id;
405       --  First four pragma arguments (pragma argument association nodes, or
406       --  Empty if the corresponding argument does not exist).
407
408       type Name_List is array (Natural range <>) of Name_Id;
409       type Args_List is array (Natural range <>) of Node_Id;
410       --  Types used for arguments to Check_Arg_Order and Gather_Associations
411
412       procedure Ada_2005_Pragma;
413       --  Called for pragmas defined in Ada 2005, that are not in Ada 95. In
414       --  Ada 95 mode, these are implementation defined pragmas, so should be
415       --  caught by the No_Implementation_Pragmas restriction.
416
417       procedure Ada_2012_Pragma;
418       --  Called for pragmas defined in Ada 2012, that are not in Ada 95 or 05.
419       --  In Ada 95 or 05 mode, these are implementation defined pragmas, so
420       --  should be caught by the No_Implementation_Pragmas restriction.
421
422       procedure Check_Ada_83_Warning;
423       --  Issues a warning message for the current pragma if operating in Ada
424       --  83 mode (used for language pragmas that are not a standard part of
425       --  Ada 83). This procedure does not raise Error_Pragma. Also notes use
426       --  of 95 pragma.
427
428       procedure Check_Arg_Count (Required : Nat);
429       --  Check argument count for pragma is equal to given parameter. If not,
430       --  then issue an error message and raise Pragma_Exit.
431
432       --  Note: all routines whose name is Check_Arg_Is_xxx take an argument
433       --  Arg which can either be a pragma argument association, in which case
434       --  the check is applied to the expression of the association or an
435       --  expression directly.
436
437       procedure Check_Arg_Is_External_Name (Arg : Node_Id);
438       --  Check that an argument has the right form for an EXTERNAL_NAME
439       --  parameter of an extended import/export pragma. The rule is that the
440       --  name must be an identifier or string literal (in Ada 83 mode) or a
441       --  static string expression (in Ada 95 mode).
442
443       procedure Check_Arg_Is_Identifier (Arg : Node_Id);
444       --  Check the specified argument Arg to make sure that it is an
445       --  identifier. If not give error and raise Pragma_Exit.
446
447       procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id);
448       --  Check the specified argument Arg to make sure that it is an integer
449       --  literal. If not give error and raise Pragma_Exit.
450
451       procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id);
452       --  Check the specified argument Arg to make sure that it has the proper
453       --  syntactic form for a local name and meets the semantic requirements
454       --  for a local name. The local name is analyzed as part of the
455       --  processing for this call. In addition, the local name is required
456       --  to represent an entity at the library level.
457
458       procedure Check_Arg_Is_Local_Name (Arg : Node_Id);
459       --  Check the specified argument Arg to make sure that it has the proper
460       --  syntactic form for a local name and meets the semantic requirements
461       --  for a local name. The local name is analyzed as part of the
462       --  processing for this call.
463
464       procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id);
465       --  Check the specified argument Arg to make sure that it is a valid
466       --  locking policy name. If not give error and raise Pragma_Exit.
467
468       procedure Check_Arg_Is_One_Of
469         (Arg                : Node_Id;
470          N1, N2             : Name_Id);
471       procedure Check_Arg_Is_One_Of
472         (Arg                : Node_Id;
473          N1, N2, N3         : Name_Id);
474       procedure Check_Arg_Is_One_Of
475         (Arg                : Node_Id;
476          N1, N2, N3, N4, N5 : Name_Id);
477       --  Check the specified argument Arg to make sure that it is an
478       --  identifier whose name matches either N1 or N2 (or N3, N4, N5 if
479       --  present). If not then give error and raise Pragma_Exit.
480
481       procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id);
482       --  Check the specified argument Arg to make sure that it is a valid
483       --  queuing policy name. If not give error and raise Pragma_Exit.
484
485       procedure Check_Arg_Is_Static_Expression
486         (Arg : Node_Id;
487          Typ : Entity_Id := Empty);
488       --  Check the specified argument Arg to make sure that it is a static
489       --  expression of the given type (i.e. it will be analyzed and resolved
490       --  using this type, which can be any valid argument to Resolve, e.g.
491       --  Any_Integer is OK). If not, given error and raise Pragma_Exit. If
492       --  Typ is left Empty, then any static expression is allowed.
493
494       procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id);
495       --  Check the specified argument Arg to make sure that it is a valid task
496       --  dispatching policy name. If not give error and raise Pragma_Exit.
497
498       procedure Check_Arg_Order (Names : Name_List);
499       --  Checks for an instance of two arguments with identifiers for the
500       --  current pragma which are not in the sequence indicated by Names,
501       --  and if so, generates a fatal message about bad order of arguments.
502
503       procedure Check_At_Least_N_Arguments (N : Nat);
504       --  Check there are at least N arguments present
505
506       procedure Check_At_Most_N_Arguments (N : Nat);
507       --  Check there are no more than N arguments present
508
509       procedure Check_Component
510         (Comp            : Node_Id;
511          UU_Typ          : Entity_Id;
512          In_Variant_Part : Boolean := False);
513       --  Examine an Unchecked_Union component for correct use of per-object
514       --  constrained subtypes, and for restrictions on finalizable components.
515       --  UU_Typ is the related Unchecked_Union type. Flag In_Variant_Part
516       --  should be set when Comp comes from a record variant.
517
518       procedure Check_Duplicate_Pragma (E : Entity_Id);
519       --  Check if a pragma of the same name as the current pragma is already
520       --  chained as a rep pragma to the given entity. If so give a message
521       --  about the duplicate, and then raise Pragma_Exit so does not return.
522       --  Also checks for delayed aspect specification node in the chain.
523
524       procedure Check_Duplicated_Export_Name (Nam : Node_Id);
525       --  Nam is an N_String_Literal node containing the external name set by
526       --  an Import or Export pragma (or extended Import or Export pragma).
527       --  This procedure checks for possible duplications if this is the export
528       --  case, and if found, issues an appropriate error message.
529
530       procedure Check_Expr_Is_Static_Expression
531         (Expr : Node_Id;
532          Typ  : Entity_Id := Empty);
533       --  Check the specified expression Expr to make sure that it is a static
534       --  expression of the given type (i.e. it will be analyzed and resolved
535       --  using this type, which can be any valid argument to Resolve, e.g.
536       --  Any_Integer is OK). If not, given error and raise Pragma_Exit. If
537       --  Typ is left Empty, then any static expression is allowed.
538
539       procedure Check_First_Subtype (Arg : Node_Id);
540       --  Checks that Arg, whose expression is an entity name, references a
541       --  first subtype.
542
543       procedure Check_Identifier (Arg : Node_Id; Id : Name_Id);
544       --  Checks that the given argument has an identifier, and if so, requires
545       --  it to match the given identifier name. If there is no identifier, or
546       --  a non-matching identifier, then an error message is given and
547       --  Pragma_Exit is raised.
548
549       procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id);
550       --  Checks that the given argument has an identifier, and if so, requires
551       --  it to match one of the given identifier names. If there is no
552       --  identifier, or a non-matching identifier, then an error message is
553       --  given and Pragma_Exit is raised.
554
555       procedure Check_In_Main_Program;
556       --  Common checks for pragmas that appear within a main program
557       --  (Priority, Main_Storage, Time_Slice, Relative_Deadline, CPU).
558
559       procedure Check_Interrupt_Or_Attach_Handler;
560       --  Common processing for first argument of pragma Interrupt_Handler or
561       --  pragma Attach_Handler.
562
563       procedure Check_Is_In_Decl_Part_Or_Package_Spec;
564       --  Check that pragma appears in a declarative part, or in a package
565       --  specification, i.e. that it does not occur in a statement sequence
566       --  in a body.
567
568       procedure Check_No_Identifier (Arg : Node_Id);
569       --  Checks that the given argument does not have an identifier. If
570       --  an identifier is present, then an error message is issued, and
571       --  Pragma_Exit is raised.
572
573       procedure Check_No_Identifiers;
574       --  Checks that none of the arguments to the pragma has an identifier.
575       --  If any argument has an identifier, then an error message is issued,
576       --  and Pragma_Exit is raised.
577
578       procedure Check_No_Link_Name;
579       --  Checks that no link name is specified
580
581       procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id);
582       --  Checks if the given argument has an identifier, and if so, requires
583       --  it to match the given identifier name. If there is a non-matching
584       --  identifier, then an error message is given and Pragma_Exit is raised.
585
586       procedure Check_Optional_Identifier (Arg : Node_Id; Id : String);
587       --  Checks if the given argument has an identifier, and if so, requires
588       --  it to match the given identifier name. If there is a non-matching
589       --  identifier, then an error message is given and Pragma_Exit is raised.
590       --  In this version of the procedure, the identifier name is given as
591       --  a string with lower case letters.
592
593       procedure Check_Precondition_Postcondition (In_Body : out Boolean);
594       --  Called to process a precondition or postcondition pragma. There are
595       --  three cases:
596       --
597       --    The pragma appears after a subprogram spec
598       --
599       --      If the corresponding check is not enabled, the pragma is analyzed
600       --      but otherwise ignored and control returns with In_Body set False.
601       --
602       --      If the check is enabled, then the first step is to analyze the
603       --      pragma, but this is skipped if the subprogram spec appears within
604       --      a package specification (because this is the case where we delay
605       --      analysis till the end of the spec). Then (whether or not it was
606       --      analyzed), the pragma is chained to the subprogram in question
607       --      (using Spec_PPC_List and Next_Pragma) and control returns to the
608       --      caller with In_Body set False.
609       --
610       --    The pragma appears at the start of subprogram body declarations
611       --
612       --      In this case an immediate return to the caller is made with
613       --      In_Body set True, and the pragma is NOT analyzed.
614       --
615       --    In all other cases, an error message for bad placement is given
616
617       procedure Check_Static_Constraint (Constr : Node_Id);
618       --  Constr is a constraint from an N_Subtype_Indication node from a
619       --  component constraint in an Unchecked_Union type. This routine checks
620       --  that the constraint is static as required by the restrictions for
621       --  Unchecked_Union.
622
623       procedure Check_Test_Case;
624       --  Called to process a test-case pragma. The treatment is similar to the
625       --  one for pre- and postcondition in Check_Precondition_Postcondition,
626       --  except the placement rules for the test-case pragma are stricter.
627       --  This pragma may only occur after a subprogram spec declared directly
628       --  in a package spec unit. In this case, the pragma is chained to the
629       --  subprogram in question (using Spec_TC_List and Next_Pragma) and
630       --  analysis of the pragma is delayed till the end of the spec. In
631       --  all other cases, an error message for bad placement is given.
632
633       procedure Check_Valid_Configuration_Pragma;
634       --  Legality checks for placement of a configuration pragma
635
636       procedure Check_Valid_Library_Unit_Pragma;
637       --  Legality checks for library unit pragmas. A special case arises for
638       --  pragmas in generic instances that come from copies of the original
639       --  library unit pragmas in the generic templates. In the case of other
640       --  than library level instantiations these can appear in contexts which
641       --  would normally be invalid (they only apply to the original template
642       --  and to library level instantiations), and they are simply ignored,
643       --  which is implemented by rewriting them as null statements.
644
645       procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id);
646       --  Check an Unchecked_Union variant for lack of nested variants and
647       --  presence of at least one component. UU_Typ is the related Unchecked_
648       --  Union type.
649
650       procedure Error_Pragma (Msg : String);
651       pragma No_Return (Error_Pragma);
652       --  Outputs error message for current pragma. The message contains a %
653       --  that will be replaced with the pragma name, and the flag is placed
654       --  on the pragma itself. Pragma_Exit is then raised.
655
656       procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id);
657       pragma No_Return (Error_Pragma_Arg);
658       --  Outputs error message for current pragma. The message may contain
659       --  a % that will be replaced with the pragma name. The parameter Arg
660       --  may either be a pragma argument association, in which case the flag
661       --  is placed on the expression of this association, or an expression,
662       --  in which case the flag is placed directly on the expression. The
663       --  message is placed using Error_Msg_N, so the message may also contain
664       --  an & insertion character which will reference the given Arg value.
665       --  After placing the message, Pragma_Exit is raised.
666
667       procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id);
668       pragma No_Return (Error_Pragma_Arg);
669       --  Similar to above form of Error_Pragma_Arg except that two messages
670       --  are provided, the second is a continuation comment starting with \.
671
672       procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id);
673       pragma No_Return (Error_Pragma_Arg_Ident);
674       --  Outputs error message for current pragma. The message may contain
675       --  a % that will be replaced with the pragma name. The parameter Arg
676       --  must be a pragma argument association with a non-empty identifier
677       --  (i.e. its Chars field must be set), and the error message is placed
678       --  on the identifier. The message is placed using Error_Msg_N so
679       --  the message may also contain an & insertion character which will
680       --  reference the identifier. After placing the message, Pragma_Exit
681       --  is raised.
682
683       procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id);
684       pragma No_Return (Error_Pragma_Ref);
685       --  Outputs error message for current pragma. The message may contain
686       --  a % that will be replaced with the pragma name. The parameter Ref
687       --  must be an entity whose name can be referenced by & and sloc by #.
688       --  After placing the message, Pragma_Exit is raised.
689
690       function Find_Lib_Unit_Name return Entity_Id;
691       --  Used for a library unit pragma to find the entity to which the
692       --  library unit pragma applies, returns the entity found.
693
694       procedure Find_Program_Unit_Name (Id : Node_Id);
695       --  If the pragma is a compilation unit pragma, the id must denote the
696       --  compilation unit in the same compilation, and the pragma must appear
697       --  in the list of preceding or trailing pragmas. If it is a program
698       --  unit pragma that is not a compilation unit pragma, then the
699       --  identifier must be visible.
700
701       function Find_Unique_Parameterless_Procedure
702         (Name : Entity_Id;
703          Arg  : Node_Id) return Entity_Id;
704       --  Used for a procedure pragma to find the unique parameterless
705       --  procedure identified by Name, returns it if it exists, otherwise
706       --  errors out and uses Arg as the pragma argument for the message.
707
708       procedure Fix_Error (Msg : in out String);
709       --  This is called prior to issuing an error message. Msg is a string
710       --  which typically contains the substring pragma. If the current pragma
711       --  comes from an aspect, each such "pragma" substring is replaced with
712       --  the characters "aspect", and if Error_Msg_Name_1 is Name_Precondition
713       --  (resp Name_Postcondition) it is changed to Name_Pre (resp Name_Post).
714
715       procedure Gather_Associations
716         (Names : Name_List;
717          Args  : out Args_List);
718       --  This procedure is used to gather the arguments for a pragma that
719       --  permits arbitrary ordering of parameters using the normal rules
720       --  for named and positional parameters. The Names argument is a list
721       --  of Name_Id values that corresponds to the allowed pragma argument
722       --  association identifiers in order. The result returned in Args is
723       --  a list of corresponding expressions that are the pragma arguments.
724       --  Note that this is a list of expressions, not of pragma argument
725       --  associations (Gather_Associations has completely checked all the
726       --  optional identifiers when it returns). An entry in Args is Empty
727       --  on return if the corresponding argument is not present.
728
729       procedure GNAT_Pragma;
730       --  Called for all GNAT defined pragmas to check the relevant restriction
731       --  (No_Implementation_Pragmas).
732
733       function Is_Before_First_Decl
734         (Pragma_Node : Node_Id;
735          Decls       : List_Id) return Boolean;
736       --  Return True if Pragma_Node is before the first declarative item in
737       --  Decls where Decls is the list of declarative items.
738
739       function Is_Configuration_Pragma return Boolean;
740       --  Determines if the placement of the current pragma is appropriate
741       --  for a configuration pragma.
742
743       function Is_In_Context_Clause return Boolean;
744       --  Returns True if pragma appears within the context clause of a unit,
745       --  and False for any other placement (does not generate any messages).
746
747       function Is_Static_String_Expression (Arg : Node_Id) return Boolean;
748       --  Analyzes the argument, and determines if it is a static string
749       --  expression, returns True if so, False if non-static or not String.
750
751       procedure Pragma_Misplaced;
752       pragma No_Return (Pragma_Misplaced);
753       --  Issue fatal error message for misplaced pragma
754
755       procedure Process_Atomic_Shared_Volatile;
756       --  Common processing for pragmas Atomic, Shared, Volatile. Note that
757       --  Shared is an obsolete Ada 83 pragma, treated as being identical
758       --  in effect to pragma Atomic.
759
760       procedure Process_Compile_Time_Warning_Or_Error;
761       --  Common processing for Compile_Time_Error and Compile_Time_Warning
762
763       procedure Process_Convention
764         (C   : out Convention_Id;
765          Ent : out Entity_Id);
766       --  Common processing for Convention, Interface, Import and Export.
767       --  Checks first two arguments of pragma, and sets the appropriate
768       --  convention value in the specified entity or entities. On return
769       --  C is the convention, Ent is the referenced entity.
770
771       procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id);
772       --  Common processing for Disable/Enable_Atomic_Synchronization. Nam is
773       --  Name_Suppress for Disable and Name_Unsuppress for Enable.
774
775       procedure Process_Extended_Import_Export_Exception_Pragma
776         (Arg_Internal : Node_Id;
777          Arg_External : Node_Id;
778          Arg_Form     : Node_Id;
779          Arg_Code     : Node_Id);
780       --  Common processing for the pragmas Import/Export_Exception. The three
781       --  arguments correspond to the three named parameters of the pragma. An
782       --  argument is empty if the corresponding parameter is not present in
783       --  the pragma.
784
785       procedure Process_Extended_Import_Export_Object_Pragma
786         (Arg_Internal : Node_Id;
787          Arg_External : Node_Id;
788          Arg_Size     : Node_Id);
789       --  Common processing for the pragmas Import/Export_Object. The three
790       --  arguments correspond to the three named parameters of the pragmas. An
791       --  argument is empty if the corresponding parameter is not present in
792       --  the pragma.
793
794       procedure Process_Extended_Import_Export_Internal_Arg
795         (Arg_Internal : Node_Id := Empty);
796       --  Common processing for all extended Import and Export pragmas. The
797       --  argument is the pragma parameter for the Internal argument. If
798       --  Arg_Internal is empty or inappropriate, an error message is posted.
799       --  Otherwise, on normal return, the Entity_Field of Arg_Internal is
800       --  set to identify the referenced entity.
801
802       procedure Process_Extended_Import_Export_Subprogram_Pragma
803         (Arg_Internal                 : Node_Id;
804          Arg_External                 : Node_Id;
805          Arg_Parameter_Types          : Node_Id;
806          Arg_Result_Type              : Node_Id := Empty;
807          Arg_Mechanism                : Node_Id;
808          Arg_Result_Mechanism         : Node_Id := Empty;
809          Arg_First_Optional_Parameter : Node_Id := Empty);
810       --  Common processing for all extended Import and Export pragmas applying
811       --  to subprograms. The caller omits any arguments that do not apply to
812       --  the pragma in question (for example, Arg_Result_Type can be non-Empty
813       --  only in the Import_Function and Export_Function cases). The argument
814       --  names correspond to the allowed pragma association identifiers.
815
816       procedure Process_Generic_List;
817       --  Common processing for Share_Generic and Inline_Generic
818
819       procedure Process_Import_Or_Interface;
820       --  Common processing for Import of Interface
821
822       procedure Process_Import_Predefined_Type;
823       --  Processing for completing a type with pragma Import. This is used
824       --  to declare types that match predefined C types, especially for cases
825       --  without corresponding Ada predefined type.
826
827       procedure Process_Inline (Active : Boolean);
828       --  Common processing for Inline and Inline_Always. The parameter
829       --  indicates if the inline pragma is active, i.e. if it should actually
830       --  cause inlining to occur.
831
832       procedure Process_Interface_Name
833         (Subprogram_Def : Entity_Id;
834          Ext_Arg        : Node_Id;
835          Link_Arg       : Node_Id);
836       --  Given the last two arguments of pragma Import, pragma Export, or
837       --  pragma Interface_Name, performs validity checks and sets the
838       --  Interface_Name field of the given subprogram entity to the
839       --  appropriate external or link name, depending on the arguments given.
840       --  Ext_Arg is always present, but Link_Arg may be missing. Note that
841       --  Ext_Arg may represent the Link_Name if Link_Arg is missing, and
842       --  appropriate named notation is used for Ext_Arg. If neither Ext_Arg
843       --  nor Link_Arg is present, the interface name is set to the default
844       --  from the subprogram name.
845
846       procedure Process_Interrupt_Or_Attach_Handler;
847       --  Common processing for Interrupt and Attach_Handler pragmas
848
849       procedure Process_Restrictions_Or_Restriction_Warnings (Warn : Boolean);
850       --  Common processing for Restrictions and Restriction_Warnings pragmas.
851       --  Warn is True for Restriction_Warnings, or for Restrictions if the
852       --  flag Treat_Restrictions_As_Warnings is set, and False if this flag
853       --  is not set in the Restrictions case.
854
855       procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean);
856       --  Common processing for Suppress and Unsuppress. The boolean parameter
857       --  Suppress_Case is True for the Suppress case, and False for the
858       --  Unsuppress case.
859
860       procedure Set_Exported (E : Entity_Id; Arg : Node_Id);
861       --  This procedure sets the Is_Exported flag for the given entity,
862       --  checking that the entity was not previously imported. Arg is
863       --  the argument that specified the entity. A check is also made
864       --  for exporting inappropriate entities.
865
866       procedure Set_Extended_Import_Export_External_Name
867         (Internal_Ent : Entity_Id;
868          Arg_External : Node_Id);
869       --  Common processing for all extended import export pragmas. The first
870       --  argument, Internal_Ent, is the internal entity, which has already
871       --  been checked for validity by the caller. Arg_External is from the
872       --  Import or Export pragma, and may be null if no External parameter
873       --  was present. If Arg_External is present and is a non-null string
874       --  (a null string is treated as the default), then the Interface_Name
875       --  field of Internal_Ent is set appropriately.
876
877       procedure Set_Imported (E : Entity_Id);
878       --  This procedure sets the Is_Imported flag for the given entity,
879       --  checking that it is not previously exported or imported.
880
881       procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id);
882       --  Mech is a parameter passing mechanism (see Import_Function syntax
883       --  for MECHANISM_NAME). This routine checks that the mechanism argument
884       --  has the right form, and if not issues an error message. If the
885       --  argument has the right form then the Mechanism field of Ent is
886       --  set appropriately.
887
888       procedure Set_Ravenscar_Profile (N : Node_Id);
889       --  Activate the set of configuration pragmas and restrictions that make
890       --  up the Ravenscar Profile. N is the corresponding pragma node, which
891       --  is used for error messages on any constructs that violate the
892       --  profile.
893
894       ---------------------
895       -- Ada_2005_Pragma --
896       ---------------------
897
898       procedure Ada_2005_Pragma is
899       begin
900          if Ada_Version <= Ada_95 then
901             Check_Restriction (No_Implementation_Pragmas, N);
902          end if;
903       end Ada_2005_Pragma;
904
905       ---------------------
906       -- Ada_2012_Pragma --
907       ---------------------
908
909       procedure Ada_2012_Pragma is
910       begin
911          if Ada_Version <= Ada_2005 then
912             Check_Restriction (No_Implementation_Pragmas, N);
913          end if;
914       end Ada_2012_Pragma;
915
916       --------------------------
917       -- Check_Ada_83_Warning --
918       --------------------------
919
920       procedure Check_Ada_83_Warning is
921       begin
922          if Ada_Version = Ada_83 and then Comes_From_Source (N) then
923             Error_Msg_N ("(Ada 83) pragma& is non-standard?", N);
924          end if;
925       end Check_Ada_83_Warning;
926
927       ---------------------
928       -- Check_Arg_Count --
929       ---------------------
930
931       procedure Check_Arg_Count (Required : Nat) is
932       begin
933          if Arg_Count /= Required then
934             Error_Pragma ("wrong number of arguments for pragma%");
935          end if;
936       end Check_Arg_Count;
937
938       --------------------------------
939       -- Check_Arg_Is_External_Name --
940       --------------------------------
941
942       procedure Check_Arg_Is_External_Name (Arg : Node_Id) is
943          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
944
945       begin
946          if Nkind (Argx) = N_Identifier then
947             return;
948
949          else
950             Analyze_And_Resolve (Argx, Standard_String);
951
952             if Is_OK_Static_Expression (Argx) then
953                return;
954
955             elsif Etype (Argx) = Any_Type then
956                raise Pragma_Exit;
957
958             --  An interesting special case, if we have a string literal and
959             --  we are in Ada 83 mode, then we allow it even though it will
960             --  not be flagged as static. This allows expected Ada 83 mode
961             --  use of external names which are string literals, even though
962             --  technically these are not static in Ada 83.
963
964             elsif Ada_Version = Ada_83
965               and then Nkind (Argx) = N_String_Literal
966             then
967                return;
968
969             --  Static expression that raises Constraint_Error. This has
970             --  already been flagged, so just exit from pragma processing.
971
972             elsif Is_Static_Expression (Argx) then
973                raise Pragma_Exit;
974
975             --  Here we have a real error (non-static expression)
976
977             else
978                Error_Msg_Name_1 := Pname;
979
980                declare
981                   Msg : String :=
982                           "argument for pragma% must be a identifier or "
983                           & "static string expression!";
984                begin
985                   Fix_Error (Msg);
986                   Flag_Non_Static_Expr (Msg, Argx);
987                   raise Pragma_Exit;
988                end;
989             end if;
990          end if;
991       end Check_Arg_Is_External_Name;
992
993       -----------------------------
994       -- Check_Arg_Is_Identifier --
995       -----------------------------
996
997       procedure Check_Arg_Is_Identifier (Arg : Node_Id) is
998          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
999       begin
1000          if Nkind (Argx) /= N_Identifier then
1001             Error_Pragma_Arg
1002               ("argument for pragma% must be identifier", Argx);
1003          end if;
1004       end Check_Arg_Is_Identifier;
1005
1006       ----------------------------------
1007       -- Check_Arg_Is_Integer_Literal --
1008       ----------------------------------
1009
1010       procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id) is
1011          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1012       begin
1013          if Nkind (Argx) /= N_Integer_Literal then
1014             Error_Pragma_Arg
1015               ("argument for pragma% must be integer literal", Argx);
1016          end if;
1017       end Check_Arg_Is_Integer_Literal;
1018
1019       -------------------------------------------
1020       -- Check_Arg_Is_Library_Level_Local_Name --
1021       -------------------------------------------
1022
1023       --  LOCAL_NAME ::=
1024       --    DIRECT_NAME
1025       --  | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
1026       --  | library_unit_NAME
1027
1028       procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id) is
1029       begin
1030          Check_Arg_Is_Local_Name (Arg);
1031
1032          if not Is_Library_Level_Entity (Entity (Get_Pragma_Arg (Arg)))
1033            and then Comes_From_Source (N)
1034          then
1035             Error_Pragma_Arg
1036               ("argument for pragma% must be library level entity", Arg);
1037          end if;
1038       end Check_Arg_Is_Library_Level_Local_Name;
1039
1040       -----------------------------
1041       -- Check_Arg_Is_Local_Name --
1042       -----------------------------
1043
1044       --  LOCAL_NAME ::=
1045       --    DIRECT_NAME
1046       --  | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
1047       --  | library_unit_NAME
1048
1049       procedure Check_Arg_Is_Local_Name (Arg : Node_Id) is
1050          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1051
1052       begin
1053          Analyze (Argx);
1054
1055          if Nkind (Argx) not in N_Direct_Name
1056            and then (Nkind (Argx) /= N_Attribute_Reference
1057                       or else Present (Expressions (Argx))
1058                       or else Nkind (Prefix (Argx)) /= N_Identifier)
1059            and then (not Is_Entity_Name (Argx)
1060                       or else not Is_Compilation_Unit (Entity (Argx)))
1061          then
1062             Error_Pragma_Arg ("argument for pragma% must be local name", Argx);
1063          end if;
1064
1065          --  No further check required if not an entity name
1066
1067          if not Is_Entity_Name (Argx) then
1068             null;
1069
1070          else
1071             declare
1072                OK   : Boolean;
1073                Ent  : constant Entity_Id := Entity (Argx);
1074                Scop : constant Entity_Id := Scope (Ent);
1075             begin
1076                --  Case of a pragma applied to a compilation unit: pragma must
1077                --  occur immediately after the program unit in the compilation.
1078
1079                if Is_Compilation_Unit (Ent) then
1080                   declare
1081                      Decl : constant Node_Id := Unit_Declaration_Node (Ent);
1082
1083                   begin
1084                      --  Case of pragma placed immediately after spec
1085
1086                      if Parent (N) = Aux_Decls_Node (Parent (Decl)) then
1087                         OK := True;
1088
1089                      --  Case of pragma placed immediately after body
1090
1091                      elsif Nkind (Decl) = N_Subprogram_Declaration
1092                              and then Present (Corresponding_Body (Decl))
1093                      then
1094                         OK := Parent (N) =
1095                                 Aux_Decls_Node
1096                                   (Parent (Unit_Declaration_Node
1097                                              (Corresponding_Body (Decl))));
1098
1099                      --  All other cases are illegal
1100
1101                      else
1102                         OK := False;
1103                      end if;
1104                   end;
1105
1106                --  Special restricted placement rule from 10.2.1(11.8/2)
1107
1108                elsif Is_Generic_Formal (Ent)
1109                        and then Prag_Id = Pragma_Preelaborable_Initialization
1110                then
1111                   OK := List_Containing (N) =
1112                           Generic_Formal_Declarations
1113                             (Unit_Declaration_Node (Scop));
1114
1115                --  Default case, just check that the pragma occurs in the scope
1116                --  of the entity denoted by the name.
1117
1118                else
1119                   OK := Current_Scope = Scop;
1120                end if;
1121
1122                if not OK then
1123                   Error_Pragma_Arg
1124                     ("pragma% argument must be in same declarative part", Arg);
1125                end if;
1126             end;
1127          end if;
1128       end Check_Arg_Is_Local_Name;
1129
1130       ---------------------------------
1131       -- Check_Arg_Is_Locking_Policy --
1132       ---------------------------------
1133
1134       procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id) is
1135          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1136
1137       begin
1138          Check_Arg_Is_Identifier (Argx);
1139
1140          if not Is_Locking_Policy_Name (Chars (Argx)) then
1141             Error_Pragma_Arg ("& is not a valid locking policy name", Argx);
1142          end if;
1143       end Check_Arg_Is_Locking_Policy;
1144
1145       -------------------------
1146       -- Check_Arg_Is_One_Of --
1147       -------------------------
1148
1149       procedure Check_Arg_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
1150          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1151
1152       begin
1153          Check_Arg_Is_Identifier (Argx);
1154
1155          if Chars (Argx) /= N1 and then Chars (Argx) /= N2 then
1156             Error_Msg_Name_2 := N1;
1157             Error_Msg_Name_3 := N2;
1158             Error_Pragma_Arg ("argument for pragma% must be% or%", Argx);
1159          end if;
1160       end Check_Arg_Is_One_Of;
1161
1162       procedure Check_Arg_Is_One_Of
1163         (Arg        : Node_Id;
1164          N1, N2, N3 : Name_Id)
1165       is
1166          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1167
1168       begin
1169          Check_Arg_Is_Identifier (Argx);
1170
1171          if Chars (Argx) /= N1
1172            and then Chars (Argx) /= N2
1173            and then Chars (Argx) /= N3
1174          then
1175             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1176          end if;
1177       end Check_Arg_Is_One_Of;
1178
1179       procedure Check_Arg_Is_One_Of
1180         (Arg                : Node_Id;
1181          N1, N2, N3, N4, N5 : Name_Id)
1182       is
1183          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1184
1185       begin
1186          Check_Arg_Is_Identifier (Argx);
1187
1188          if Chars (Argx) /= N1
1189            and then Chars (Argx) /= N2
1190            and then Chars (Argx) /= N3
1191            and then Chars (Argx) /= N4
1192            and then Chars (Argx) /= N5
1193          then
1194             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1195          end if;
1196       end Check_Arg_Is_One_Of;
1197       ---------------------------------
1198       -- Check_Arg_Is_Queuing_Policy --
1199       ---------------------------------
1200
1201       procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id) is
1202          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1203
1204       begin
1205          Check_Arg_Is_Identifier (Argx);
1206
1207          if not Is_Queuing_Policy_Name (Chars (Argx)) then
1208             Error_Pragma_Arg ("& is not a valid queuing policy name", Argx);
1209          end if;
1210       end Check_Arg_Is_Queuing_Policy;
1211
1212       ------------------------------------
1213       -- Check_Arg_Is_Static_Expression --
1214       ------------------------------------
1215
1216       procedure Check_Arg_Is_Static_Expression
1217         (Arg : Node_Id;
1218          Typ : Entity_Id := Empty)
1219       is
1220       begin
1221          Check_Expr_Is_Static_Expression (Get_Pragma_Arg (Arg), Typ);
1222       end Check_Arg_Is_Static_Expression;
1223
1224       ------------------------------------------
1225       -- Check_Arg_Is_Task_Dispatching_Policy --
1226       ------------------------------------------
1227
1228       procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id) is
1229          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1230
1231       begin
1232          Check_Arg_Is_Identifier (Argx);
1233
1234          if not Is_Task_Dispatching_Policy_Name (Chars (Argx)) then
1235             Error_Pragma_Arg
1236               ("& is not a valid task dispatching policy name", Argx);
1237          end if;
1238       end Check_Arg_Is_Task_Dispatching_Policy;
1239
1240       ---------------------
1241       -- Check_Arg_Order --
1242       ---------------------
1243
1244       procedure Check_Arg_Order (Names : Name_List) is
1245          Arg : Node_Id;
1246
1247          Highest_So_Far : Natural := 0;
1248          --  Highest index in Names seen do far
1249
1250       begin
1251          Arg := Arg1;
1252          for J in 1 .. Arg_Count loop
1253             if Chars (Arg) /= No_Name then
1254                for K in Names'Range loop
1255                   if Chars (Arg) = Names (K) then
1256                      if K < Highest_So_Far then
1257                         Error_Msg_Name_1 := Pname;
1258                         Error_Msg_N
1259                           ("parameters out of order for pragma%", Arg);
1260                         Error_Msg_Name_1 := Names (K);
1261                         Error_Msg_Name_2 := Names (Highest_So_Far);
1262                         Error_Msg_N ("\% must appear before %", Arg);
1263                         raise Pragma_Exit;
1264
1265                      else
1266                         Highest_So_Far := K;
1267                      end if;
1268                   end if;
1269                end loop;
1270             end if;
1271
1272             Arg := Next (Arg);
1273          end loop;
1274       end Check_Arg_Order;
1275
1276       --------------------------------
1277       -- Check_At_Least_N_Arguments --
1278       --------------------------------
1279
1280       procedure Check_At_Least_N_Arguments (N : Nat) is
1281       begin
1282          if Arg_Count < N then
1283             Error_Pragma ("too few arguments for pragma%");
1284          end if;
1285       end Check_At_Least_N_Arguments;
1286
1287       -------------------------------
1288       -- Check_At_Most_N_Arguments --
1289       -------------------------------
1290
1291       procedure Check_At_Most_N_Arguments (N : Nat) is
1292          Arg : Node_Id;
1293       begin
1294          if Arg_Count > N then
1295             Arg := Arg1;
1296             for J in 1 .. N loop
1297                Next (Arg);
1298                Error_Pragma_Arg ("too many arguments for pragma%", Arg);
1299             end loop;
1300          end if;
1301       end Check_At_Most_N_Arguments;
1302
1303       ---------------------
1304       -- Check_Component --
1305       ---------------------
1306
1307       procedure Check_Component
1308         (Comp            : Node_Id;
1309          UU_Typ          : Entity_Id;
1310          In_Variant_Part : Boolean := False)
1311       is
1312          Comp_Id : constant Entity_Id := Defining_Identifier (Comp);
1313          Sindic  : constant Node_Id :=
1314                      Subtype_Indication (Component_Definition (Comp));
1315          Typ     : constant Entity_Id := Etype (Comp_Id);
1316
1317       begin
1318          --  Ada 2005 (AI-216): If a component subtype is subject to a per-
1319          --  object constraint, then the component type shall be an Unchecked_
1320          --  Union.
1321
1322          if Nkind (Sindic) = N_Subtype_Indication
1323            and then Has_Per_Object_Constraint (Comp_Id)
1324            and then not Is_Unchecked_Union (Etype (Subtype_Mark (Sindic)))
1325          then
1326             Error_Msg_N
1327               ("component subtype subject to per-object constraint " &
1328                "must be an Unchecked_Union", Comp);
1329
1330          --  Ada 2012 (AI05-0026): For an unchecked union type declared within
1331          --  the body of a generic unit, or within the body of any of its
1332          --  descendant library units, no part of the type of a component
1333          --  declared in a variant_part of the unchecked union type shall be of
1334          --  a formal private type or formal private extension declared within
1335          --  the formal part of the generic unit.
1336
1337          elsif Ada_Version >= Ada_2012
1338            and then In_Generic_Body (UU_Typ)
1339            and then In_Variant_Part
1340            and then Is_Private_Type (Typ)
1341            and then Is_Generic_Type (Typ)
1342          then
1343             Error_Msg_N
1344               ("component of Unchecked_Union cannot be of generic type", Comp);
1345
1346          elsif Needs_Finalization (Typ) then
1347             Error_Msg_N
1348               ("component of Unchecked_Union cannot be controlled", Comp);
1349
1350          elsif Has_Task (Typ) then
1351             Error_Msg_N
1352               ("component of Unchecked_Union cannot have tasks", Comp);
1353          end if;
1354       end Check_Component;
1355
1356       ----------------------------
1357       -- Check_Duplicate_Pragma --
1358       ----------------------------
1359
1360       procedure Check_Duplicate_Pragma (E : Entity_Id) is
1361          P : Node_Id;
1362
1363       begin
1364          --  Nothing to do if this pragma comes from an aspect specification,
1365          --  since we could not be duplicating a pragma, and we dealt with the
1366          --  case of duplicated aspects in Analyze_Aspect_Specifications.
1367
1368          if From_Aspect_Specification (N) then
1369             return;
1370          end if;
1371
1372          --  Otherwise current pragma may duplicate previous pragma or a
1373          --  previously given aspect specification for the same pragma.
1374
1375          P := Get_Rep_Item_For_Entity (E, Pragma_Name (N));
1376
1377          if Present (P) then
1378             Error_Msg_Name_1 := Pragma_Name (N);
1379             Error_Msg_Sloc := Sloc (P);
1380
1381             if Nkind (P) = N_Aspect_Specification
1382               or else From_Aspect_Specification (P)
1383             then
1384                Error_Msg_NE ("aspect% for & previously given#", N, E);
1385             else
1386                Error_Msg_NE ("pragma% for & duplicates pragma#", N, E);
1387             end if;
1388
1389             raise Pragma_Exit;
1390          end if;
1391       end Check_Duplicate_Pragma;
1392
1393       ----------------------------------
1394       -- Check_Duplicated_Export_Name --
1395       ----------------------------------
1396
1397       procedure Check_Duplicated_Export_Name (Nam : Node_Id) is
1398          String_Val : constant String_Id := Strval (Nam);
1399
1400       begin
1401          --  We are only interested in the export case, and in the case of
1402          --  generics, it is the instance, not the template, that is the
1403          --  problem (the template will generate a warning in any case).
1404
1405          if not Inside_A_Generic
1406            and then (Prag_Id = Pragma_Export
1407                        or else
1408                      Prag_Id = Pragma_Export_Procedure
1409                        or else
1410                      Prag_Id = Pragma_Export_Valued_Procedure
1411                        or else
1412                      Prag_Id = Pragma_Export_Function)
1413          then
1414             for J in Externals.First .. Externals.Last loop
1415                if String_Equal (String_Val, Strval (Externals.Table (J))) then
1416                   Error_Msg_Sloc := Sloc (Externals.Table (J));
1417                   Error_Msg_N ("external name duplicates name given#", Nam);
1418                   exit;
1419                end if;
1420             end loop;
1421
1422             Externals.Append (Nam);
1423          end if;
1424       end Check_Duplicated_Export_Name;
1425
1426       -------------------------------------
1427       -- Check_Expr_Is_Static_Expression --
1428       -------------------------------------
1429
1430       procedure Check_Expr_Is_Static_Expression
1431         (Expr : Node_Id;
1432          Typ  : Entity_Id := Empty)
1433       is
1434       begin
1435          if Present (Typ) then
1436             Analyze_And_Resolve (Expr, Typ);
1437          else
1438             Analyze_And_Resolve (Expr);
1439          end if;
1440
1441          if Is_OK_Static_Expression (Expr) then
1442             return;
1443
1444          elsif Etype (Expr) = Any_Type then
1445             raise Pragma_Exit;
1446
1447          --  An interesting special case, if we have a string literal and we
1448          --  are in Ada 83 mode, then we allow it even though it will not be
1449          --  flagged as static. This allows the use of Ada 95 pragmas like
1450          --  Import in Ada 83 mode. They will of course be flagged with
1451          --  warnings as usual, but will not cause errors.
1452
1453          elsif Ada_Version = Ada_83
1454            and then Nkind (Expr) = N_String_Literal
1455          then
1456             return;
1457
1458          --  Static expression that raises Constraint_Error. This has already
1459          --  been flagged, so just exit from pragma processing.
1460
1461          elsif Is_Static_Expression (Expr) then
1462             raise Pragma_Exit;
1463
1464          --  Finally, we have a real error
1465
1466          else
1467             Error_Msg_Name_1 := Pname;
1468
1469             declare
1470                Msg : String :=
1471                        "argument for pragma% must be a static expression!";
1472             begin
1473                Fix_Error (Msg);
1474                Flag_Non_Static_Expr (Msg, Expr);
1475             end;
1476
1477             raise Pragma_Exit;
1478          end if;
1479       end Check_Expr_Is_Static_Expression;
1480
1481       -------------------------
1482       -- Check_First_Subtype --
1483       -------------------------
1484
1485       procedure Check_First_Subtype (Arg : Node_Id) is
1486          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1487          Ent  : constant Entity_Id := Entity (Argx);
1488
1489       begin
1490          if Is_First_Subtype (Ent) then
1491             null;
1492
1493          elsif Is_Type (Ent) then
1494             Error_Pragma_Arg
1495               ("pragma% cannot apply to subtype", Argx);
1496
1497          elsif Is_Object (Ent) then
1498             Error_Pragma_Arg
1499               ("pragma% cannot apply to object, requires a type", Argx);
1500
1501          else
1502             Error_Pragma_Arg
1503               ("pragma% cannot apply to&, requires a type", Argx);
1504          end if;
1505       end Check_First_Subtype;
1506
1507       ----------------------
1508       -- Check_Identifier --
1509       ----------------------
1510
1511       procedure Check_Identifier (Arg : Node_Id; Id : Name_Id) is
1512       begin
1513          if Present (Arg)
1514            and then Nkind (Arg) = N_Pragma_Argument_Association
1515          then
1516             if Chars (Arg) = No_Name or else Chars (Arg) /= Id then
1517                Error_Msg_Name_1 := Pname;
1518                Error_Msg_Name_2 := Id;
1519                Error_Msg_N ("pragma% argument expects identifier%", Arg);
1520                raise Pragma_Exit;
1521             end if;
1522          end if;
1523       end Check_Identifier;
1524
1525       --------------------------------
1526       -- Check_Identifier_Is_One_Of --
1527       --------------------------------
1528
1529       procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
1530       begin
1531          if Present (Arg)
1532            and then Nkind (Arg) = N_Pragma_Argument_Association
1533          then
1534             if Chars (Arg) = No_Name then
1535                Error_Msg_Name_1 := Pname;
1536                Error_Msg_N ("pragma% argument expects an identifier", Arg);
1537                raise Pragma_Exit;
1538
1539             elsif Chars (Arg) /= N1
1540               and then Chars (Arg) /= N2
1541             then
1542                Error_Msg_Name_1 := Pname;
1543                Error_Msg_N ("invalid identifier for pragma% argument", Arg);
1544                raise Pragma_Exit;
1545             end if;
1546          end if;
1547       end Check_Identifier_Is_One_Of;
1548
1549       ---------------------------
1550       -- Check_In_Main_Program --
1551       ---------------------------
1552
1553       procedure Check_In_Main_Program is
1554          P : constant Node_Id := Parent (N);
1555
1556       begin
1557          --  Must be at in subprogram body
1558
1559          if Nkind (P) /= N_Subprogram_Body then
1560             Error_Pragma ("% pragma allowed only in subprogram");
1561
1562          --  Otherwise warn if obviously not main program
1563
1564          elsif Present (Parameter_Specifications (Specification (P)))
1565            or else not Is_Compilation_Unit (Defining_Entity (P))
1566          then
1567             Error_Msg_Name_1 := Pname;
1568             Error_Msg_N
1569               ("?pragma% is only effective in main program", N);
1570          end if;
1571       end Check_In_Main_Program;
1572
1573       ---------------------------------------
1574       -- Check_Interrupt_Or_Attach_Handler --
1575       ---------------------------------------
1576
1577       procedure Check_Interrupt_Or_Attach_Handler is
1578          Arg1_X : constant Node_Id := Get_Pragma_Arg (Arg1);
1579          Handler_Proc, Proc_Scope : Entity_Id;
1580
1581       begin
1582          Analyze (Arg1_X);
1583
1584          if Prag_Id = Pragma_Interrupt_Handler then
1585             Check_Restriction (No_Dynamic_Attachment, N);
1586          end if;
1587
1588          Handler_Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
1589          Proc_Scope := Scope (Handler_Proc);
1590
1591          --  On AAMP only, a pragma Interrupt_Handler is supported for
1592          --  nonprotected parameterless procedures.
1593
1594          if not AAMP_On_Target
1595            or else Prag_Id = Pragma_Attach_Handler
1596          then
1597             if Ekind (Proc_Scope) /= E_Protected_Type then
1598                Error_Pragma_Arg
1599                  ("argument of pragma% must be protected procedure", Arg1);
1600             end if;
1601
1602             if Parent (N) /= Protected_Definition (Parent (Proc_Scope)) then
1603                Error_Pragma ("pragma% must be in protected definition");
1604             end if;
1605          end if;
1606
1607          if not Is_Library_Level_Entity (Proc_Scope)
1608            or else (AAMP_On_Target
1609                      and then not Is_Library_Level_Entity (Handler_Proc))
1610          then
1611             Error_Pragma_Arg
1612               ("argument for pragma% must be library level entity", Arg1);
1613          end if;
1614
1615          --  AI05-0033: A pragma cannot appear within a generic body, because
1616          --  instance can be in a nested scope. The check that protected type
1617          --  is itself a library-level declaration is done elsewhere.
1618
1619          --  Note: we omit this check in Codepeer mode to properly handle code
1620          --  prior to AI-0033 (pragmas don't matter to codepeer in any case).
1621
1622          if Inside_A_Generic then
1623             if Ekind (Scope (Current_Scope)) = E_Generic_Package
1624               and then In_Package_Body (Scope (Current_Scope))
1625               and then not CodePeer_Mode
1626             then
1627                Error_Pragma ("pragma% cannot be used inside a generic");
1628             end if;
1629          end if;
1630       end Check_Interrupt_Or_Attach_Handler;
1631
1632       -------------------------------------------
1633       -- Check_Is_In_Decl_Part_Or_Package_Spec --
1634       -------------------------------------------
1635
1636       procedure Check_Is_In_Decl_Part_Or_Package_Spec is
1637          P : Node_Id;
1638
1639       begin
1640          P := Parent (N);
1641          loop
1642             if No (P) then
1643                exit;
1644
1645             elsif Nkind (P) = N_Handled_Sequence_Of_Statements then
1646                exit;
1647
1648             elsif Nkind_In (P, N_Package_Specification,
1649                                N_Block_Statement)
1650             then
1651                return;
1652
1653             --  Note: the following tests seem a little peculiar, because
1654             --  they test for bodies, but if we were in the statement part
1655             --  of the body, we would already have hit the handled statement
1656             --  sequence, so the only way we get here is by being in the
1657             --  declarative part of the body.
1658
1659             elsif Nkind_In (P, N_Subprogram_Body,
1660                                N_Package_Body,
1661                                N_Task_Body,
1662                                N_Entry_Body)
1663             then
1664                return;
1665             end if;
1666
1667             P := Parent (P);
1668          end loop;
1669
1670          Error_Pragma ("pragma% is not in declarative part or package spec");
1671       end Check_Is_In_Decl_Part_Or_Package_Spec;
1672
1673       -------------------------
1674       -- Check_No_Identifier --
1675       -------------------------
1676
1677       procedure Check_No_Identifier (Arg : Node_Id) is
1678       begin
1679          if Nkind (Arg) = N_Pragma_Argument_Association
1680            and then Chars (Arg) /= No_Name
1681          then
1682             Error_Pragma_Arg_Ident
1683               ("pragma% does not permit identifier& here", Arg);
1684          end if;
1685       end Check_No_Identifier;
1686
1687       --------------------------
1688       -- Check_No_Identifiers --
1689       --------------------------
1690
1691       procedure Check_No_Identifiers is
1692          Arg_Node : Node_Id;
1693       begin
1694          if Arg_Count > 0 then
1695             Arg_Node := Arg1;
1696             while Present (Arg_Node) loop
1697                Check_No_Identifier (Arg_Node);
1698                Next (Arg_Node);
1699             end loop;
1700          end if;
1701       end Check_No_Identifiers;
1702
1703       ------------------------
1704       -- Check_No_Link_Name --
1705       ------------------------
1706
1707       procedure Check_No_Link_Name is
1708       begin
1709          if Present (Arg3)
1710            and then Chars (Arg3) = Name_Link_Name
1711          then
1712             Arg4 := Arg3;
1713          end if;
1714
1715          if Present (Arg4) then
1716             Error_Pragma_Arg
1717               ("Link_Name argument not allowed for Import Intrinsic", Arg4);
1718          end if;
1719       end Check_No_Link_Name;
1720
1721       -------------------------------
1722       -- Check_Optional_Identifier --
1723       -------------------------------
1724
1725       procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id) is
1726       begin
1727          if Present (Arg)
1728            and then Nkind (Arg) = N_Pragma_Argument_Association
1729            and then Chars (Arg) /= No_Name
1730          then
1731             if Chars (Arg) /= Id then
1732                Error_Msg_Name_1 := Pname;
1733                Error_Msg_Name_2 := Id;
1734                Error_Msg_N ("pragma% argument expects identifier%", Arg);
1735                raise Pragma_Exit;
1736             end if;
1737          end if;
1738       end Check_Optional_Identifier;
1739
1740       procedure Check_Optional_Identifier (Arg : Node_Id; Id : String) is
1741       begin
1742          Name_Buffer (1 .. Id'Length) := Id;
1743          Name_Len := Id'Length;
1744          Check_Optional_Identifier (Arg, Name_Find);
1745       end Check_Optional_Identifier;
1746
1747       --------------------------------------
1748       -- Check_Precondition_Postcondition --
1749       --------------------------------------
1750
1751       procedure Check_Precondition_Postcondition (In_Body : out Boolean) is
1752          P  : Node_Id;
1753          PO : Node_Id;
1754
1755          procedure Chain_PPC (PO : Node_Id);
1756          --  If PO is an entry or a [generic] subprogram declaration node, then
1757          --  the precondition/postcondition applies to this subprogram and the
1758          --  processing for the pragma is completed. Otherwise the pragma is
1759          --  misplaced.
1760
1761          ---------------
1762          -- Chain_PPC --
1763          ---------------
1764
1765          procedure Chain_PPC (PO : Node_Id) is
1766             S   : Entity_Id;
1767             P   : Node_Id;
1768
1769          begin
1770             if Nkind (PO) = N_Abstract_Subprogram_Declaration then
1771                if not From_Aspect_Specification (N) then
1772                   Error_Pragma
1773                     ("pragma% cannot be applied to abstract subprogram");
1774
1775                elsif Class_Present (N) then
1776                   null;
1777
1778                else
1779                   Error_Pragma
1780                     ("aspect % requires ''Class for abstract subprogram");
1781                end if;
1782
1783             --  AI05-0230: The same restriction applies to null procedures. For
1784             --  compatibility with earlier uses of the Ada pragma, apply this
1785             --  rule only to aspect specifications.
1786
1787             --  The above discrpency needs documentation. Robert is dubious
1788             --  about whether it is a good idea ???
1789
1790             elsif Nkind (PO) = N_Subprogram_Declaration
1791               and then Nkind (Specification (PO)) = N_Procedure_Specification
1792               and then Null_Present (Specification (PO))
1793               and then From_Aspect_Specification (N)
1794               and then not Class_Present (N)
1795             then
1796                Error_Pragma
1797                  ("aspect % requires ''Class for null procedure");
1798
1799             elsif not Nkind_In (PO, N_Subprogram_Declaration,
1800                                     N_Generic_Subprogram_Declaration,
1801                                     N_Entry_Declaration)
1802             then
1803                Pragma_Misplaced;
1804             end if;
1805
1806             --  Here if we have [generic] subprogram or entry declaration
1807
1808             if Nkind (PO) = N_Entry_Declaration then
1809                S := Defining_Entity (PO);
1810             else
1811                S := Defining_Unit_Name (Specification (PO));
1812             end if;
1813
1814             --  Make sure we do not have the case of a precondition pragma when
1815             --  the Pre'Class aspect is present.
1816
1817             --  We do this by looking at pragmas already chained to the entity
1818             --  since the aspect derived pragma will be put on this list first.
1819
1820             if Pragma_Name (N) = Name_Precondition then
1821                if not From_Aspect_Specification (N) then
1822                   P := Spec_PPC_List (Contract (S));
1823                   while Present (P) loop
1824                      if Pragma_Name (P) = Name_Precondition
1825                        and then From_Aspect_Specification (P)
1826                        and then Class_Present (P)
1827                      then
1828                         Error_Msg_Sloc := Sloc (P);
1829                         Error_Pragma
1830                           ("pragma% not allowed, `Pre''Class` aspect given#");
1831                      end if;
1832
1833                      P := Next_Pragma (P);
1834                   end loop;
1835                end if;
1836             end if;
1837
1838             --  Similarly check for Pre with inherited Pre'Class. Note that
1839             --  we cover the aspect case as well here.
1840
1841             if Pragma_Name (N) = Name_Precondition
1842               and then not Class_Present (N)
1843             then
1844                declare
1845                   Inherited : constant Subprogram_List :=
1846                                 Inherited_Subprograms (S);
1847                   P         : Node_Id;
1848
1849                begin
1850                   for J in Inherited'Range loop
1851                      P := Spec_PPC_List (Contract (Inherited (J)));
1852                      while Present (P) loop
1853                         if Pragma_Name (P) = Name_Precondition
1854                           and then Class_Present (P)
1855                         then
1856                            Error_Msg_Sloc := Sloc (P);
1857                            Error_Pragma
1858                              ("pragma% not allowed, `Pre''Class` "
1859                               & "aspect inherited from#");
1860                         end if;
1861
1862                         P := Next_Pragma (P);
1863                      end loop;
1864                   end loop;
1865                end;
1866             end if;
1867
1868             --  Note: we do not analyze the pragma at this point. Instead we
1869             --  delay this analysis until the end of the declarative part in
1870             --  which the pragma appears. This implements the required delay
1871             --  in this analysis, allowing forward references. The analysis
1872             --  happens at the end of Analyze_Declarations.
1873
1874             --  Chain spec PPC pragma to list for subprogram
1875
1876             Set_Next_Pragma (N, Spec_PPC_List (Contract (S)));
1877             Set_Spec_PPC_List (Contract (S), N);
1878
1879             --  Return indicating spec case
1880
1881             In_Body := False;
1882             return;
1883          end Chain_PPC;
1884
1885       --  Start of processing for Check_Precondition_Postcondition
1886
1887       begin
1888          if not Is_List_Member (N) then
1889             Pragma_Misplaced;
1890          end if;
1891
1892          --  Preanalyze message argument if present. Visibility in this
1893          --  argument is established at the point of pragma occurrence.
1894
1895          if Arg_Count = 2 then
1896             Check_Optional_Identifier (Arg2, Name_Message);
1897             Preanalyze_Spec_Expression
1898               (Get_Pragma_Arg (Arg2), Standard_String);
1899          end if;
1900
1901          --  Record if pragma is disabled
1902
1903          if Check_Enabled (Pname) then
1904             Set_SCO_Pragma_Enabled (Loc);
1905          end if;
1906
1907          --  If we are within an inlined body, the legality of the pragma
1908          --  has been checked already.
1909
1910          if In_Inlined_Body then
1911             In_Body := True;
1912             return;
1913          end if;
1914
1915          --  Search prior declarations
1916
1917          P := N;
1918          while Present (Prev (P)) loop
1919             P := Prev (P);
1920
1921             --  If the previous node is a generic subprogram, do not go to to
1922             --  the original node, which is the unanalyzed tree: we need to
1923             --  attach the pre/postconditions to the analyzed version at this
1924             --  point. They get propagated to the original tree when analyzing
1925             --  the corresponding body.
1926
1927             if Nkind (P) not in N_Generic_Declaration then
1928                PO := Original_Node (P);
1929             else
1930                PO := P;
1931             end if;
1932
1933             --  Skip past prior pragma
1934
1935             if Nkind (PO) = N_Pragma then
1936                null;
1937
1938             --  Skip stuff not coming from source
1939
1940             elsif not Comes_From_Source (PO) then
1941
1942                --  The condition may apply to a subprogram instantiation
1943
1944                if Nkind (PO) = N_Subprogram_Declaration
1945                  and then Present (Generic_Parent (Specification (PO)))
1946                then
1947                   Chain_PPC (PO);
1948                   return;
1949
1950                elsif Nkind (PO) = N_Subprogram_Declaration
1951                  and then In_Instance
1952                then
1953                   Chain_PPC (PO);
1954                   return;
1955
1956                --  For all other cases of non source code, do nothing
1957
1958                else
1959                   null;
1960                end if;
1961
1962             --  Only remaining possibility is subprogram declaration
1963
1964             else
1965                Chain_PPC (PO);
1966                return;
1967             end if;
1968          end loop;
1969
1970          --  If we fall through loop, pragma is at start of list, so see if it
1971          --  is at the start of declarations of a subprogram body.
1972
1973          if Nkind (Parent (N)) = N_Subprogram_Body
1974            and then List_Containing (N) = Declarations (Parent (N))
1975          then
1976             if Operating_Mode /= Generate_Code
1977               or else Inside_A_Generic
1978             then
1979                --  Analyze pragma expression for correctness and for ASIS use
1980
1981                Preanalyze_Spec_Expression
1982                  (Get_Pragma_Arg (Arg1), Standard_Boolean);
1983
1984                --  In ASIS mode, for a pragma generated from a source aspect,
1985                --  also analyze the original aspect expression.
1986
1987                if ASIS_Mode
1988                  and then Present (Corresponding_Aspect (N))
1989                then
1990                   Preanalyze_Spec_Expression
1991                     (Expression (Corresponding_Aspect (N)), Standard_Boolean);
1992                end if;
1993             end if;
1994
1995             In_Body := True;
1996             return;
1997
1998          --  See if it is in the pragmas after a library level subprogram
1999
2000          elsif Nkind (Parent (N)) = N_Compilation_Unit_Aux then
2001
2002             --  In formal verification mode, analyze pragma expression for
2003             --  correctness, as it is not expanded later.
2004
2005             if Alfa_Mode then
2006                Analyze_PPC_In_Decl_Part
2007                  (N, Defining_Entity (Unit (Parent (Parent (N)))));
2008             end if;
2009
2010             Chain_PPC (Unit (Parent (Parent (N))));
2011             return;
2012          end if;
2013
2014          --  If we fall through, pragma was misplaced
2015
2016          Pragma_Misplaced;
2017       end Check_Precondition_Postcondition;
2018
2019       -----------------------------
2020       -- Check_Static_Constraint --
2021       -----------------------------
2022
2023       --  Note: for convenience in writing this procedure, in addition to
2024       --  the officially (i.e. by spec) allowed argument which is always a
2025       --  constraint, it also allows ranges and discriminant associations.
2026       --  Above is not clear ???
2027
2028       procedure Check_Static_Constraint (Constr : Node_Id) is
2029
2030          procedure Require_Static (E : Node_Id);
2031          --  Require given expression to be static expression
2032
2033          --------------------
2034          -- Require_Static --
2035          --------------------
2036
2037          procedure Require_Static (E : Node_Id) is
2038          begin
2039             if not Is_OK_Static_Expression (E) then
2040                Flag_Non_Static_Expr
2041                  ("non-static constraint not allowed in Unchecked_Union!", E);
2042                raise Pragma_Exit;
2043             end if;
2044          end Require_Static;
2045
2046       --  Start of processing for Check_Static_Constraint
2047
2048       begin
2049          case Nkind (Constr) is
2050             when N_Discriminant_Association =>
2051                Require_Static (Expression (Constr));
2052
2053             when N_Range =>
2054                Require_Static (Low_Bound (Constr));
2055                Require_Static (High_Bound (Constr));
2056
2057             when N_Attribute_Reference =>
2058                Require_Static (Type_Low_Bound  (Etype (Prefix (Constr))));
2059                Require_Static (Type_High_Bound (Etype (Prefix (Constr))));
2060
2061             when N_Range_Constraint =>
2062                Check_Static_Constraint (Range_Expression (Constr));
2063
2064             when N_Index_Or_Discriminant_Constraint =>
2065                declare
2066                   IDC : Entity_Id;
2067                begin
2068                   IDC := First (Constraints (Constr));
2069                   while Present (IDC) loop
2070                      Check_Static_Constraint (IDC);
2071                      Next (IDC);
2072                   end loop;
2073                end;
2074
2075             when others =>
2076                null;
2077          end case;
2078       end Check_Static_Constraint;
2079
2080       ---------------------
2081       -- Check_Test_Case --
2082       ---------------------
2083
2084       procedure Check_Test_Case is
2085          P  : Node_Id;
2086          PO : Node_Id;
2087
2088          procedure Chain_TC (PO : Node_Id);
2089          --  If PO is a [generic] subprogram declaration node, then the
2090          --  test-case applies to this subprogram and the processing for the
2091          --  pragma is completed. Otherwise the pragma is misplaced.
2092
2093          --------------
2094          -- Chain_TC --
2095          --------------
2096
2097          procedure Chain_TC (PO : Node_Id) is
2098             S   : Entity_Id;
2099
2100          begin
2101             if Nkind (PO) = N_Abstract_Subprogram_Declaration then
2102                if From_Aspect_Specification (N) then
2103                   Error_Pragma
2104                     ("aspect% cannot be applied to abstract subprogram");
2105                else
2106                   Error_Pragma
2107                     ("pragma% cannot be applied to abstract subprogram");
2108                end if;
2109
2110             elsif Nkind (PO) = N_Entry_Declaration then
2111                if From_Aspect_Specification (N) then
2112                   Error_Pragma ("aspect% cannot be applied to entry");
2113                else
2114                   Error_Pragma ("pragma% cannot be applied to entry");
2115                end if;
2116
2117             elsif not Nkind_In (PO, N_Subprogram_Declaration,
2118                                     N_Generic_Subprogram_Declaration)
2119             then
2120                Pragma_Misplaced;
2121             end if;
2122
2123             --  Here if we have [generic] subprogram declaration
2124
2125             S := Defining_Unit_Name (Specification (PO));
2126
2127             --  Note: we do not analyze the pragma at this point. Instead we
2128             --  delay this analysis until the end of the declarative part in
2129             --  which the pragma appears. This implements the required delay
2130             --  in this analysis, allowing forward references. The analysis
2131             --  happens at the end of Analyze_Declarations.
2132
2133             --  There should not be another test case with the same name
2134             --  associated to this subprogram.
2135
2136             declare
2137                Name : constant String_Id := Get_Name_From_Test_Case_Pragma (N);
2138                TC   : Node_Id;
2139
2140             begin
2141                TC := Spec_TC_List (Contract (S));
2142                while Present (TC) loop
2143
2144                   if String_Equal
2145                     (Name, Get_Name_From_Test_Case_Pragma (TC))
2146                   then
2147                      Error_Msg_Sloc := Sloc (TC);
2148
2149                      if From_Aspect_Specification (N) then
2150                         Error_Pragma ("name for aspect% is already used#");
2151                      else
2152                         Error_Pragma ("name for pragma% is already used#");
2153                      end if;
2154                   end if;
2155
2156                   TC := Next_Pragma (TC);
2157                end loop;
2158             end;
2159
2160             --  Chain spec TC pragma to list for subprogram
2161
2162             Set_Next_Pragma (N, Spec_TC_List (Contract (S)));
2163             Set_Spec_TC_List (Contract (S), N);
2164          end Chain_TC;
2165
2166       --  Start of processing for Check_Test_Case
2167
2168       begin
2169          if not Is_List_Member (N) then
2170             Pragma_Misplaced;
2171          end if;
2172
2173          --  Test cases should only appear in package spec unit
2174
2175          if Get_Source_Unit (N) = No_Unit
2176            or else not Nkind_In (Sinfo.Unit (Cunit (Get_Source_Unit (N))),
2177                                  N_Package_Declaration,
2178                                  N_Generic_Package_Declaration)
2179          then
2180             Pragma_Misplaced;
2181          end if;
2182
2183          --  Search prior declarations
2184
2185          P := N;
2186          while Present (Prev (P)) loop
2187             P := Prev (P);
2188
2189             --  If the previous node is a generic subprogram, do not go to to
2190             --  the original node, which is the unanalyzed tree: we need to
2191             --  attach the test-case to the analyzed version at this point.
2192             --  They get propagated to the original tree when analyzing the
2193             --  corresponding body.
2194
2195             if Nkind (P) not in N_Generic_Declaration then
2196                PO := Original_Node (P);
2197             else
2198                PO := P;
2199             end if;
2200
2201             --  Skip past prior pragma
2202
2203             if Nkind (PO) = N_Pragma then
2204                null;
2205
2206             --  Skip stuff not coming from source
2207
2208             elsif not Comes_From_Source (PO) then
2209                null;
2210
2211             --  Only remaining possibility is subprogram declaration. First
2212             --  check that it is declared directly in a package declaration.
2213             --  This may be either the package declaration for the current unit
2214             --  being defined or a local package declaration.
2215
2216             elsif not Present (Parent (Parent (PO)))
2217               or else not Present (Parent (Parent (Parent (PO))))
2218               or else not Nkind_In (Parent (Parent (PO)),
2219                                     N_Package_Declaration,
2220                                     N_Generic_Package_Declaration)
2221             then
2222                Pragma_Misplaced;
2223
2224             else
2225                Chain_TC (PO);
2226                return;
2227             end if;
2228          end loop;
2229
2230          --  If we fall through, pragma was misplaced
2231
2232          Pragma_Misplaced;
2233       end Check_Test_Case;
2234
2235       --------------------------------------
2236       -- Check_Valid_Configuration_Pragma --
2237       --------------------------------------
2238
2239       --  A configuration pragma must appear in the context clause of a
2240       --  compilation unit, and only other pragmas may precede it. Note that
2241       --  the test also allows use in a configuration pragma file.
2242
2243       procedure Check_Valid_Configuration_Pragma is
2244       begin
2245          if not Is_Configuration_Pragma then
2246             Error_Pragma ("incorrect placement for configuration pragma%");
2247          end if;
2248       end Check_Valid_Configuration_Pragma;
2249
2250       -------------------------------------
2251       -- Check_Valid_Library_Unit_Pragma --
2252       -------------------------------------
2253
2254       procedure Check_Valid_Library_Unit_Pragma is
2255          Plist       : List_Id;
2256          Parent_Node : Node_Id;
2257          Unit_Name   : Entity_Id;
2258          Unit_Kind   : Node_Kind;
2259          Unit_Node   : Node_Id;
2260          Sindex      : Source_File_Index;
2261
2262       begin
2263          if not Is_List_Member (N) then
2264             Pragma_Misplaced;
2265
2266          else
2267             Plist := List_Containing (N);
2268             Parent_Node := Parent (Plist);
2269
2270             if Parent_Node = Empty then
2271                Pragma_Misplaced;
2272
2273             --  Case of pragma appearing after a compilation unit. In this case
2274             --  it must have an argument with the corresponding name and must
2275             --  be part of the following pragmas of its parent.
2276
2277             elsif Nkind (Parent_Node) = N_Compilation_Unit_Aux then
2278                if Plist /= Pragmas_After (Parent_Node) then
2279                   Pragma_Misplaced;
2280
2281                elsif Arg_Count = 0 then
2282                   Error_Pragma
2283                     ("argument required if outside compilation unit");
2284
2285                else
2286                   Check_No_Identifiers;
2287                   Check_Arg_Count (1);
2288                   Unit_Node := Unit (Parent (Parent_Node));
2289                   Unit_Kind := Nkind (Unit_Node);
2290
2291                   Analyze (Get_Pragma_Arg (Arg1));
2292
2293                   if Unit_Kind = N_Generic_Subprogram_Declaration
2294                     or else Unit_Kind = N_Subprogram_Declaration
2295                   then
2296                      Unit_Name := Defining_Entity (Unit_Node);
2297
2298                   elsif Unit_Kind in N_Generic_Instantiation then
2299                      Unit_Name := Defining_Entity (Unit_Node);
2300
2301                   else
2302                      Unit_Name := Cunit_Entity (Current_Sem_Unit);
2303                   end if;
2304
2305                   if Chars (Unit_Name) /=
2306                      Chars (Entity (Get_Pragma_Arg (Arg1)))
2307                   then
2308                      Error_Pragma_Arg
2309                        ("pragma% argument is not current unit name", Arg1);
2310                   end if;
2311
2312                   if Ekind (Unit_Name) = E_Package
2313                     and then Present (Renamed_Entity (Unit_Name))
2314                   then
2315                      Error_Pragma ("pragma% not allowed for renamed package");
2316                   end if;
2317                end if;
2318
2319             --  Pragma appears other than after a compilation unit
2320
2321             else
2322                --  Here we check for the generic instantiation case and also
2323                --  for the case of processing a generic formal package. We
2324                --  detect these cases by noting that the Sloc on the node
2325                --  does not belong to the current compilation unit.
2326
2327                Sindex := Source_Index (Current_Sem_Unit);
2328
2329                if Loc not in Source_First (Sindex) .. Source_Last (Sindex) then
2330                   Rewrite (N, Make_Null_Statement (Loc));
2331                   return;
2332
2333                --  If before first declaration, the pragma applies to the
2334                --  enclosing unit, and the name if present must be this name.
2335
2336                elsif Is_Before_First_Decl (N, Plist) then
2337                   Unit_Node := Unit_Declaration_Node (Current_Scope);
2338                   Unit_Kind := Nkind (Unit_Node);
2339
2340                   if Nkind (Parent (Unit_Node)) /= N_Compilation_Unit then
2341                      Pragma_Misplaced;
2342
2343                   elsif Unit_Kind = N_Subprogram_Body
2344                     and then not Acts_As_Spec (Unit_Node)
2345                   then
2346                      Pragma_Misplaced;
2347
2348                   elsif Nkind (Parent_Node) = N_Package_Body then
2349                      Pragma_Misplaced;
2350
2351                   elsif Nkind (Parent_Node) = N_Package_Specification
2352                     and then Plist = Private_Declarations (Parent_Node)
2353                   then
2354                      Pragma_Misplaced;
2355
2356                   elsif (Nkind (Parent_Node) = N_Generic_Package_Declaration
2357                            or else Nkind (Parent_Node) =
2358                                              N_Generic_Subprogram_Declaration)
2359                     and then Plist = Generic_Formal_Declarations (Parent_Node)
2360                   then
2361                      Pragma_Misplaced;
2362
2363                   elsif Arg_Count > 0 then
2364                      Analyze (Get_Pragma_Arg (Arg1));
2365
2366                      if Entity (Get_Pragma_Arg (Arg1)) /= Current_Scope then
2367                         Error_Pragma_Arg
2368                           ("name in pragma% must be enclosing unit", Arg1);
2369                      end if;
2370
2371                   --  It is legal to have no argument in this context
2372
2373                   else
2374                      return;
2375                   end if;
2376
2377                --  Error if not before first declaration. This is because a
2378                --  library unit pragma argument must be the name of a library
2379                --  unit (RM 10.1.5(7)), but the only names permitted in this
2380                --  context are (RM 10.1.5(6)) names of subprogram declarations,
2381                --  generic subprogram declarations or generic instantiations.
2382
2383                else
2384                   Error_Pragma
2385                     ("pragma% misplaced, must be before first declaration");
2386                end if;
2387             end if;
2388          end if;
2389       end Check_Valid_Library_Unit_Pragma;
2390
2391       -------------------
2392       -- Check_Variant --
2393       -------------------
2394
2395       procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id) is
2396          Clist : constant Node_Id := Component_List (Variant);
2397          Comp  : Node_Id;
2398
2399       begin
2400          if not Is_Non_Empty_List (Component_Items (Clist)) then
2401             Error_Msg_N
2402               ("Unchecked_Union may not have empty component list",
2403                Variant);
2404             return;
2405          end if;
2406
2407          Comp := First (Component_Items (Clist));
2408          while Present (Comp) loop
2409             Check_Component (Comp, UU_Typ, In_Variant_Part => True);
2410             Next (Comp);
2411          end loop;
2412       end Check_Variant;
2413
2414       ------------------
2415       -- Error_Pragma --
2416       ------------------
2417
2418       procedure Error_Pragma (Msg : String) is
2419          MsgF : String := Msg;
2420       begin
2421          Error_Msg_Name_1 := Pname;
2422          Fix_Error (MsgF);
2423          Error_Msg_N (MsgF, N);
2424          raise Pragma_Exit;
2425       end Error_Pragma;
2426
2427       ----------------------
2428       -- Error_Pragma_Arg --
2429       ----------------------
2430
2431       procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id) is
2432          MsgF : String := Msg;
2433       begin
2434          Error_Msg_Name_1 := Pname;
2435          Fix_Error (MsgF);
2436          Error_Msg_N (MsgF, Get_Pragma_Arg (Arg));
2437          raise Pragma_Exit;
2438       end Error_Pragma_Arg;
2439
2440       procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id) is
2441          MsgF : String := Msg1;
2442       begin
2443          Error_Msg_Name_1 := Pname;
2444          Fix_Error (MsgF);
2445          Error_Msg_N (MsgF, Get_Pragma_Arg (Arg));
2446          Error_Pragma_Arg (Msg2, Arg);
2447       end Error_Pragma_Arg;
2448
2449       ----------------------------
2450       -- Error_Pragma_Arg_Ident --
2451       ----------------------------
2452
2453       procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id) is
2454          MsgF : String := Msg;
2455       begin
2456          Error_Msg_Name_1 := Pname;
2457          Fix_Error (MsgF);
2458          Error_Msg_N (MsgF, Arg);
2459          raise Pragma_Exit;
2460       end Error_Pragma_Arg_Ident;
2461
2462       ----------------------
2463       -- Error_Pragma_Ref --
2464       ----------------------
2465
2466       procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id) is
2467          MsgF : String := Msg;
2468       begin
2469          Error_Msg_Name_1 := Pname;
2470          Fix_Error (MsgF);
2471          Error_Msg_Sloc   := Sloc (Ref);
2472          Error_Msg_NE (MsgF, N, Ref);
2473          raise Pragma_Exit;
2474       end Error_Pragma_Ref;
2475
2476       ------------------------
2477       -- Find_Lib_Unit_Name --
2478       ------------------------
2479
2480       function Find_Lib_Unit_Name return Entity_Id is
2481       begin
2482          --  Return inner compilation unit entity, for case of nested
2483          --  categorization pragmas. This happens in generic unit.
2484
2485          if Nkind (Parent (N)) = N_Package_Specification
2486            and then Defining_Entity (Parent (N)) /= Current_Scope
2487          then
2488             return Defining_Entity (Parent (N));
2489          else
2490             return Current_Scope;
2491          end if;
2492       end Find_Lib_Unit_Name;
2493
2494       ----------------------------
2495       -- Find_Program_Unit_Name --
2496       ----------------------------
2497
2498       procedure Find_Program_Unit_Name (Id : Node_Id) is
2499          Unit_Name : Entity_Id;
2500          Unit_Kind : Node_Kind;
2501          P         : constant Node_Id := Parent (N);
2502
2503       begin
2504          if Nkind (P) = N_Compilation_Unit then
2505             Unit_Kind := Nkind (Unit (P));
2506
2507             if Unit_Kind = N_Subprogram_Declaration
2508               or else Unit_Kind = N_Package_Declaration
2509               or else Unit_Kind in N_Generic_Declaration
2510             then
2511                Unit_Name := Defining_Entity (Unit (P));
2512
2513                if Chars (Id) = Chars (Unit_Name) then
2514                   Set_Entity (Id, Unit_Name);
2515                   Set_Etype (Id, Etype (Unit_Name));
2516                else
2517                   Set_Etype (Id, Any_Type);
2518                   Error_Pragma
2519                     ("cannot find program unit referenced by pragma%");
2520                end if;
2521
2522             else
2523                Set_Etype (Id, Any_Type);
2524                Error_Pragma ("pragma% inapplicable to this unit");
2525             end if;
2526
2527          else
2528             Analyze (Id);
2529          end if;
2530       end Find_Program_Unit_Name;
2531
2532       -----------------------------------------
2533       -- Find_Unique_Parameterless_Procedure --
2534       -----------------------------------------
2535
2536       function Find_Unique_Parameterless_Procedure
2537         (Name : Entity_Id;
2538          Arg  : Node_Id) return Entity_Id
2539       is
2540          Proc : Entity_Id := Empty;
2541
2542       begin
2543          --  The body of this procedure needs some comments ???
2544
2545          if not Is_Entity_Name (Name) then
2546             Error_Pragma_Arg
2547               ("argument of pragma% must be entity name", Arg);
2548
2549          elsif not Is_Overloaded (Name) then
2550             Proc := Entity (Name);
2551
2552             if Ekind (Proc) /= E_Procedure
2553               or else Present (First_Formal (Proc))
2554             then
2555                Error_Pragma_Arg
2556                  ("argument of pragma% must be parameterless procedure", Arg);
2557             end if;
2558
2559          else
2560             declare
2561                Found : Boolean := False;
2562                It    : Interp;
2563                Index : Interp_Index;
2564
2565             begin
2566                Get_First_Interp (Name, Index, It);
2567                while Present (It.Nam) loop
2568                   Proc := It.Nam;
2569
2570                   if Ekind (Proc) = E_Procedure
2571                     and then No (First_Formal (Proc))
2572                   then
2573                      if not Found then
2574                         Found := True;
2575                         Set_Entity (Name, Proc);
2576                         Set_Is_Overloaded (Name, False);
2577                      else
2578                         Error_Pragma_Arg
2579                           ("ambiguous handler name for pragma% ", Arg);
2580                      end if;
2581                   end if;
2582
2583                   Get_Next_Interp (Index, It);
2584                end loop;
2585
2586                if not Found then
2587                   Error_Pragma_Arg
2588                     ("argument of pragma% must be parameterless procedure",
2589                      Arg);
2590                else
2591                   Proc := Entity (Name);
2592                end if;
2593             end;
2594          end if;
2595
2596          return Proc;
2597       end Find_Unique_Parameterless_Procedure;
2598
2599       ---------------
2600       -- Fix_Error --
2601       ---------------
2602
2603       procedure Fix_Error (Msg : in out String) is
2604       begin
2605          if From_Aspect_Specification (N) then
2606             for J in Msg'First .. Msg'Last - 5 loop
2607                if Msg (J .. J + 5) = "pragma" then
2608                   Msg (J .. J + 5) := "aspect";
2609                end if;
2610             end loop;
2611
2612             if Error_Msg_Name_1 = Name_Precondition then
2613                Error_Msg_Name_1 := Name_Pre;
2614             elsif Error_Msg_Name_1 = Name_Postcondition then
2615                Error_Msg_Name_1 := Name_Post;
2616             end if;
2617          end if;
2618       end Fix_Error;
2619
2620       -------------------------
2621       -- Gather_Associations --
2622       -------------------------
2623
2624       procedure Gather_Associations
2625         (Names : Name_List;
2626          Args  : out Args_List)
2627       is
2628          Arg : Node_Id;
2629
2630       begin
2631          --  Initialize all parameters to Empty
2632
2633          for J in Args'Range loop
2634             Args (J) := Empty;
2635          end loop;
2636
2637          --  That's all we have to do if there are no argument associations
2638
2639          if No (Pragma_Argument_Associations (N)) then
2640             return;
2641          end if;
2642
2643          --  Otherwise first deal with any positional parameters present
2644
2645          Arg := First (Pragma_Argument_Associations (N));
2646          for Index in Args'Range loop
2647             exit when No (Arg) or else Chars (Arg) /= No_Name;
2648             Args (Index) := Get_Pragma_Arg (Arg);
2649             Next (Arg);
2650          end loop;
2651
2652          --  Positional parameters all processed, if any left, then we
2653          --  have too many positional parameters.
2654
2655          if Present (Arg) and then Chars (Arg) = No_Name then
2656             Error_Pragma_Arg
2657               ("too many positional associations for pragma%", Arg);
2658          end if;
2659
2660          --  Process named parameters if any are present
2661
2662          while Present (Arg) loop
2663             if Chars (Arg) = No_Name then
2664                Error_Pragma_Arg
2665                  ("positional association cannot follow named association",
2666                   Arg);
2667
2668             else
2669                for Index in Names'Range loop
2670                   if Names (Index) = Chars (Arg) then
2671                      if Present (Args (Index)) then
2672                         Error_Pragma_Arg
2673                           ("duplicate argument association for pragma%", Arg);
2674                      else
2675                         Args (Index) := Get_Pragma_Arg (Arg);
2676                         exit;
2677                      end if;
2678                   end if;
2679
2680                   if Index = Names'Last then
2681                      Error_Msg_Name_1 := Pname;
2682                      Error_Msg_N ("pragma% does not allow & argument", Arg);
2683
2684                      --  Check for possible misspelling
2685
2686                      for Index1 in Names'Range loop
2687                         if Is_Bad_Spelling_Of
2688                              (Chars (Arg), Names (Index1))
2689                         then
2690                            Error_Msg_Name_1 := Names (Index1);
2691                            Error_Msg_N -- CODEFIX
2692                              ("\possible misspelling of%", Arg);
2693                            exit;
2694                         end if;
2695                      end loop;
2696
2697                      raise Pragma_Exit;
2698                   end if;
2699                end loop;
2700             end if;
2701
2702             Next (Arg);
2703          end loop;
2704       end Gather_Associations;
2705
2706       -----------------
2707       -- GNAT_Pragma --
2708       -----------------
2709
2710       procedure GNAT_Pragma is
2711       begin
2712          --  We need to check the No_Implementation_Pragmas restriction for
2713          --  the case of a pragma from source. Note that the case of aspects
2714          --  generating corresponding pragmas marks these pragmas as not being
2715          --  from source, so this test also catches that case.
2716
2717          if Comes_From_Source (N) then
2718             Check_Restriction (No_Implementation_Pragmas, N);
2719          end if;
2720       end GNAT_Pragma;
2721
2722       --------------------------
2723       -- Is_Before_First_Decl --
2724       --------------------------
2725
2726       function Is_Before_First_Decl
2727         (Pragma_Node : Node_Id;
2728          Decls       : List_Id) return Boolean
2729       is
2730          Item : Node_Id := First (Decls);
2731
2732       begin
2733          --  Only other pragmas can come before this pragma
2734
2735          loop
2736             if No (Item) or else Nkind (Item) /= N_Pragma then
2737                return False;
2738
2739             elsif Item = Pragma_Node then
2740                return True;
2741             end if;
2742
2743             Next (Item);
2744          end loop;
2745       end Is_Before_First_Decl;
2746
2747       -----------------------------
2748       -- Is_Configuration_Pragma --
2749       -----------------------------
2750
2751       --  A configuration pragma must appear in the context clause of a
2752       --  compilation unit, and only other pragmas may precede it. Note that
2753       --  the test below also permits use in a configuration pragma file.
2754
2755       function Is_Configuration_Pragma return Boolean is
2756          Lis : constant List_Id := List_Containing (N);
2757          Par : constant Node_Id := Parent (N);
2758          Prg : Node_Id;
2759
2760       begin
2761          --  If no parent, then we are in the configuration pragma file,
2762          --  so the placement is definitely appropriate.
2763
2764          if No (Par) then
2765             return True;
2766
2767          --  Otherwise we must be in the context clause of a compilation unit
2768          --  and the only thing allowed before us in the context list is more
2769          --  configuration pragmas.
2770
2771          elsif Nkind (Par) = N_Compilation_Unit
2772            and then Context_Items (Par) = Lis
2773          then
2774             Prg := First (Lis);
2775
2776             loop
2777                if Prg = N then
2778                   return True;
2779                elsif Nkind (Prg) /= N_Pragma then
2780                   return False;
2781                end if;
2782
2783                Next (Prg);
2784             end loop;
2785
2786          else
2787             return False;
2788          end if;
2789       end Is_Configuration_Pragma;
2790
2791       --------------------------
2792       -- Is_In_Context_Clause --
2793       --------------------------
2794
2795       function Is_In_Context_Clause return Boolean is
2796          Plist       : List_Id;
2797          Parent_Node : Node_Id;
2798
2799       begin
2800          if not Is_List_Member (N) then
2801             return False;
2802
2803          else
2804             Plist := List_Containing (N);
2805             Parent_Node := Parent (Plist);
2806
2807             if Parent_Node = Empty
2808               or else Nkind (Parent_Node) /= N_Compilation_Unit
2809               or else Context_Items (Parent_Node) /= Plist
2810             then
2811                return False;
2812             end if;
2813          end if;
2814
2815          return True;
2816       end Is_In_Context_Clause;
2817
2818       ---------------------------------
2819       -- Is_Static_String_Expression --
2820       ---------------------------------
2821
2822       function Is_Static_String_Expression (Arg : Node_Id) return Boolean is
2823          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
2824
2825       begin
2826          Analyze_And_Resolve (Argx);
2827          return Is_OK_Static_Expression (Argx)
2828            and then Nkind (Argx) = N_String_Literal;
2829       end Is_Static_String_Expression;
2830
2831       ----------------------
2832       -- Pragma_Misplaced --
2833       ----------------------
2834
2835       procedure Pragma_Misplaced is
2836       begin
2837          Error_Pragma ("incorrect placement of pragma%");
2838       end Pragma_Misplaced;
2839
2840       ------------------------------------
2841       -- Process Atomic_Shared_Volatile --
2842       ------------------------------------
2843
2844       procedure Process_Atomic_Shared_Volatile is
2845          E_Id : Node_Id;
2846          E    : Entity_Id;
2847          D    : Node_Id;
2848          K    : Node_Kind;
2849          Utyp : Entity_Id;
2850
2851          procedure Set_Atomic (E : Entity_Id);
2852          --  Set given type as atomic, and if no explicit alignment was given,
2853          --  set alignment to unknown, since back end knows what the alignment
2854          --  requirements are for atomic arrays. Note: this step is necessary
2855          --  for derived types.
2856
2857          ----------------
2858          -- Set_Atomic --
2859          ----------------
2860
2861          procedure Set_Atomic (E : Entity_Id) is
2862          begin
2863             Set_Is_Atomic (E);
2864
2865             if not Has_Alignment_Clause (E) then
2866                Set_Alignment (E, Uint_0);
2867             end if;
2868          end Set_Atomic;
2869
2870       --  Start of processing for Process_Atomic_Shared_Volatile
2871
2872       begin
2873          Check_Ada_83_Warning;
2874          Check_No_Identifiers;
2875          Check_Arg_Count (1);
2876          Check_Arg_Is_Local_Name (Arg1);
2877          E_Id := Get_Pragma_Arg (Arg1);
2878
2879          if Etype (E_Id) = Any_Type then
2880             return;
2881          end if;
2882
2883          E := Entity (E_Id);
2884          D := Declaration_Node (E);
2885          K := Nkind (D);
2886
2887          --  Check duplicate before we chain ourselves!
2888
2889          Check_Duplicate_Pragma (E);
2890
2891          --  Now check appropriateness of the entity
2892
2893          if Is_Type (E) then
2894             if Rep_Item_Too_Early (E, N)
2895                  or else
2896                Rep_Item_Too_Late (E, N)
2897             then
2898                return;
2899             else
2900                Check_First_Subtype (Arg1);
2901             end if;
2902
2903             if Prag_Id /= Pragma_Volatile then
2904                Set_Atomic (E);
2905                Set_Atomic (Underlying_Type (E));
2906                Set_Atomic (Base_Type (E));
2907             end if;
2908
2909             --  Attribute belongs on the base type. If the view of the type is
2910             --  currently private, it also belongs on the underlying type.
2911
2912             Set_Is_Volatile (Base_Type (E));
2913             Set_Is_Volatile (Underlying_Type (E));
2914
2915             Set_Treat_As_Volatile (E);
2916             Set_Treat_As_Volatile (Underlying_Type (E));
2917
2918          elsif K = N_Object_Declaration
2919            or else (K = N_Component_Declaration
2920                      and then Original_Record_Component (E) = E)
2921          then
2922             if Rep_Item_Too_Late (E, N) then
2923                return;
2924             end if;
2925
2926             if Prag_Id /= Pragma_Volatile then
2927                Set_Is_Atomic (E);
2928
2929                --  If the object declaration has an explicit initialization, a
2930                --  temporary may have to be created to hold the expression, to
2931                --  ensure that access to the object remain atomic.
2932
2933                if Nkind (Parent (E)) = N_Object_Declaration
2934                  and then Present (Expression (Parent (E)))
2935                then
2936                   Set_Has_Delayed_Freeze (E);
2937                end if;
2938
2939                --  An interesting improvement here. If an object of type X is
2940                --  declared atomic, and the type X is not atomic, that's a
2941                --  pity, since it may not have appropriate alignment etc. We
2942                --  can rescue this in the special case where the object and
2943                --  type are in the same unit by just setting the type as
2944                --  atomic, so that the back end will process it as atomic.
2945
2946                Utyp := Underlying_Type (Etype (E));
2947
2948                if Present (Utyp)
2949                  and then Sloc (E) > No_Location
2950                  and then Sloc (Utyp) > No_Location
2951                  and then
2952                    Get_Source_File_Index (Sloc (E)) =
2953                    Get_Source_File_Index (Sloc (Underlying_Type (Etype (E))))
2954                then
2955                   Set_Is_Atomic (Underlying_Type (Etype (E)));
2956                end if;
2957             end if;
2958
2959             Set_Is_Volatile (E);
2960             Set_Treat_As_Volatile (E);
2961
2962          else
2963             Error_Pragma_Arg
2964               ("inappropriate entity for pragma%", Arg1);
2965          end if;
2966       end Process_Atomic_Shared_Volatile;
2967
2968       -------------------------------------------
2969       -- Process_Compile_Time_Warning_Or_Error --
2970       -------------------------------------------
2971
2972       procedure Process_Compile_Time_Warning_Or_Error is
2973          Arg1x : constant Node_Id := Get_Pragma_Arg (Arg1);
2974
2975       begin
2976          Check_Arg_Count (2);
2977          Check_No_Identifiers;
2978          Check_Arg_Is_Static_Expression (Arg2, Standard_String);
2979          Analyze_And_Resolve (Arg1x, Standard_Boolean);
2980
2981          if Compile_Time_Known_Value (Arg1x) then
2982             if Is_True (Expr_Value (Get_Pragma_Arg (Arg1))) then
2983                declare
2984                   Str   : constant String_Id :=
2985                             Strval (Get_Pragma_Arg (Arg2));
2986                   Len   : constant Int := String_Length (Str);
2987                   Cont  : Boolean;
2988                   Ptr   : Nat;
2989                   CC    : Char_Code;
2990                   C     : Character;
2991                   Cent  : constant Entity_Id :=
2992                             Cunit_Entity (Current_Sem_Unit);
2993
2994                   Force : constant Boolean :=
2995                             Prag_Id = Pragma_Compile_Time_Warning
2996                               and then
2997                                 Is_Spec_Name (Unit_Name (Current_Sem_Unit))
2998                               and then (Ekind (Cent) /= E_Package
2999                                           or else not In_Private_Part (Cent));
3000                   --  Set True if this is the warning case, and we are in the
3001                   --  visible part of a package spec, or in a subprogram spec,
3002                   --  in which case we want to force the client to see the
3003                   --  warning, even though it is not in the main unit.
3004
3005                begin
3006                   --  Loop through segments of message separated by line feeds.
3007                   --  We output these segments as separate messages with
3008                   --  continuation marks for all but the first.
3009
3010                   Cont := False;
3011                   Ptr := 1;
3012                   loop
3013                      Error_Msg_Strlen := 0;
3014
3015                      --  Loop to copy characters from argument to error message
3016                      --  string buffer.
3017
3018                      loop
3019                         exit when Ptr > Len;
3020                         CC := Get_String_Char (Str, Ptr);
3021                         Ptr := Ptr + 1;
3022
3023                         --  Ignore wide chars ??? else store character
3024
3025                         if In_Character_Range (CC) then
3026                            C := Get_Character (CC);
3027                            exit when C = ASCII.LF;
3028                            Error_Msg_Strlen := Error_Msg_Strlen + 1;
3029                            Error_Msg_String (Error_Msg_Strlen) := C;
3030                         end if;
3031                      end loop;
3032
3033                      --  Here with one line ready to go
3034
3035                      Error_Msg_Warn := Prag_Id = Pragma_Compile_Time_Warning;
3036
3037                      --  If this is a warning in a spec, then we want clients
3038                      --  to see the warning, so mark the message with the
3039                      --  special sequence !! to force the warning. In the case
3040                      --  of a package spec, we do not force this if we are in
3041                      --  the private part of the spec.
3042
3043                      if Force then
3044                         if Cont = False then
3045                            Error_Msg_N ("<~!!", Arg1);
3046                            Cont := True;
3047                         else
3048                            Error_Msg_N ("\<~!!", Arg1);
3049                         end if;
3050
3051                      --  Error, rather than warning, or in a body, so we do not
3052                      --  need to force visibility for client (error will be
3053                      --  output in any case, and this is the situation in which
3054                      --  we do not want a client to get a warning, since the
3055                      --  warning is in the body or the spec private part).
3056
3057                      else
3058                         if Cont = False then
3059                            Error_Msg_N ("<~", Arg1);
3060                            Cont := True;
3061                         else
3062                            Error_Msg_N ("\<~", Arg1);
3063                         end if;
3064                      end if;
3065
3066                      exit when Ptr > Len;
3067                   end loop;
3068                end;
3069             end if;
3070          end if;
3071       end Process_Compile_Time_Warning_Or_Error;
3072
3073       ------------------------
3074       -- Process_Convention --
3075       ------------------------
3076
3077       procedure Process_Convention
3078         (C   : out Convention_Id;
3079          Ent : out Entity_Id)
3080       is
3081          Id        : Node_Id;
3082          E         : Entity_Id;
3083          E1        : Entity_Id;
3084          Cname     : Name_Id;
3085          Comp_Unit : Unit_Number_Type;
3086
3087          procedure Diagnose_Multiple_Pragmas (S : Entity_Id);
3088          --  Called if we have more than one Export/Import/Convention pragma.
3089          --  This is generally illegal, but we have a special case of allowing
3090          --  Import and Interface to coexist if they specify the convention in
3091          --  a consistent manner. We are allowed to do this, since Interface is
3092          --  an implementation defined pragma, and we choose to do it since we
3093          --  know Rational allows this combination. S is the entity id of the
3094          --  subprogram in question. This procedure also sets the special flag
3095          --  Import_Interface_Present in both pragmas in the case where we do
3096          --  have matching Import and Interface pragmas.
3097
3098          procedure Set_Convention_From_Pragma (E : Entity_Id);
3099          --  Set convention in entity E, and also flag that the entity has a
3100          --  convention pragma. If entity is for a private or incomplete type,
3101          --  also set convention and flag on underlying type. This procedure
3102          --  also deals with the special case of C_Pass_By_Copy convention.
3103
3104          -------------------------------
3105          -- Diagnose_Multiple_Pragmas --
3106          -------------------------------
3107
3108          procedure Diagnose_Multiple_Pragmas (S : Entity_Id) is
3109             Pdec : constant Node_Id := Declaration_Node (S);
3110             Decl : Node_Id;
3111             Err  : Boolean;
3112
3113             function Same_Convention (Decl : Node_Id) return Boolean;
3114             --  Decl is a pragma node. This function returns True if this
3115             --  pragma has a first argument that is an identifier with a
3116             --  Chars field corresponding to the Convention_Id C.
3117
3118             function Same_Name (Decl : Node_Id) return Boolean;
3119             --  Decl is a pragma node. This function returns True if this
3120             --  pragma has a second argument that is an identifier with a
3121             --  Chars field that matches the Chars of the current subprogram.
3122
3123             ---------------------
3124             -- Same_Convention --
3125             ---------------------
3126
3127             function Same_Convention (Decl : Node_Id) return Boolean is
3128                Arg1 : constant Node_Id :=
3129                         First (Pragma_Argument_Associations (Decl));
3130
3131             begin
3132                if Present (Arg1) then
3133                   declare
3134                      Arg : constant Node_Id := Get_Pragma_Arg (Arg1);
3135                   begin
3136                      if Nkind (Arg) = N_Identifier
3137                        and then Is_Convention_Name (Chars (Arg))
3138                        and then Get_Convention_Id (Chars (Arg)) = C
3139                      then
3140                         return True;
3141                      end if;
3142                   end;
3143                end if;
3144
3145                return False;
3146             end Same_Convention;
3147
3148             ---------------
3149             -- Same_Name --
3150             ---------------
3151
3152             function Same_Name (Decl : Node_Id) return Boolean is
3153                Arg1 : constant Node_Id :=
3154                         First (Pragma_Argument_Associations (Decl));
3155                Arg2 : Node_Id;
3156
3157             begin
3158                if No (Arg1) then
3159                   return False;
3160                end if;
3161
3162                Arg2 := Next (Arg1);
3163
3164                if No (Arg2) then
3165                   return False;
3166                end if;
3167
3168                declare
3169                   Arg : constant Node_Id := Get_Pragma_Arg (Arg2);
3170                begin
3171                   if Nkind (Arg) = N_Identifier
3172                     and then Chars (Arg) = Chars (S)
3173                   then
3174                      return True;
3175                   end if;
3176                end;
3177
3178                return False;
3179             end Same_Name;
3180
3181          --  Start of processing for Diagnose_Multiple_Pragmas
3182
3183          begin
3184             Err := True;
3185
3186             --  Definitely give message if we have Convention/Export here
3187
3188             if Prag_Id = Pragma_Convention or else Prag_Id = Pragma_Export then
3189                null;
3190
3191                --  If we have an Import or Export, scan back from pragma to
3192                --  find any previous pragma applying to the same procedure.
3193                --  The scan will be terminated by the start of the list, or
3194                --  hitting the subprogram declaration. This won't allow one
3195                --  pragma to appear in the public part and one in the private
3196                --  part, but that seems very unlikely in practice.
3197
3198             else
3199                Decl := Prev (N);
3200                while Present (Decl) and then Decl /= Pdec loop
3201
3202                   --  Look for pragma with same name as us
3203
3204                   if Nkind (Decl) = N_Pragma
3205                     and then Same_Name (Decl)
3206                   then
3207                      --  Give error if same as our pragma or Export/Convention
3208
3209                      if Pragma_Name (Decl) = Name_Export
3210                           or else
3211                         Pragma_Name (Decl) = Name_Convention
3212                           or else
3213                         Pragma_Name (Decl) = Pragma_Name (N)
3214                      then
3215                         exit;
3216
3217                      --  Case of Import/Interface or the other way round
3218
3219                      elsif Pragma_Name (Decl) = Name_Interface
3220                              or else
3221                            Pragma_Name (Decl) = Name_Import
3222                      then
3223                         --  Here we know that we have Import and Interface. It
3224                         --  doesn't matter which way round they are. See if
3225                         --  they specify the same convention. If so, all OK,
3226                         --  and set special flags to stop other messages
3227
3228                         if Same_Convention (Decl) then
3229                            Set_Import_Interface_Present (N);
3230                            Set_Import_Interface_Present (Decl);
3231                            Err := False;
3232
3233                         --  If different conventions, special message
3234
3235                         else
3236                            Error_Msg_Sloc := Sloc (Decl);
3237                            Error_Pragma_Arg
3238                              ("convention differs from that given#", Arg1);
3239                            return;
3240                         end if;
3241                      end if;
3242                   end if;
3243
3244                   Next (Decl);
3245                end loop;
3246             end if;
3247
3248             --  Give message if needed if we fall through those tests
3249
3250             if Err then
3251                Error_Pragma_Arg
3252                  ("at most one Convention/Export/Import pragma is allowed",
3253                   Arg2);
3254             end if;
3255          end Diagnose_Multiple_Pragmas;
3256
3257          --------------------------------
3258          -- Set_Convention_From_Pragma --
3259          --------------------------------
3260
3261          procedure Set_Convention_From_Pragma (E : Entity_Id) is
3262          begin
3263             --  Ada 2005 (AI-430): Check invalid attempt to change convention
3264             --  for an overridden dispatching operation. Technically this is
3265             --  an amendment and should only be done in Ada 2005 mode. However,
3266             --  this is clearly a mistake, since the problem that is addressed
3267             --  by this AI is that there is a clear gap in the RM!
3268
3269             if Is_Dispatching_Operation (E)
3270               and then Present (Overridden_Operation (E))
3271               and then C /= Convention (Overridden_Operation (E))
3272             then
3273                Error_Pragma_Arg
3274                  ("cannot change convention for " &
3275                   "overridden dispatching operation",
3276                   Arg1);
3277             end if;
3278
3279             --  Set the convention
3280
3281             Set_Convention (E, C);
3282             Set_Has_Convention_Pragma (E);
3283
3284             if Is_Incomplete_Or_Private_Type (E)
3285               and then Present (Underlying_Type (E))
3286             then
3287                Set_Convention            (Underlying_Type (E), C);
3288                Set_Has_Convention_Pragma (Underlying_Type (E), True);
3289             end if;
3290
3291             --  A class-wide type should inherit the convention of the specific
3292             --  root type (although this isn't specified clearly by the RM).
3293
3294             if Is_Type (E) and then Present (Class_Wide_Type (E)) then
3295                Set_Convention (Class_Wide_Type (E), C);
3296             end if;
3297
3298             --  If the entity is a record type, then check for special case of
3299             --  C_Pass_By_Copy, which is treated the same as C except that the
3300             --  special record flag is set. This convention is only permitted
3301             --  on record types (see AI95-00131).
3302
3303             if Cname = Name_C_Pass_By_Copy then
3304                if Is_Record_Type (E) then
3305                   Set_C_Pass_By_Copy (Base_Type (E));
3306                elsif Is_Incomplete_Or_Private_Type (E)
3307                  and then Is_Record_Type (Underlying_Type (E))
3308                then
3309                   Set_C_Pass_By_Copy (Base_Type (Underlying_Type (E)));
3310                else
3311                   Error_Pragma_Arg
3312                     ("C_Pass_By_Copy convention allowed only for record type",
3313                      Arg2);
3314                end if;
3315             end if;
3316
3317             --  If the entity is a derived boolean type, check for the special
3318             --  case of convention C, C++, or Fortran, where we consider any
3319             --  nonzero value to represent true.
3320
3321             if Is_Discrete_Type (E)
3322               and then Root_Type (Etype (E)) = Standard_Boolean
3323               and then
3324                 (C = Convention_C
3325                    or else
3326                  C = Convention_CPP
3327                    or else
3328                  C = Convention_Fortran)
3329             then
3330                Set_Nonzero_Is_True (Base_Type (E));
3331             end if;
3332          end Set_Convention_From_Pragma;
3333
3334       --  Start of processing for Process_Convention
3335
3336       begin
3337          Check_At_Least_N_Arguments (2);
3338          Check_Optional_Identifier (Arg1, Name_Convention);
3339          Check_Arg_Is_Identifier (Arg1);
3340          Cname := Chars (Get_Pragma_Arg (Arg1));
3341
3342          --  C_Pass_By_Copy is treated as a synonym for convention C (this is
3343          --  tested again below to set the critical flag).
3344
3345          if Cname = Name_C_Pass_By_Copy then
3346             C := Convention_C;
3347
3348          --  Otherwise we must have something in the standard convention list
3349
3350          elsif Is_Convention_Name (Cname) then
3351             C := Get_Convention_Id (Chars (Get_Pragma_Arg (Arg1)));
3352
3353          --  In DEC VMS, it seems that there is an undocumented feature that
3354          --  any unrecognized convention is treated as the default, which for
3355          --  us is convention C. It does not seem so terrible to do this
3356          --  unconditionally, silently in the VMS case, and with a warning
3357          --  in the non-VMS case.
3358
3359          else
3360             if Warn_On_Export_Import and not OpenVMS_On_Target then
3361                Error_Msg_N
3362                  ("?unrecognized convention name, C assumed",
3363                   Get_Pragma_Arg (Arg1));
3364             end if;
3365
3366             C := Convention_C;
3367          end if;
3368
3369          Check_Optional_Identifier (Arg2, Name_Entity);
3370          Check_Arg_Is_Local_Name (Arg2);
3371
3372          Id := Get_Pragma_Arg (Arg2);
3373          Analyze (Id);
3374
3375          if not Is_Entity_Name (Id) then
3376             Error_Pragma_Arg ("entity name required", Arg2);
3377          end if;
3378
3379          E := Entity (Id);
3380
3381          --  Set entity to return
3382
3383          Ent := E;
3384
3385          --  Ada_Pass_By_Copy special checking
3386
3387          if C = Convention_Ada_Pass_By_Copy then
3388             if not Is_First_Subtype (E) then
3389                Error_Pragma_Arg
3390                  ("convention `Ada_Pass_By_Copy` only "
3391                   & "allowed for types", Arg2);
3392             end if;
3393
3394             if Is_By_Reference_Type (E) then
3395                Error_Pragma_Arg
3396                  ("convention `Ada_Pass_By_Copy` not allowed for "
3397                   & "by-reference type", Arg1);
3398             end if;
3399          end if;
3400
3401          --  Ada_Pass_By_Reference special checking
3402
3403          if C = Convention_Ada_Pass_By_Reference then
3404             if not Is_First_Subtype (E) then
3405                Error_Pragma_Arg
3406                  ("convention `Ada_Pass_By_Reference` only "
3407                   & "allowed for types", Arg2);
3408             end if;
3409
3410             if Is_By_Copy_Type (E) then
3411                Error_Pragma_Arg
3412                  ("convention `Ada_Pass_By_Reference` not allowed for "
3413                   & "by-copy type", Arg1);
3414             end if;
3415          end if;
3416
3417          --  Go to renamed subprogram if present, since convention applies to
3418          --  the actual renamed entity, not to the renaming entity. If the
3419          --  subprogram is inherited, go to parent subprogram.
3420
3421          if Is_Subprogram (E)
3422            and then Present (Alias (E))
3423          then
3424             if Nkind (Parent (Declaration_Node (E))) =
3425                                        N_Subprogram_Renaming_Declaration
3426             then
3427                if Scope (E) /= Scope (Alias (E)) then
3428                   Error_Pragma_Ref
3429                     ("cannot apply pragma% to non-local entity&#", E);
3430                end if;
3431
3432                E := Alias (E);
3433
3434             elsif Nkind_In (Parent (E), N_Full_Type_Declaration,
3435                                         N_Private_Extension_Declaration)
3436               and then Scope (E) = Scope (Alias (E))
3437             then
3438                E := Alias (E);
3439
3440                --  Return the parent subprogram the entity was inherited from
3441
3442                Ent := E;
3443             end if;
3444          end if;
3445
3446          --  Check that we are not applying this to a specless body
3447
3448          if Is_Subprogram (E)
3449            and then Nkind (Parent (Declaration_Node (E))) = N_Subprogram_Body
3450          then
3451             Error_Pragma
3452               ("pragma% requires separate spec and must come before body");
3453          end if;
3454
3455          --  Check that we are not applying this to a named constant
3456
3457          if Ekind_In (E, E_Named_Integer, E_Named_Real) then
3458             Error_Msg_Name_1 := Pname;
3459             Error_Msg_N
3460               ("cannot apply pragma% to named constant!",
3461                Get_Pragma_Arg (Arg2));
3462             Error_Pragma_Arg
3463               ("\supply appropriate type for&!", Arg2);
3464          end if;
3465
3466          if Ekind (E) = E_Enumeration_Literal then
3467             Error_Pragma ("enumeration literal not allowed for pragma%");
3468          end if;
3469
3470          --  Check for rep item appearing too early or too late
3471
3472          if Etype (E) = Any_Type
3473            or else Rep_Item_Too_Early (E, N)
3474          then
3475             raise Pragma_Exit;
3476
3477          elsif Present (Underlying_Type (E)) then
3478             E := Underlying_Type (E);
3479          end if;
3480
3481          if Rep_Item_Too_Late (E, N) then
3482             raise Pragma_Exit;
3483          end if;
3484
3485          if Has_Convention_Pragma (E) then
3486             Diagnose_Multiple_Pragmas (E);
3487
3488          elsif Convention (E) = Convention_Protected
3489            or else Ekind (Scope (E)) = E_Protected_Type
3490          then
3491             Error_Pragma_Arg
3492               ("a protected operation cannot be given a different convention",
3493                 Arg2);
3494          end if;
3495
3496          --  For Intrinsic, a subprogram is required
3497
3498          if C = Convention_Intrinsic
3499            and then not Is_Subprogram (E)
3500            and then not Is_Generic_Subprogram (E)
3501          then
3502             Error_Pragma_Arg
3503               ("second argument of pragma% must be a subprogram", Arg2);
3504          end if;
3505
3506          --  Stdcall case
3507
3508          if C = Convention_Stdcall then
3509
3510             --  A dispatching call is not allowed. A dispatching subprogram
3511             --  cannot be used to interface to the Win32 API, so in fact this
3512             --  check does not impose any effective restriction.
3513
3514             if Is_Dispatching_Operation (E) then
3515
3516                Error_Pragma
3517                  ("dispatching subprograms cannot use Stdcall convention");
3518
3519             --  Subprogram is allowed, but not a generic subprogram, and not a
3520             --  dispatching operation.
3521
3522             elsif not Is_Subprogram (E)
3523               and then not Is_Generic_Subprogram (E)
3524
3525               --  A variable is OK
3526
3527               and then Ekind (E) /= E_Variable
3528
3529               --  An access to subprogram is also allowed
3530
3531               and then not
3532                 (Is_Access_Type (E)
3533                   and then Ekind (Designated_Type (E)) = E_Subprogram_Type)
3534             then
3535                Error_Pragma_Arg
3536                  ("second argument of pragma% must be subprogram (type)",
3537                   Arg2);
3538             end if;
3539          end if;
3540
3541          if not Is_Subprogram (E)
3542            and then not Is_Generic_Subprogram (E)
3543          then
3544             Set_Convention_From_Pragma (E);
3545
3546             if Is_Type (E) then
3547                Check_First_Subtype (Arg2);
3548                Set_Convention_From_Pragma (Base_Type (E));
3549
3550                --  For subprograms, we must set the convention on the
3551                --  internally generated directly designated type as well.
3552
3553                if Ekind (E) = E_Access_Subprogram_Type then
3554                   Set_Convention_From_Pragma (Directly_Designated_Type (E));
3555                end if;
3556             end if;
3557
3558          --  For the subprogram case, set proper convention for all homonyms
3559          --  in same scope and the same declarative part, i.e. the same
3560          --  compilation unit.
3561
3562          else
3563             Comp_Unit := Get_Source_Unit (E);
3564             Set_Convention_From_Pragma (E);
3565
3566             --  Treat a pragma Import as an implicit body, for GPS use
3567
3568             if Prag_Id = Pragma_Import then
3569                Generate_Reference (E, Id, 'b');
3570             end if;
3571
3572             --  Loop through the homonyms of the pragma argument's entity
3573
3574             E1 := Ent;
3575             loop
3576                E1 := Homonym (E1);
3577                exit when No (E1) or else Scope (E1) /= Current_Scope;
3578
3579                --  Do not set the pragma on inherited operations or on formal
3580                --  subprograms.
3581
3582                if Comes_From_Source (E1)
3583                  and then Comp_Unit = Get_Source_Unit (E1)
3584                  and then not Is_Formal_Subprogram (E1)
3585                  and then Nkind (Original_Node (Parent (E1))) /=
3586                                                     N_Full_Type_Declaration
3587                then
3588                   if Present (Alias (E1))
3589                     and then Scope (E1) /= Scope (Alias (E1))
3590                   then
3591                      Error_Pragma_Ref
3592                        ("cannot apply pragma% to non-local entity& declared#",
3593                         E1);
3594                   end if;
3595
3596                   Set_Convention_From_Pragma (E1);
3597
3598                   if Prag_Id = Pragma_Import then
3599                      Generate_Reference (E1, Id, 'b');
3600                   end if;
3601                end if;
3602
3603                --  For aspect case, do NOT apply to homonyms
3604
3605                exit when From_Aspect_Specification (N);
3606             end loop;
3607          end if;
3608       end Process_Convention;
3609
3610       ----------------------------------------
3611       -- Process_Disable_Enable_Atomic_Sync --
3612       ----------------------------------------
3613
3614       procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id) is
3615       begin
3616          GNAT_Pragma;
3617          Check_No_Identifiers;
3618          Check_At_Most_N_Arguments (1);
3619
3620          --  Modeled internally as
3621          --    pragma Unsuppress (Atomic_Synchronization [,Entity])
3622
3623          Rewrite (N,
3624            Make_Pragma (Loc,
3625              Pragma_Identifier            =>
3626                Make_Identifier (Loc, Nam),
3627              Pragma_Argument_Associations => New_List (
3628                Make_Pragma_Argument_Association (Loc,
3629                  Expression =>
3630                    Make_Identifier (Loc, Name_Atomic_Synchronization)))));
3631
3632          if Present (Arg1) then
3633             Append_To (Pragma_Argument_Associations (N), New_Copy (Arg1));
3634          end if;
3635
3636          Analyze (N);
3637       end Process_Disable_Enable_Atomic_Sync;
3638
3639       -----------------------------------------------------
3640       -- Process_Extended_Import_Export_Exception_Pragma --
3641       -----------------------------------------------------
3642
3643       procedure Process_Extended_Import_Export_Exception_Pragma
3644         (Arg_Internal : Node_Id;
3645          Arg_External : Node_Id;
3646          Arg_Form     : Node_Id;
3647          Arg_Code     : Node_Id)
3648       is
3649          Def_Id   : Entity_Id;
3650          Code_Val : Uint;
3651
3652       begin
3653          if not OpenVMS_On_Target then
3654             Error_Pragma
3655               ("?pragma% ignored (applies only to Open'V'M'S)");
3656          end if;
3657
3658          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3659          Def_Id := Entity (Arg_Internal);
3660
3661          if Ekind (Def_Id) /= E_Exception then
3662             Error_Pragma_Arg
3663               ("pragma% must refer to declared exception", Arg_Internal);
3664          end if;
3665
3666          Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
3667
3668          if Present (Arg_Form) then
3669             Check_Arg_Is_One_Of (Arg_Form, Name_Ada, Name_VMS);
3670          end if;
3671
3672          if Present (Arg_Form)
3673            and then Chars (Arg_Form) = Name_Ada
3674          then
3675             null;
3676          else
3677             Set_Is_VMS_Exception (Def_Id);
3678             Set_Exception_Code (Def_Id, No_Uint);
3679          end if;
3680
3681          if Present (Arg_Code) then
3682             if not Is_VMS_Exception (Def_Id) then
3683                Error_Pragma_Arg
3684                  ("Code option for pragma% not allowed for Ada case",
3685                   Arg_Code);
3686             end if;
3687
3688             Check_Arg_Is_Static_Expression (Arg_Code, Any_Integer);
3689             Code_Val := Expr_Value (Arg_Code);
3690
3691             if not UI_Is_In_Int_Range (Code_Val) then
3692                Error_Pragma_Arg
3693                  ("Code option for pragma% must be in 32-bit range",
3694                   Arg_Code);
3695
3696             else
3697                Set_Exception_Code (Def_Id, Code_Val);
3698             end if;
3699          end if;
3700       end Process_Extended_Import_Export_Exception_Pragma;
3701
3702       -------------------------------------------------
3703       -- Process_Extended_Import_Export_Internal_Arg --
3704       -------------------------------------------------
3705
3706       procedure Process_Extended_Import_Export_Internal_Arg
3707         (Arg_Internal : Node_Id := Empty)
3708       is
3709       begin
3710          if No (Arg_Internal) then
3711             Error_Pragma ("Internal parameter required for pragma%");
3712          end if;
3713
3714          if Nkind (Arg_Internal) = N_Identifier then
3715             null;
3716
3717          elsif Nkind (Arg_Internal) = N_Operator_Symbol
3718            and then (Prag_Id = Pragma_Import_Function
3719                        or else
3720                      Prag_Id = Pragma_Export_Function)
3721          then
3722             null;
3723
3724          else
3725             Error_Pragma_Arg
3726               ("wrong form for Internal parameter for pragma%", Arg_Internal);
3727          end if;
3728
3729          Check_Arg_Is_Local_Name (Arg_Internal);
3730       end Process_Extended_Import_Export_Internal_Arg;
3731
3732       --------------------------------------------------
3733       -- Process_Extended_Import_Export_Object_Pragma --
3734       --------------------------------------------------
3735
3736       procedure Process_Extended_Import_Export_Object_Pragma
3737         (Arg_Internal : Node_Id;
3738          Arg_External : Node_Id;
3739          Arg_Size     : Node_Id)
3740       is
3741          Def_Id : Entity_Id;
3742
3743       begin
3744          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3745          Def_Id := Entity (Arg_Internal);
3746
3747          if not Ekind_In (Def_Id, E_Constant, E_Variable) then
3748             Error_Pragma_Arg
3749               ("pragma% must designate an object", Arg_Internal);
3750          end if;
3751
3752          if Has_Rep_Pragma (Def_Id, Name_Common_Object)
3753               or else
3754             Has_Rep_Pragma (Def_Id, Name_Psect_Object)
3755          then
3756             Error_Pragma_Arg
3757               ("previous Common/Psect_Object applies, pragma % not permitted",
3758                Arg_Internal);
3759          end if;
3760
3761          if Rep_Item_Too_Late (Def_Id, N) then
3762             raise Pragma_Exit;
3763          end if;
3764
3765          Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
3766
3767          if Present (Arg_Size) then
3768             Check_Arg_Is_External_Name (Arg_Size);
3769          end if;
3770
3771          --  Export_Object case
3772
3773          if Prag_Id = Pragma_Export_Object then
3774             if not Is_Library_Level_Entity (Def_Id) then
3775                Error_Pragma_Arg
3776                  ("argument for pragma% must be library level entity",
3777                   Arg_Internal);
3778             end if;
3779
3780             if Ekind (Current_Scope) = E_Generic_Package then
3781                Error_Pragma ("pragma& cannot appear in a generic unit");
3782             end if;
3783
3784             if not Size_Known_At_Compile_Time (Etype (Def_Id)) then
3785                Error_Pragma_Arg
3786                  ("exported object must have compile time known size",
3787                   Arg_Internal);
3788             end if;
3789
3790             if Warn_On_Export_Import and then Is_Exported (Def_Id) then
3791                Error_Msg_N ("?duplicate Export_Object pragma", N);
3792             else
3793                Set_Exported (Def_Id, Arg_Internal);
3794             end if;
3795
3796          --  Import_Object case
3797
3798          else
3799             if Is_Concurrent_Type (Etype (Def_Id)) then
3800                Error_Pragma_Arg
3801                  ("cannot use pragma% for task/protected object",
3802                   Arg_Internal);
3803             end if;
3804
3805             if Ekind (Def_Id) = E_Constant then
3806                Error_Pragma_Arg
3807                  ("cannot import a constant", Arg_Internal);
3808             end if;
3809
3810             if Warn_On_Export_Import
3811               and then Has_Discriminants (Etype (Def_Id))
3812             then
3813                Error_Msg_N
3814                  ("imported value must be initialized?", Arg_Internal);
3815             end if;
3816
3817             if Warn_On_Export_Import
3818               and then Is_Access_Type (Etype (Def_Id))
3819             then
3820                Error_Pragma_Arg
3821                  ("cannot import object of an access type?", Arg_Internal);
3822             end if;
3823
3824             if Warn_On_Export_Import
3825               and then Is_Imported (Def_Id)
3826             then
3827                Error_Msg_N
3828                  ("?duplicate Import_Object pragma", N);
3829
3830             --  Check for explicit initialization present. Note that an
3831             --  initialization generated by the code generator, e.g. for an
3832             --  access type, does not count here.
3833
3834             elsif Present (Expression (Parent (Def_Id)))
3835                and then
3836                  Comes_From_Source
3837                    (Original_Node (Expression (Parent (Def_Id))))
3838             then
3839                Error_Msg_Sloc := Sloc (Def_Id);
3840                Error_Pragma_Arg
3841                  ("imported entities cannot be initialized (RM B.1(24))",
3842                   "\no initialization allowed for & declared#", Arg1);
3843             else
3844                Set_Imported (Def_Id);
3845                Note_Possible_Modification (Arg_Internal, Sure => False);
3846             end if;
3847          end if;
3848       end Process_Extended_Import_Export_Object_Pragma;
3849
3850       ------------------------------------------------------
3851       -- Process_Extended_Import_Export_Subprogram_Pragma --
3852       ------------------------------------------------------
3853
3854       procedure Process_Extended_Import_Export_Subprogram_Pragma
3855         (Arg_Internal                 : Node_Id;
3856          Arg_External                 : Node_Id;
3857          Arg_Parameter_Types          : Node_Id;
3858          Arg_Result_Type              : Node_Id := Empty;
3859          Arg_Mechanism                : Node_Id;
3860          Arg_Result_Mechanism         : Node_Id := Empty;
3861          Arg_First_Optional_Parameter : Node_Id := Empty)
3862       is
3863          Ent       : Entity_Id;
3864          Def_Id    : Entity_Id;
3865          Hom_Id    : Entity_Id;
3866          Formal    : Entity_Id;
3867          Ambiguous : Boolean;
3868          Match     : Boolean;
3869          Dval      : Node_Id;
3870
3871          function Same_Base_Type
3872           (Ptype  : Node_Id;
3873            Formal : Entity_Id) return Boolean;
3874          --  Determines if Ptype references the type of Formal. Note that only
3875          --  the base types need to match according to the spec. Ptype here is
3876          --  the argument from the pragma, which is either a type name, or an
3877          --  access attribute.
3878
3879          --------------------
3880          -- Same_Base_Type --
3881          --------------------
3882
3883          function Same_Base_Type
3884            (Ptype  : Node_Id;
3885             Formal : Entity_Id) return Boolean
3886          is
3887             Ftyp : constant Entity_Id := Base_Type (Etype (Formal));
3888             Pref : Node_Id;
3889
3890          begin
3891             --  Case where pragma argument is typ'Access
3892
3893             if Nkind (Ptype) = N_Attribute_Reference
3894               and then Attribute_Name (Ptype) = Name_Access
3895             then
3896                Pref := Prefix (Ptype);
3897                Find_Type (Pref);
3898
3899                if not Is_Entity_Name (Pref)
3900                  or else Entity (Pref) = Any_Type
3901                then
3902                   raise Pragma_Exit;
3903                end if;
3904
3905                --  We have a match if the corresponding argument is of an
3906                --  anonymous access type, and its designated type matches the
3907                --  type of the prefix of the access attribute
3908
3909                return Ekind (Ftyp) = E_Anonymous_Access_Type
3910                  and then Base_Type (Entity (Pref)) =
3911                             Base_Type (Etype (Designated_Type (Ftyp)));
3912
3913             --  Case where pragma argument is a type name
3914
3915             else
3916                Find_Type (Ptype);
3917
3918                if not Is_Entity_Name (Ptype)
3919                  or else Entity (Ptype) = Any_Type
3920                then
3921                   raise Pragma_Exit;
3922                end if;
3923
3924                --  We have a match if the corresponding argument is of the type
3925                --  given in the pragma (comparing base types)
3926
3927                return Base_Type (Entity (Ptype)) = Ftyp;
3928             end if;
3929          end Same_Base_Type;
3930
3931       --  Start of processing for
3932       --  Process_Extended_Import_Export_Subprogram_Pragma
3933
3934       begin
3935          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3936          Ent := Empty;
3937          Ambiguous := False;
3938
3939          --  Loop through homonyms (overloadings) of the entity
3940
3941          Hom_Id := Entity (Arg_Internal);
3942          while Present (Hom_Id) loop
3943             Def_Id := Get_Base_Subprogram (Hom_Id);
3944
3945             --  We need a subprogram in the current scope
3946
3947             if not Is_Subprogram (Def_Id)
3948               or else Scope (Def_Id) /= Current_Scope
3949             then
3950                null;
3951
3952             else
3953                Match := True;
3954
3955                --  Pragma cannot apply to subprogram body
3956
3957                if Is_Subprogram (Def_Id)
3958                  and then Nkind (Parent (Declaration_Node (Def_Id))) =
3959                                                              N_Subprogram_Body
3960                then
3961                   Error_Pragma
3962                     ("pragma% requires separate spec"
3963                       & " and must come before body");
3964                end if;
3965
3966                --  Test result type if given, note that the result type
3967                --  parameter can only be present for the function cases.
3968
3969                if Present (Arg_Result_Type)
3970                  and then not Same_Base_Type (Arg_Result_Type, Def_Id)
3971                then
3972                   Match := False;
3973
3974                elsif Etype (Def_Id) /= Standard_Void_Type
3975                  and then
3976                    (Pname = Name_Export_Procedure
3977                       or else
3978                     Pname = Name_Import_Procedure)
3979                then
3980                   Match := False;
3981
3982                --  Test parameter types if given. Note that this parameter
3983                --  has not been analyzed (and must not be, since it is
3984                --  semantic nonsense), so we get it as the parser left it.
3985
3986                elsif Present (Arg_Parameter_Types) then
3987                   Check_Matching_Types : declare
3988                      Formal : Entity_Id;
3989                      Ptype  : Node_Id;
3990
3991                   begin
3992                      Formal := First_Formal (Def_Id);
3993
3994                      if Nkind (Arg_Parameter_Types) = N_Null then
3995                         if Present (Formal) then
3996                            Match := False;
3997                         end if;
3998
3999                      --  A list of one type, e.g. (List) is parsed as
4000                      --  a parenthesized expression.
4001
4002                      elsif Nkind (Arg_Parameter_Types) /= N_Aggregate
4003                        and then Paren_Count (Arg_Parameter_Types) = 1
4004                      then
4005                         if No (Formal)
4006                           or else Present (Next_Formal (Formal))
4007                         then
4008                            Match := False;
4009                         else
4010                            Match :=
4011                              Same_Base_Type (Arg_Parameter_Types, Formal);
4012                         end if;
4013
4014                      --  A list of more than one type is parsed as a aggregate
4015
4016                      elsif Nkind (Arg_Parameter_Types) = N_Aggregate
4017                        and then Paren_Count (Arg_Parameter_Types) = 0
4018                      then
4019                         Ptype := First (Expressions (Arg_Parameter_Types));
4020                         while Present (Ptype) or else Present (Formal) loop
4021                            if No (Ptype)
4022                              or else No (Formal)
4023                              or else not Same_Base_Type (Ptype, Formal)
4024                            then
4025                               Match := False;
4026                               exit;
4027                            else
4028                               Next_Formal (Formal);
4029                               Next (Ptype);
4030                            end if;
4031                         end loop;
4032
4033                      --  Anything else is of the wrong form
4034
4035                      else
4036                         Error_Pragma_Arg
4037                           ("wrong form for Parameter_Types parameter",
4038                            Arg_Parameter_Types);
4039                      end if;
4040                   end Check_Matching_Types;
4041                end if;
4042
4043                --  Match is now False if the entry we found did not match
4044                --  either a supplied Parameter_Types or Result_Types argument
4045
4046                if Match then
4047                   if No (Ent) then
4048                      Ent := Def_Id;
4049
4050                   --  Ambiguous case, the flag Ambiguous shows if we already
4051                   --  detected this and output the initial messages.
4052
4053                   else
4054                      if not Ambiguous then
4055                         Ambiguous := True;
4056                         Error_Msg_Name_1 := Pname;
4057                         Error_Msg_N
4058                           ("pragma% does not uniquely identify subprogram!",
4059                            N);
4060                         Error_Msg_Sloc := Sloc (Ent);
4061                         Error_Msg_N ("matching subprogram #!", N);
4062                         Ent := Empty;
4063                      end if;
4064
4065                      Error_Msg_Sloc := Sloc (Def_Id);
4066                      Error_Msg_N ("matching subprogram #!", N);
4067                   end if;
4068                end if;
4069             end if;
4070
4071             Hom_Id := Homonym (Hom_Id);
4072          end loop;
4073
4074          --  See if we found an entry
4075
4076          if No (Ent) then
4077             if not Ambiguous then
4078                if Is_Generic_Subprogram (Entity (Arg_Internal)) then
4079                   Error_Pragma
4080                     ("pragma% cannot be given for generic subprogram");
4081                else
4082                   Error_Pragma
4083                     ("pragma% does not identify local subprogram");
4084                end if;
4085             end if;
4086
4087             return;
4088          end if;
4089
4090          --  Import pragmas must be for imported entities
4091
4092          if Prag_Id = Pragma_Import_Function
4093               or else
4094             Prag_Id = Pragma_Import_Procedure
4095               or else
4096             Prag_Id = Pragma_Import_Valued_Procedure
4097          then
4098             if not Is_Imported (Ent) then
4099                Error_Pragma
4100                  ("pragma Import or Interface must precede pragma%");
4101             end if;
4102
4103          --  Here we have the Export case which can set the entity as exported
4104
4105          --  But does not do so if the specified external name is null, since
4106          --  that is taken as a signal in DEC Ada 83 (with which we want to be
4107          --  compatible) to request no external name.
4108
4109          elsif Nkind (Arg_External) = N_String_Literal
4110            and then String_Length (Strval (Arg_External)) = 0
4111          then
4112             null;
4113
4114          --  In all other cases, set entity as exported
4115
4116          else
4117             Set_Exported (Ent, Arg_Internal);
4118          end if;
4119
4120          --  Special processing for Valued_Procedure cases
4121
4122          if Prag_Id = Pragma_Import_Valued_Procedure
4123            or else
4124             Prag_Id = Pragma_Export_Valued_Procedure
4125          then
4126             Formal := First_Formal (Ent);
4127
4128             if No (Formal) then
4129                Error_Pragma ("at least one parameter required for pragma%");
4130
4131             elsif Ekind (Formal) /= E_Out_Parameter then
4132                Error_Pragma ("first parameter must have mode out for pragma%");
4133
4134             else
4135                Set_Is_Valued_Procedure (Ent);
4136             end if;
4137          end if;
4138
4139          Set_Extended_Import_Export_External_Name (Ent, Arg_External);
4140
4141          --  Process Result_Mechanism argument if present. We have already
4142          --  checked that this is only allowed for the function case.
4143
4144          if Present (Arg_Result_Mechanism) then
4145             Set_Mechanism_Value (Ent, Arg_Result_Mechanism);
4146          end if;
4147
4148          --  Process Mechanism parameter if present. Note that this parameter
4149          --  is not analyzed, and must not be analyzed since it is semantic
4150          --  nonsense, so we get it in exactly as the parser left it.
4151
4152          if Present (Arg_Mechanism) then
4153             declare
4154                Formal : Entity_Id;
4155                Massoc : Node_Id;
4156                Mname  : Node_Id;
4157                Choice : Node_Id;
4158
4159             begin
4160                --  A single mechanism association without a formal parameter
4161                --  name is parsed as a parenthesized expression. All other
4162                --  cases are parsed as aggregates, so we rewrite the single
4163                --  parameter case as an aggregate for consistency.
4164
4165                if Nkind (Arg_Mechanism) /= N_Aggregate
4166                  and then Paren_Count (Arg_Mechanism) = 1
4167                then
4168                   Rewrite (Arg_Mechanism,
4169                     Make_Aggregate (Sloc (Arg_Mechanism),
4170                       Expressions => New_List (
4171                         Relocate_Node (Arg_Mechanism))));
4172                end if;
4173
4174                --  Case of only mechanism name given, applies to all formals
4175
4176                if Nkind (Arg_Mechanism) /= N_Aggregate then
4177                   Formal := First_Formal (Ent);
4178                   while Present (Formal) loop
4179                      Set_Mechanism_Value (Formal, Arg_Mechanism);
4180                      Next_Formal (Formal);
4181                   end loop;
4182
4183                --  Case of list of mechanism associations given
4184
4185                else
4186                   if Null_Record_Present (Arg_Mechanism) then
4187                      Error_Pragma_Arg
4188                        ("inappropriate form for Mechanism parameter",
4189                         Arg_Mechanism);
4190                   end if;
4191
4192                   --  Deal with positional ones first
4193
4194                   Formal := First_Formal (Ent);
4195
4196                   if Present (Expressions (Arg_Mechanism)) then
4197                      Mname := First (Expressions (Arg_Mechanism));
4198                      while Present (Mname) loop
4199                         if No (Formal) then
4200                            Error_Pragma_Arg
4201                              ("too many mechanism associations", Mname);
4202                         end if;
4203
4204                         Set_Mechanism_Value (Formal, Mname);
4205                         Next_Formal (Formal);
4206                         Next (Mname);
4207                      end loop;
4208                   end if;
4209
4210                   --  Deal with named entries
4211
4212                   if Present (Component_Associations (Arg_Mechanism)) then
4213                      Massoc := First (Component_Associations (Arg_Mechanism));
4214                      while Present (Massoc) loop
4215                         Choice := First (Choices (Massoc));
4216
4217                         if Nkind (Choice) /= N_Identifier
4218                           or else Present (Next (Choice))
4219                         then
4220                            Error_Pragma_Arg
4221                              ("incorrect form for mechanism association",
4222                               Massoc);
4223                         end if;
4224
4225                         Formal := First_Formal (Ent);
4226                         loop
4227                            if No (Formal) then
4228                               Error_Pragma_Arg
4229                                 ("parameter name & not present", Choice);
4230                            end if;
4231
4232                            if Chars (Choice) = Chars (Formal) then
4233                               Set_Mechanism_Value
4234                                 (Formal, Expression (Massoc));
4235
4236                               --  Set entity on identifier (needed by ASIS)
4237
4238                               Set_Entity (Choice, Formal);
4239
4240                               exit;
4241                            end if;
4242
4243                            Next_Formal (Formal);
4244                         end loop;
4245
4246                         Next (Massoc);
4247                      end loop;
4248                   end if;
4249                end if;
4250             end;
4251          end if;
4252
4253          --  Process First_Optional_Parameter argument if present. We have
4254          --  already checked that this is only allowed for the Import case.
4255
4256          if Present (Arg_First_Optional_Parameter) then
4257             if Nkind (Arg_First_Optional_Parameter) /= N_Identifier then
4258                Error_Pragma_Arg
4259                  ("first optional parameter must be formal parameter name",
4260                   Arg_First_Optional_Parameter);
4261             end if;
4262
4263             Formal := First_Formal (Ent);
4264             loop
4265                if No (Formal) then
4266                   Error_Pragma_Arg
4267                     ("specified formal parameter& not found",
4268                      Arg_First_Optional_Parameter);
4269                end if;
4270
4271                exit when Chars (Formal) =
4272                          Chars (Arg_First_Optional_Parameter);
4273
4274                Next_Formal (Formal);
4275             end loop;
4276
4277             Set_First_Optional_Parameter (Ent, Formal);
4278
4279             --  Check specified and all remaining formals have right form
4280
4281             while Present (Formal) loop
4282                if Ekind (Formal) /= E_In_Parameter then
4283                   Error_Msg_NE
4284                     ("optional formal& is not of mode in!",
4285                      Arg_First_Optional_Parameter, Formal);
4286
4287                else
4288                   Dval := Default_Value (Formal);
4289
4290                   if No (Dval) then
4291                      Error_Msg_NE
4292                        ("optional formal& does not have default value!",
4293                         Arg_First_Optional_Parameter, Formal);
4294
4295                   elsif Compile_Time_Known_Value_Or_Aggr (Dval) then
4296                      null;
4297
4298                   else
4299                      Error_Msg_FE
4300                        ("default value for optional formal& is non-static!",
4301                         Arg_First_Optional_Parameter, Formal);
4302                   end if;
4303                end if;
4304
4305                Set_Is_Optional_Parameter (Formal);
4306                Next_Formal (Formal);
4307             end loop;
4308          end if;
4309       end Process_Extended_Import_Export_Subprogram_Pragma;
4310
4311       --------------------------
4312       -- Process_Generic_List --
4313       --------------------------
4314
4315       procedure Process_Generic_List is
4316          Arg : Node_Id;
4317          Exp : Node_Id;
4318
4319       begin
4320          Check_No_Identifiers;
4321          Check_At_Least_N_Arguments (1);
4322
4323          Arg := Arg1;
4324          while Present (Arg) loop
4325             Exp := Get_Pragma_Arg (Arg);
4326             Analyze (Exp);
4327
4328             if not Is_Entity_Name (Exp)
4329               or else
4330                 (not Is_Generic_Instance (Entity (Exp))
4331                   and then
4332                  not Is_Generic_Unit (Entity (Exp)))
4333             then
4334                Error_Pragma_Arg
4335                  ("pragma% argument must be name of generic unit/instance",
4336                   Arg);
4337             end if;
4338
4339             Next (Arg);
4340          end loop;
4341       end Process_Generic_List;
4342
4343       ------------------------------------
4344       -- Process_Import_Predefined_Type --
4345       ------------------------------------
4346
4347       procedure Process_Import_Predefined_Type is
4348          Loc  : constant Source_Ptr := Sloc (N);
4349          Elmt : Elmt_Id;
4350          Ftyp : Node_Id := Empty;
4351          Decl : Node_Id;
4352          Def  : Node_Id;
4353          Nam  : Name_Id;
4354
4355       begin
4356          String_To_Name_Buffer (Strval (Expression (Arg3)));
4357          Nam := Name_Find;
4358
4359          Elmt := First_Elmt (Predefined_Float_Types);
4360          while Present (Elmt) and then Chars (Node (Elmt)) /= Nam loop
4361             Next_Elmt (Elmt);
4362          end loop;
4363
4364          Ftyp := Node (Elmt);
4365
4366          if Present (Ftyp) then
4367
4368             --  Don't build a derived type declaration, because predefined C
4369             --  types have no declaration anywhere, so cannot really be named.
4370             --  Instead build a full type declaration, starting with an
4371             --  appropriate type definition is built
4372
4373             if Is_Floating_Point_Type (Ftyp) then
4374                Def := Make_Floating_Point_Definition (Loc,
4375                  Make_Integer_Literal (Loc, Digits_Value (Ftyp)),
4376                  Make_Real_Range_Specification (Loc,
4377                    Make_Real_Literal (Loc, Realval (Type_Low_Bound (Ftyp))),
4378                    Make_Real_Literal (Loc, Realval (Type_High_Bound (Ftyp)))));
4379
4380             --  Should never have a predefined type we cannot handle
4381
4382             else
4383                raise Program_Error;
4384             end if;
4385
4386             --  Build and insert a Full_Type_Declaration, which will be
4387             --  analyzed as soon as this list entry has been analyzed.
4388
4389             Decl := Make_Full_Type_Declaration (Loc,
4390               Make_Defining_Identifier (Loc, Chars (Expression (Arg2))),
4391               Type_Definition => Def);
4392
4393             Insert_After (N, Decl);
4394             Mark_Rewrite_Insertion (Decl);
4395
4396          else
4397             Error_Pragma_Arg ("no matching type found for pragma%",
4398             Arg2);
4399          end if;
4400       end Process_Import_Predefined_Type;
4401
4402       ---------------------------------
4403       -- Process_Import_Or_Interface --
4404       ---------------------------------
4405
4406       procedure Process_Import_Or_Interface is
4407          C      : Convention_Id;
4408          Def_Id : Entity_Id;
4409          Hom_Id : Entity_Id;
4410
4411       begin
4412          Process_Convention (C, Def_Id);
4413          Kill_Size_Check_Code (Def_Id);
4414          Note_Possible_Modification (Get_Pragma_Arg (Arg2), Sure => False);
4415
4416          if Ekind_In (Def_Id, E_Variable, E_Constant) then
4417
4418             --  We do not permit Import to apply to a renaming declaration
4419
4420             if Present (Renamed_Object (Def_Id)) then
4421                Error_Pragma_Arg
4422                  ("pragma% not allowed for object renaming", Arg2);
4423
4424             --  User initialization is not allowed for imported object, but
4425             --  the object declaration may contain a default initialization,
4426             --  that will be discarded. Note that an explicit initialization
4427             --  only counts if it comes from source, otherwise it is simply
4428             --  the code generator making an implicit initialization explicit.
4429
4430             elsif Present (Expression (Parent (Def_Id)))
4431               and then Comes_From_Source (Expression (Parent (Def_Id)))
4432             then
4433                Error_Msg_Sloc := Sloc (Def_Id);
4434                Error_Pragma_Arg
4435                  ("no initialization allowed for declaration of& #",
4436                   "\imported entities cannot be initialized (RM B.1(24))",
4437                   Arg2);
4438
4439             else
4440                Set_Imported (Def_Id);
4441                Process_Interface_Name (Def_Id, Arg3, Arg4);
4442
4443                --  Note that we do not set Is_Public here. That's because we
4444                --  only want to set it if there is no address clause, and we
4445                --  don't know that yet, so we delay that processing till
4446                --  freeze time.
4447
4448                --  pragma Import completes deferred constants
4449
4450                if Ekind (Def_Id) = E_Constant then
4451                   Set_Has_Completion (Def_Id);
4452                end if;
4453
4454                --  It is not possible to import a constant of an unconstrained
4455                --  array type (e.g. string) because there is no simple way to
4456                --  write a meaningful subtype for it.
4457
4458                if Is_Array_Type (Etype (Def_Id))
4459                  and then not Is_Constrained (Etype (Def_Id))
4460                then
4461                   Error_Msg_NE
4462                     ("imported constant& must have a constrained subtype",
4463                       N, Def_Id);
4464                end if;
4465             end if;
4466
4467          elsif Is_Subprogram (Def_Id)
4468            or else Is_Generic_Subprogram (Def_Id)
4469          then
4470             --  If the name is overloaded, pragma applies to all of the denoted
4471             --  entities in the same declarative part.
4472
4473             Hom_Id := Def_Id;
4474             while Present (Hom_Id) loop
4475                Def_Id := Get_Base_Subprogram (Hom_Id);
4476
4477                --  Ignore inherited subprograms because the pragma will apply
4478                --  to the parent operation, which is the one called.
4479
4480                if Is_Overloadable (Def_Id)
4481                  and then Present (Alias (Def_Id))
4482                then
4483                   null;
4484
4485                --  If it is not a subprogram, it must be in an outer scope and
4486                --  pragma does not apply.
4487
4488                elsif not Is_Subprogram (Def_Id)
4489                  and then not Is_Generic_Subprogram (Def_Id)
4490                then
4491                   null;
4492
4493                --  The pragma does not apply to primitives of interfaces
4494
4495                elsif Is_Dispatching_Operation (Def_Id)
4496                  and then Present (Find_Dispatching_Type (Def_Id))
4497                  and then Is_Interface (Find_Dispatching_Type (Def_Id))
4498                then
4499                   null;
4500
4501                --  Verify that the homonym is in the same declarative part (not
4502                --  just the same scope).
4503
4504                elsif Parent (Unit_Declaration_Node (Def_Id)) /= Parent (N)
4505                  and then Nkind (Parent (N)) /= N_Compilation_Unit_Aux
4506                then
4507                   exit;
4508
4509                else
4510                   Set_Imported (Def_Id);
4511
4512                   --  Reject an Import applied to an abstract subprogram
4513
4514                   if Is_Subprogram (Def_Id)
4515                     and then Is_Abstract_Subprogram (Def_Id)
4516                   then
4517                      Error_Msg_Sloc := Sloc (Def_Id);
4518                      Error_Msg_NE
4519                        ("cannot import abstract subprogram& declared#",
4520                         Arg2, Def_Id);
4521                   end if;
4522
4523                   --  Special processing for Convention_Intrinsic
4524
4525                   if C = Convention_Intrinsic then
4526
4527                      --  Link_Name argument not allowed for intrinsic
4528
4529                      Check_No_Link_Name;
4530
4531                      Set_Is_Intrinsic_Subprogram (Def_Id);
4532
4533                      --  If no external name is present, then check that this
4534                      --  is a valid intrinsic subprogram. If an external name
4535                      --  is present, then this is handled by the back end.
4536
4537                      if No (Arg3) then
4538                         Check_Intrinsic_Subprogram
4539                           (Def_Id, Get_Pragma_Arg (Arg2));
4540                      end if;
4541                   end if;
4542
4543                   --  All interfaced procedures need an external symbol created
4544                   --  for them since they are always referenced from another
4545                   --  object file.
4546
4547                   Set_Is_Public (Def_Id);
4548
4549                   --  Verify that the subprogram does not have a completion
4550                   --  through a renaming declaration. For other completions the
4551                   --  pragma appears as a too late representation.
4552
4553                   declare
4554                      Decl : constant Node_Id := Unit_Declaration_Node (Def_Id);
4555
4556                   begin
4557                      if Present (Decl)
4558                        and then Nkind (Decl) = N_Subprogram_Declaration
4559                        and then Present (Corresponding_Body (Decl))
4560                        and then Nkind (Unit_Declaration_Node
4561                                         (Corresponding_Body (Decl))) =
4562                                              N_Subprogram_Renaming_Declaration
4563                      then
4564                         Error_Msg_Sloc := Sloc (Def_Id);
4565                         Error_Msg_NE
4566                           ("cannot import&, renaming already provided for " &
4567                            "declaration #", N, Def_Id);
4568                      end if;
4569                   end;
4570
4571                   Set_Has_Completion (Def_Id);
4572                   Process_Interface_Name (Def_Id, Arg3, Arg4);
4573                end if;
4574
4575                if Is_Compilation_Unit (Hom_Id) then
4576
4577                   --  Its possible homonyms are not affected by the pragma.
4578                   --  Such homonyms might be present in the context of other
4579                   --  units being compiled.
4580
4581                   exit;
4582
4583                else
4584                   Hom_Id := Homonym (Hom_Id);
4585                end if;
4586             end loop;
4587
4588          --  When the convention is Java or CIL, we also allow Import to be
4589          --  given for packages, generic packages, exceptions, record
4590          --  components, and access to subprograms.
4591
4592          elsif (C = Convention_Java or else C = Convention_CIL)
4593            and then
4594              (Is_Package_Or_Generic_Package (Def_Id)
4595                or else Ekind (Def_Id) = E_Exception
4596                or else Ekind (Def_Id) = E_Access_Subprogram_Type
4597                or else Nkind (Parent (Def_Id)) = N_Component_Declaration)
4598          then
4599             Set_Imported (Def_Id);
4600             Set_Is_Public (Def_Id);
4601             Process_Interface_Name (Def_Id, Arg3, Arg4);
4602
4603          --  Import a CPP class
4604
4605          elsif Is_Record_Type (Def_Id)
4606            and then C = Convention_CPP
4607          then
4608             --  Types treated as CPP classes must be declared limited (note:
4609             --  this used to be a warning but there is no real benefit to it
4610             --  since we did effectively intend to treat the type as limited
4611             --  anyway).
4612
4613             if not Is_Limited_Type (Def_Id) then
4614                Error_Msg_N
4615                  ("imported 'C'P'P type must be limited",
4616                   Get_Pragma_Arg (Arg2));
4617             end if;
4618
4619             Set_Is_CPP_Class (Def_Id);
4620
4621             --  Imported CPP types must not have discriminants (because C++
4622             --  classes do not have discriminants).
4623
4624             if Has_Discriminants (Def_Id) then
4625                Error_Msg_N
4626                  ("imported 'C'P'P type cannot have discriminants",
4627                   First (Discriminant_Specifications
4628                           (Declaration_Node (Def_Id))));
4629             end if;
4630
4631             --  Components of imported CPP types must not have default
4632             --  expressions because the constructor (if any) is on the
4633             --  C++ side.
4634
4635             declare
4636                Tdef  : constant Node_Id :=
4637                          Type_Definition (Declaration_Node (Def_Id));
4638                Clist : Node_Id;
4639                Comp  : Node_Id;
4640
4641             begin
4642                if Nkind (Tdef) = N_Record_Definition then
4643                   Clist := Component_List (Tdef);
4644
4645                else
4646                   pragma Assert (Nkind (Tdef) = N_Derived_Type_Definition);
4647                   Clist := Component_List (Record_Extension_Part (Tdef));
4648                end if;
4649
4650                if Present (Clist) then
4651                   Comp := First (Component_Items (Clist));
4652                   while Present (Comp) loop
4653                      if Present (Expression (Comp)) then
4654                         Error_Msg_N
4655                           ("component of imported 'C'P'P type cannot have" &
4656                            " default expression", Expression (Comp));
4657                      end if;
4658
4659                      Next (Comp);
4660                   end loop;
4661                end if;
4662             end;
4663
4664          elsif Nkind (Parent (Def_Id)) = N_Incomplete_Type_Declaration then
4665             Check_No_Link_Name;
4666             Check_Arg_Count (3);
4667             Check_Arg_Is_Static_Expression (Arg3, Standard_String);
4668
4669             Process_Import_Predefined_Type;
4670
4671          else
4672             Error_Pragma_Arg
4673               ("second argument of pragma% must be object, subprogram" &
4674                " or incomplete type",
4675                Arg2);
4676          end if;
4677
4678          --  If this pragma applies to a compilation unit, then the unit, which
4679          --  is a subprogram, does not require (or allow) a body. We also do
4680          --  not need to elaborate imported procedures.
4681
4682          if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
4683             declare
4684                Cunit : constant Node_Id := Parent (Parent (N));
4685             begin
4686                Set_Body_Required (Cunit, False);
4687             end;
4688          end if;
4689       end Process_Import_Or_Interface;
4690
4691       --------------------
4692       -- Process_Inline --
4693       --------------------
4694
4695       procedure Process_Inline (Active : Boolean) is
4696          Assoc     : Node_Id;
4697          Decl      : Node_Id;
4698          Subp_Id   : Node_Id;
4699          Subp      : Entity_Id;
4700          Applies   : Boolean;
4701
4702          Effective : Boolean := False;
4703          --  Set True if inline has some effect, i.e. if there is at least one
4704          --  subprogram set as inlined as a result of the use of the pragma.
4705
4706          procedure Make_Inline (Subp : Entity_Id);
4707          --  Subp is the defining unit name of the subprogram declaration. Set
4708          --  the flag, as well as the flag in the corresponding body, if there
4709          --  is one present.
4710
4711          procedure Set_Inline_Flags (Subp : Entity_Id);
4712          --  Sets Is_Inlined and Has_Pragma_Inline flags for Subp and also
4713          --  Has_Pragma_Inline_Always for the Inline_Always case.
4714
4715          function Inlining_Not_Possible (Subp : Entity_Id) return Boolean;
4716          --  Returns True if it can be determined at this stage that inlining
4717          --  is not possible, for example if the body is available and contains
4718          --  exception handlers, we prevent inlining, since otherwise we can
4719          --  get undefined symbols at link time. This function also emits a
4720          --  warning if front-end inlining is enabled and the pragma appears
4721          --  too late.
4722          --
4723          --  ??? is business with link symbols still valid, or does it relate
4724          --  to front end ZCX which is being phased out ???
4725
4726          ---------------------------
4727          -- Inlining_Not_Possible --
4728          ---------------------------
4729
4730          function Inlining_Not_Possible (Subp : Entity_Id) return Boolean is
4731             Decl  : constant Node_Id := Unit_Declaration_Node (Subp);
4732             Stats : Node_Id;
4733
4734          begin
4735             if Nkind (Decl) = N_Subprogram_Body then
4736                Stats := Handled_Statement_Sequence (Decl);
4737                return Present (Exception_Handlers (Stats))
4738                  or else Present (At_End_Proc (Stats));
4739
4740             elsif Nkind (Decl) = N_Subprogram_Declaration
4741               and then Present (Corresponding_Body (Decl))
4742             then
4743                if Front_End_Inlining
4744                  and then Analyzed (Corresponding_Body (Decl))
4745                then
4746                   Error_Msg_N ("pragma appears too late, ignored?", N);
4747                   return True;
4748
4749                --  If the subprogram is a renaming as body, the body is just a
4750                --  call to the renamed subprogram, and inlining is trivially
4751                --  possible.
4752
4753                elsif
4754                  Nkind (Unit_Declaration_Node (Corresponding_Body (Decl))) =
4755                                              N_Subprogram_Renaming_Declaration
4756                then
4757                   return False;
4758
4759                else
4760                   Stats :=
4761                     Handled_Statement_Sequence
4762                         (Unit_Declaration_Node (Corresponding_Body (Decl)));
4763
4764                   return
4765                     Present (Exception_Handlers (Stats))
4766                       or else Present (At_End_Proc (Stats));
4767                end if;
4768
4769             else
4770                --  If body is not available, assume the best, the check is
4771                --  performed again when compiling enclosing package bodies.
4772
4773                return False;
4774             end if;
4775          end Inlining_Not_Possible;
4776
4777          -----------------
4778          -- Make_Inline --
4779          -----------------
4780
4781          procedure Make_Inline (Subp : Entity_Id) is
4782             Kind       : constant Entity_Kind := Ekind (Subp);
4783             Inner_Subp : Entity_Id   := Subp;
4784
4785          begin
4786             --  Ignore if bad type, avoid cascaded error
4787
4788             if Etype (Subp) = Any_Type then
4789                Applies := True;
4790                return;
4791
4792             --  Ignore if all inlining is suppressed
4793
4794             elsif Suppress_All_Inlining then
4795                Applies := True;
4796                return;
4797
4798             --  If inlining is not possible, for now do not treat as an error
4799
4800             elsif Inlining_Not_Possible (Subp) then
4801                Applies := True;
4802                return;
4803
4804             --  Here we have a candidate for inlining, but we must exclude
4805             --  derived operations. Otherwise we would end up trying to inline
4806             --  a phantom declaration, and the result would be to drag in a
4807             --  body which has no direct inlining associated with it. That
4808             --  would not only be inefficient but would also result in the
4809             --  backend doing cross-unit inlining in cases where it was
4810             --  definitely inappropriate to do so.
4811
4812             --  However, a simple Comes_From_Source test is insufficient, since
4813             --  we do want to allow inlining of generic instances which also do
4814             --  not come from source. We also need to recognize specs generated
4815             --  by the front-end for bodies that carry the pragma. Finally,
4816             --  predefined operators do not come from source but are not
4817             --  inlineable either.
4818
4819             elsif Is_Generic_Instance (Subp)
4820               or else Nkind (Parent (Parent (Subp))) = N_Subprogram_Declaration
4821             then
4822                null;
4823
4824             elsif not Comes_From_Source (Subp)
4825               and then Scope (Subp) /= Standard_Standard
4826             then
4827                Applies := True;
4828                return;
4829             end if;
4830
4831             --  The referenced entity must either be the enclosing entity, or
4832             --  an entity declared within the current open scope.
4833
4834             if Present (Scope (Subp))
4835               and then Scope (Subp) /= Current_Scope
4836               and then Subp /= Current_Scope
4837             then
4838                Error_Pragma_Arg
4839                  ("argument of% must be entity in current scope", Assoc);
4840                return;
4841             end if;
4842
4843             --  Processing for procedure, operator or function. If subprogram
4844             --  is aliased (as for an instance) indicate that the renamed
4845             --  entity (if declared in the same unit) is inlined.
4846
4847             if Is_Subprogram (Subp) then
4848                Inner_Subp := Ultimate_Alias (Inner_Subp);
4849
4850                if In_Same_Source_Unit (Subp, Inner_Subp) then
4851                   Set_Inline_Flags (Inner_Subp);
4852
4853                   Decl := Parent (Parent (Inner_Subp));
4854
4855                   if Nkind (Decl) = N_Subprogram_Declaration
4856                     and then Present (Corresponding_Body (Decl))
4857                   then
4858                      Set_Inline_Flags (Corresponding_Body (Decl));
4859
4860                   elsif Is_Generic_Instance (Subp) then
4861
4862                      --  Indicate that the body needs to be created for
4863                      --  inlining subsequent calls. The instantiation node
4864                      --  follows the declaration of the wrapper package
4865                      --  created for it.
4866
4867                      if Scope (Subp) /= Standard_Standard
4868                        and then
4869                          Need_Subprogram_Instance_Body
4870                           (Next (Unit_Declaration_Node (Scope (Alias (Subp)))),
4871                               Subp)
4872                      then
4873                         null;
4874                      end if;
4875
4876                   --  Inline is a program unit pragma (RM 10.1.5) and cannot
4877                   --  appear in a formal part to apply to a formal subprogram.
4878                   --  Do not apply check within an instance or a formal package
4879                   --  the test will have been applied to the original generic.
4880
4881                   elsif Nkind (Decl) in N_Formal_Subprogram_Declaration
4882                     and then List_Containing (Decl) = List_Containing (N)
4883                     and then not In_Instance
4884                   then
4885                      Error_Msg_N
4886                        ("Inline cannot apply to a formal subprogram", N);
4887                   end if;
4888                end if;
4889
4890                Applies := True;
4891
4892             --  For a generic subprogram set flag as well, for use at the point
4893             --  of instantiation, to determine whether the body should be
4894             --  generated.
4895
4896             elsif Is_Generic_Subprogram (Subp) then
4897                Set_Inline_Flags (Subp);
4898                Applies := True;
4899
4900             --  Literals are by definition inlined
4901
4902             elsif Kind = E_Enumeration_Literal then
4903                null;
4904
4905             --  Anything else is an error
4906
4907             else
4908                Error_Pragma_Arg
4909                  ("expect subprogram name for pragma%", Assoc);
4910             end if;
4911          end Make_Inline;
4912
4913          ----------------------
4914          -- Set_Inline_Flags --
4915          ----------------------
4916
4917          procedure Set_Inline_Flags (Subp : Entity_Id) is
4918          begin
4919             if Active then
4920                Set_Is_Inlined (Subp);
4921             end if;
4922
4923             if not Has_Pragma_Inline (Subp) then
4924                Set_Has_Pragma_Inline (Subp);
4925                Effective := True;
4926             end if;
4927
4928             if Prag_Id = Pragma_Inline_Always then
4929                Set_Has_Pragma_Inline_Always (Subp);
4930             end if;
4931          end Set_Inline_Flags;
4932
4933       --  Start of processing for Process_Inline
4934
4935       begin
4936          Check_No_Identifiers;
4937          Check_At_Least_N_Arguments (1);
4938
4939          if Active then
4940             Inline_Processing_Required := True;
4941          end if;
4942
4943          Assoc := Arg1;
4944          while Present (Assoc) loop
4945             Subp_Id := Get_Pragma_Arg (Assoc);
4946             Analyze (Subp_Id);
4947             Applies := False;
4948
4949             if Is_Entity_Name (Subp_Id) then
4950                Subp := Entity (Subp_Id);
4951
4952                if Subp = Any_Id then
4953
4954                   --  If previous error, avoid cascaded errors
4955
4956                   Applies := True;
4957                   Effective := True;
4958
4959                else
4960                   Make_Inline (Subp);
4961
4962                   --  For the pragma case, climb homonym chain. This is
4963                   --  what implements allowing the pragma in the renaming
4964                   --  case, with the result applying to the ancestors, and
4965                   --  also allows Inline to apply to all previous homonyms.
4966
4967                   if not From_Aspect_Specification (N) then
4968                      while Present (Homonym (Subp))
4969                        and then Scope (Homonym (Subp)) = Current_Scope
4970                      loop
4971                         Make_Inline (Homonym (Subp));
4972                         Subp := Homonym (Subp);
4973                      end loop;
4974                   end if;
4975                end if;
4976             end if;
4977
4978             if not Applies then
4979                Error_Pragma_Arg
4980                  ("inappropriate argument for pragma%", Assoc);
4981
4982             elsif not Effective
4983               and then Warn_On_Redundant_Constructs
4984               and then not Suppress_All_Inlining
4985             then
4986                if Inlining_Not_Possible (Subp) then
4987                   Error_Msg_NE
4988                     ("pragma Inline for& is ignored?", N, Entity (Subp_Id));
4989                else
4990                   Error_Msg_NE
4991                     ("pragma Inline for& is redundant?", N, Entity (Subp_Id));
4992                end if;
4993             end if;
4994
4995             Next (Assoc);
4996          end loop;
4997       end Process_Inline;
4998
4999       ----------------------------
5000       -- Process_Interface_Name --
5001       ----------------------------
5002
5003       procedure Process_Interface_Name
5004         (Subprogram_Def : Entity_Id;
5005          Ext_Arg        : Node_Id;
5006          Link_Arg       : Node_Id)
5007       is
5008          Ext_Nam    : Node_Id;
5009          Link_Nam   : Node_Id;
5010          String_Val : String_Id;
5011
5012          procedure Check_Form_Of_Interface_Name
5013            (SN            : Node_Id;
5014             Ext_Name_Case : Boolean);
5015          --  SN is a string literal node for an interface name. This routine
5016          --  performs some minimal checks that the name is reasonable. In
5017          --  particular that no spaces or other obviously incorrect characters
5018          --  appear. This is only a warning, since any characters are allowed.
5019          --  Ext_Name_Case is True for an External_Name, False for a Link_Name.
5020
5021          ----------------------------------
5022          -- Check_Form_Of_Interface_Name --
5023          ----------------------------------
5024
5025          procedure Check_Form_Of_Interface_Name
5026            (SN            : Node_Id;
5027             Ext_Name_Case : Boolean)
5028          is
5029             S  : constant String_Id := Strval (Expr_Value_S (SN));
5030             SL : constant Nat       := String_Length (S);
5031             C  : Char_Code;
5032
5033          begin
5034             if SL = 0 then
5035                Error_Msg_N ("interface name cannot be null string", SN);
5036             end if;
5037
5038             for J in 1 .. SL loop
5039                C := Get_String_Char (S, J);
5040
5041                --  Look for dubious character and issue unconditional warning.
5042                --  Definitely dubious if not in character range.
5043
5044                if not In_Character_Range (C)
5045
5046                   --  For all cases except CLI target,
5047                   --  commas, spaces and slashes are dubious (in CLI, we use
5048                   --  commas and backslashes in external names to specify
5049                   --  assembly version and public key, while slashes and spaces
5050                   --  can be used in names to mark nested classes and
5051                   --  valuetypes).
5052
5053                   or else ((not Ext_Name_Case or else VM_Target /= CLI_Target)
5054                              and then (Get_Character (C) = ','
5055                                          or else
5056                                        Get_Character (C) = '\'))
5057                  or else (VM_Target /= CLI_Target
5058                             and then (Get_Character (C) = ' '
5059                                         or else
5060                                       Get_Character (C) = '/'))
5061                then
5062                   Error_Msg
5063                     ("?interface name contains illegal character",
5064                      Sloc (SN) + Source_Ptr (J));
5065                end if;
5066             end loop;
5067          end Check_Form_Of_Interface_Name;
5068
5069       --  Start of processing for Process_Interface_Name
5070
5071       begin
5072          if No (Link_Arg) then
5073             if No (Ext_Arg) then
5074                if VM_Target = CLI_Target
5075                  and then Ekind (Subprogram_Def) = E_Package
5076                  and then Nkind (Parent (Subprogram_Def)) =
5077                                                  N_Package_Specification
5078                  and then Present (Generic_Parent (Parent (Subprogram_Def)))
5079                then
5080                   Set_Interface_Name
5081                      (Subprogram_Def,
5082                       Interface_Name
5083                         (Generic_Parent (Parent (Subprogram_Def))));
5084                end if;
5085
5086                return;
5087
5088             elsif Chars (Ext_Arg) = Name_Link_Name then
5089                Ext_Nam  := Empty;
5090                Link_Nam := Expression (Ext_Arg);
5091
5092             else
5093                Check_Optional_Identifier (Ext_Arg, Name_External_Name);
5094                Ext_Nam  := Expression (Ext_Arg);
5095                Link_Nam := Empty;
5096             end if;
5097
5098          else
5099             Check_Optional_Identifier (Ext_Arg,  Name_External_Name);
5100             Check_Optional_Identifier (Link_Arg, Name_Link_Name);
5101             Ext_Nam  := Expression (Ext_Arg);
5102             Link_Nam := Expression (Link_Arg);
5103          end if;
5104
5105          --  Check expressions for external name and link name are static
5106
5107          if Present (Ext_Nam) then
5108             Check_Arg_Is_Static_Expression (Ext_Nam, Standard_String);
5109             Check_Form_Of_Interface_Name (Ext_Nam, Ext_Name_Case => True);
5110
5111             --  Verify that external name is not the name of a local entity,
5112             --  which would hide the imported one and could lead to run-time
5113             --  surprises. The problem can only arise for entities declared in
5114             --  a package body (otherwise the external name is fully qualified
5115             --  and will not conflict).
5116
5117             declare
5118                Nam : Name_Id;
5119                E   : Entity_Id;
5120                Par : Node_Id;
5121
5122             begin
5123                if Prag_Id = Pragma_Import then
5124                   String_To_Name_Buffer (Strval (Expr_Value_S (Ext_Nam)));
5125                   Nam := Name_Find;
5126                   E   := Entity_Id (Get_Name_Table_Info (Nam));
5127
5128                   if Nam /= Chars (Subprogram_Def)
5129                     and then Present (E)
5130                     and then not Is_Overloadable (E)
5131                     and then Is_Immediately_Visible (E)
5132                     and then not Is_Imported (E)
5133                     and then Ekind (Scope (E)) = E_Package
5134                   then
5135                      Par := Parent (E);
5136                      while Present (Par) loop
5137                         if Nkind (Par) = N_Package_Body then
5138                            Error_Msg_Sloc := Sloc (E);
5139                            Error_Msg_NE
5140                              ("imported entity is hidden by & declared#",
5141                               Ext_Arg, E);
5142                            exit;
5143                         end if;
5144
5145                         Par := Parent (Par);
5146                      end loop;
5147                   end if;
5148                end if;
5149             end;
5150          end if;
5151
5152          if Present (Link_Nam) then
5153             Check_Arg_Is_Static_Expression (Link_Nam, Standard_String);
5154             Check_Form_Of_Interface_Name (Link_Nam, Ext_Name_Case => False);
5155          end if;
5156
5157          --  If there is no link name, just set the external name
5158
5159          if No (Link_Nam) then
5160             Link_Nam := Adjust_External_Name_Case (Expr_Value_S (Ext_Nam));
5161
5162          --  For the Link_Name case, the given literal is preceded by an
5163          --  asterisk, which indicates to GCC that the given name should be
5164          --  taken literally, and in particular that no prepending of
5165          --  underlines should occur, even in systems where this is the
5166          --  normal default.
5167
5168          else
5169             Start_String;
5170
5171             if VM_Target = No_VM then
5172                Store_String_Char (Get_Char_Code ('*'));
5173             end if;
5174
5175             String_Val := Strval (Expr_Value_S (Link_Nam));
5176             Store_String_Chars (String_Val);
5177             Link_Nam :=
5178               Make_String_Literal (Sloc (Link_Nam),
5179                 Strval => End_String);
5180          end if;
5181
5182          --  Set the interface name. If the entity is a generic instance, use
5183          --  its alias, which is the callable entity.
5184
5185          if Is_Generic_Instance (Subprogram_Def) then
5186             Set_Encoded_Interface_Name
5187               (Alias (Get_Base_Subprogram (Subprogram_Def)), Link_Nam);
5188          else
5189             Set_Encoded_Interface_Name
5190               (Get_Base_Subprogram (Subprogram_Def), Link_Nam);
5191          end if;
5192
5193          --  We allow duplicated export names in CIL/Java, as they are always
5194          --  enclosed in a namespace that differentiates them, and overloaded
5195          --  entities are supported by the VM.
5196
5197          if Convention (Subprogram_Def) /= Convention_CIL
5198               and then
5199             Convention (Subprogram_Def) /= Convention_Java
5200          then
5201             Check_Duplicated_Export_Name (Link_Nam);
5202          end if;
5203       end Process_Interface_Name;
5204
5205       -----------------------------------------
5206       -- Process_Interrupt_Or_Attach_Handler --
5207       -----------------------------------------
5208
5209       procedure Process_Interrupt_Or_Attach_Handler is
5210          Arg1_X       : constant Node_Id   := Get_Pragma_Arg (Arg1);
5211          Handler_Proc : constant Entity_Id := Entity (Arg1_X);
5212          Proc_Scope   : constant Entity_Id := Scope (Handler_Proc);
5213
5214       begin
5215          Set_Is_Interrupt_Handler (Handler_Proc);
5216
5217          --  If the pragma is not associated with a handler procedure within a
5218          --  protected type, then it must be for a nonprotected procedure for
5219          --  the AAMP target, in which case we don't associate a representation
5220          --  item with the procedure's scope.
5221
5222          if Ekind (Proc_Scope) = E_Protected_Type then
5223             if Prag_Id = Pragma_Interrupt_Handler
5224                  or else
5225                Prag_Id = Pragma_Attach_Handler
5226             then
5227                Record_Rep_Item (Proc_Scope, N);
5228             end if;
5229          end if;
5230       end Process_Interrupt_Or_Attach_Handler;
5231
5232       --------------------------------------------------
5233       -- Process_Restrictions_Or_Restriction_Warnings --
5234       --------------------------------------------------
5235
5236       --  Note: some of the simple identifier cases were handled in par-prag,
5237       --  but it is harmless (and more straightforward) to simply handle all
5238       --  cases here, even if it means we repeat a bit of work in some cases.
5239
5240       procedure Process_Restrictions_Or_Restriction_Warnings
5241         (Warn : Boolean)
5242       is
5243          Arg   : Node_Id;
5244          R_Id  : Restriction_Id;
5245          Id    : Name_Id;
5246          Expr  : Node_Id;
5247          Val   : Uint;
5248
5249          procedure Check_Unit_Name (N : Node_Id);
5250          --  Checks unit name parameter for No_Dependence. Returns if it has
5251          --  an appropriate form, otherwise raises pragma argument error.
5252
5253          ---------------------
5254          -- Check_Unit_Name --
5255          ---------------------
5256
5257          procedure Check_Unit_Name (N : Node_Id) is
5258          begin
5259             if Nkind (N) = N_Selected_Component then
5260                Check_Unit_Name (Prefix (N));
5261                Check_Unit_Name (Selector_Name (N));
5262
5263             elsif Nkind (N) = N_Identifier then
5264                return;
5265
5266             else
5267                Error_Pragma_Arg
5268                  ("wrong form for unit name for No_Dependence", N);
5269             end if;
5270          end Check_Unit_Name;
5271
5272       --  Start of processing for Process_Restrictions_Or_Restriction_Warnings
5273
5274       begin
5275          --  Ignore all Restrictions pragma in CodePeer mode
5276
5277          if CodePeer_Mode then
5278             return;
5279          end if;
5280
5281          Check_Ada_83_Warning;
5282          Check_At_Least_N_Arguments (1);
5283          Check_Valid_Configuration_Pragma;
5284
5285          Arg := Arg1;
5286          while Present (Arg) loop
5287             Id := Chars (Arg);
5288             Expr := Get_Pragma_Arg (Arg);
5289
5290             --  Case of no restriction identifier present
5291
5292             if Id = No_Name then
5293                if Nkind (Expr) /= N_Identifier then
5294                   Error_Pragma_Arg
5295                     ("invalid form for restriction", Arg);
5296                end if;
5297
5298                R_Id :=
5299                  Get_Restriction_Id
5300                    (Process_Restriction_Synonyms (Expr));
5301
5302                if R_Id not in All_Boolean_Restrictions then
5303                   Error_Msg_Name_1 := Pname;
5304                   Error_Msg_N
5305                     ("invalid restriction identifier&", Get_Pragma_Arg (Arg));
5306
5307                   --  Check for possible misspelling
5308
5309                   for J in Restriction_Id loop
5310                      declare
5311                         Rnm : constant String := Restriction_Id'Image (J);
5312
5313                      begin
5314                         Name_Buffer (1 .. Rnm'Length) := Rnm;
5315                         Name_Len := Rnm'Length;
5316                         Set_Casing (All_Lower_Case);
5317
5318                         if Is_Bad_Spelling_Of (Chars (Expr), Name_Enter) then
5319                            Set_Casing
5320                              (Identifier_Casing (Current_Source_File));
5321                            Error_Msg_String (1 .. Rnm'Length) :=
5322                              Name_Buffer (1 .. Name_Len);
5323                            Error_Msg_Strlen := Rnm'Length;
5324                            Error_Msg_N -- CODEFIX
5325                              ("\possible misspelling of ""~""",
5326                               Get_Pragma_Arg (Arg));
5327                            exit;
5328                         end if;
5329                      end;
5330                   end loop;
5331
5332                   raise Pragma_Exit;
5333                end if;
5334
5335                if Implementation_Restriction (R_Id) then
5336                   Check_Restriction (No_Implementation_Restrictions, Arg);
5337                end if;
5338
5339                --  Special processing for No_Elaboration_Code restriction
5340
5341                if R_Id = No_Elaboration_Code then
5342
5343                   --  Restriction is only recognized within a configuration
5344                   --  pragma file, or within a unit of the main extended
5345                   --  program. Note: the test for Main_Unit is needed to
5346                   --  properly include the case of configuration pragma files.
5347
5348                   if not (Current_Sem_Unit = Main_Unit
5349                            or else In_Extended_Main_Source_Unit (N))
5350                   then
5351                      return;
5352
5353                   --  Don't allow in a subunit unless already specified in
5354                   --  body or spec.
5355
5356                   elsif Nkind (Parent (N)) = N_Compilation_Unit
5357                     and then Nkind (Unit (Parent (N))) = N_Subunit
5358                     and then not Restriction_Active (No_Elaboration_Code)
5359                   then
5360                      Error_Msg_N
5361                        ("invalid specification of ""No_Elaboration_Code""",
5362                         N);
5363                      Error_Msg_N
5364                        ("\restriction cannot be specified in a subunit", N);
5365                      Error_Msg_N
5366                        ("\unless also specified in body or spec", N);
5367                      return;
5368
5369                   --  If we have a No_Elaboration_Code pragma that we
5370                   --  accept, then it needs to be added to the configuration
5371                   --  restrcition set so that we get proper application to
5372                   --  other units in the main extended source as required.
5373
5374                   else
5375                      Add_To_Config_Boolean_Restrictions (No_Elaboration_Code);
5376                   end if;
5377                end if;
5378
5379                --  If this is a warning, then set the warning unless we already
5380                --  have a real restriction active (we never want a warning to
5381                --  override a real restriction).
5382
5383                if Warn then
5384                   if not Restriction_Active (R_Id) then
5385                      Set_Restriction (R_Id, N);
5386                      Restriction_Warnings (R_Id) := True;
5387                   end if;
5388
5389                --  If real restriction case, then set it and make sure that the
5390                --  restriction warning flag is off, since a real restriction
5391                --  always overrides a warning.
5392
5393                else
5394                   Set_Restriction (R_Id, N);
5395                   Restriction_Warnings (R_Id) := False;
5396                end if;
5397
5398                --  Check for obsolescent restrictions in Ada 2005 mode
5399
5400                if not Warn
5401                  and then Ada_Version >= Ada_2005
5402                  and then (R_Id = No_Asynchronous_Control
5403                             or else
5404                            R_Id = No_Unchecked_Deallocation
5405                             or else
5406                            R_Id = No_Unchecked_Conversion)
5407                then
5408                   Check_Restriction (No_Obsolescent_Features, N);
5409                end if;
5410
5411                --  A very special case that must be processed here: pragma
5412                --  Restrictions (No_Exceptions) turns off all run-time
5413                --  checking. This is a bit dubious in terms of the formal
5414                --  language definition, but it is what is intended by RM
5415                --  H.4(12). Restriction_Warnings never affects generated code
5416                --  so this is done only in the real restriction case.
5417
5418                --  Atomic_Synchronization is not a real check, so it is not
5419                --  affected by this processing).
5420
5421                if R_Id = No_Exceptions and then not Warn then
5422                   for J in Scope_Suppress'Range loop
5423                      if J /= Atomic_Synchronization then
5424                         Scope_Suppress (J) := True;
5425                      end if;
5426                   end loop;
5427                end if;
5428
5429             --  Case of No_Dependence => unit-name. Note that the parser
5430             --  already made the necessary entry in the No_Dependence table.
5431
5432             elsif Id = Name_No_Dependence then
5433                Check_Unit_Name (Expr);
5434
5435             --  Case of No_Specification_Of_Aspect => Identifier.
5436
5437             elsif Id = Name_No_Specification_Of_Aspect then
5438                declare
5439                   A_Id : Aspect_Id;
5440
5441                begin
5442                   if Nkind (Expr) /= N_Identifier then
5443                      A_Id := No_Aspect;
5444                   else
5445                      A_Id := Get_Aspect_Id (Chars (Expr));
5446                   end if;
5447
5448                   if A_Id = No_Aspect then
5449                      Error_Pragma_Arg ("invalid restriction name", Arg);
5450                   else
5451                      Set_Restriction_No_Specification_Of_Aspect (Expr, Warn);
5452                   end if;
5453                end;
5454
5455             --  All other cases of restriction identifier present
5456
5457             else
5458                R_Id := Get_Restriction_Id (Process_Restriction_Synonyms (Arg));
5459                Analyze_And_Resolve (Expr, Any_Integer);
5460
5461                if R_Id not in All_Parameter_Restrictions then
5462                   Error_Pragma_Arg
5463                     ("invalid restriction parameter identifier", Arg);
5464
5465                elsif not Is_OK_Static_Expression (Expr) then
5466                   Flag_Non_Static_Expr
5467                     ("value must be static expression!", Expr);
5468                   raise Pragma_Exit;
5469
5470                elsif not Is_Integer_Type (Etype (Expr))
5471                  or else Expr_Value (Expr) < 0
5472                then
5473                   Error_Pragma_Arg
5474                     ("value must be non-negative integer", Arg);
5475                end if;
5476
5477                --  Restriction pragma is active
5478
5479                Val := Expr_Value (Expr);
5480
5481                if not UI_Is_In_Int_Range (Val) then
5482                   Error_Pragma_Arg
5483                     ("pragma ignored, value too large?", Arg);
5484                end if;
5485
5486                --  Warning case. If the real restriction is active, then we
5487                --  ignore the request, since warning never overrides a real
5488                --  restriction. Otherwise we set the proper warning. Note that
5489                --  this circuit sets the warning again if it is already set,
5490                --  which is what we want, since the constant may have changed.
5491
5492                if Warn then
5493                   if not Restriction_Active (R_Id) then
5494                      Set_Restriction
5495                        (R_Id, N, Integer (UI_To_Int (Val)));
5496                      Restriction_Warnings (R_Id) := True;
5497                   end if;
5498
5499                --  Real restriction case, set restriction and make sure warning
5500                --  flag is off since real restriction always overrides warning.
5501
5502                else
5503                   Set_Restriction (R_Id, N, Integer (UI_To_Int (Val)));
5504                   Restriction_Warnings (R_Id) := False;
5505                end if;
5506             end if;
5507
5508             Next (Arg);
5509          end loop;
5510       end Process_Restrictions_Or_Restriction_Warnings;
5511
5512       ---------------------------------
5513       -- Process_Suppress_Unsuppress --
5514       ---------------------------------
5515
5516       --  Note: this procedure makes entries in the check suppress data
5517       --  structures managed by Sem. See spec of package Sem for full
5518       --  details on how we handle recording of check suppression.
5519
5520       procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean) is
5521          C    : Check_Id;
5522          E_Id : Node_Id;
5523          E    : Entity_Id;
5524
5525          In_Package_Spec : constant Boolean :=
5526                              Is_Package_Or_Generic_Package (Current_Scope)
5527                                and then not In_Package_Body (Current_Scope);
5528
5529          procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id);
5530          --  Used to suppress a single check on the given entity
5531
5532          --------------------------------
5533          -- Suppress_Unsuppress_Echeck --
5534          --------------------------------
5535
5536          procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id) is
5537          begin
5538             --  Check for error of trying to set atomic synchronization for
5539             --  a non-atomic variable.
5540
5541             if C = Atomic_Synchronization
5542               and then not (Is_Atomic (E) or else Has_Atomic_Components (E))
5543             then
5544                Error_Msg_N
5545                  ("pragma & requires atomic type or variable",
5546                   Pragma_Identifier (Original_Node (N)));
5547             end if;
5548
5549             Set_Checks_May_Be_Suppressed (E);
5550
5551             if In_Package_Spec then
5552                Push_Global_Suppress_Stack_Entry
5553                  (Entity   => E,
5554                   Check    => C,
5555                   Suppress => Suppress_Case);
5556             else
5557                Push_Local_Suppress_Stack_Entry
5558                  (Entity   => E,
5559                   Check    => C,
5560                   Suppress => Suppress_Case);
5561             end if;
5562
5563             --  If this is a first subtype, and the base type is distinct,
5564             --  then also set the suppress flags on the base type.
5565
5566             if Is_First_Subtype (E)
5567               and then Etype (E) /= E
5568             then
5569                Suppress_Unsuppress_Echeck (Etype (E), C);
5570             end if;
5571          end Suppress_Unsuppress_Echeck;
5572
5573       --  Start of processing for Process_Suppress_Unsuppress
5574
5575       begin
5576          --  Ignore pragma Suppress/Unsuppress in CodePeer and Alfa modes on
5577          --  user code: we want to generate checks for analysis purposes, as
5578          --  set respectively by -gnatC and -gnatd.F
5579
5580          if (CodePeer_Mode or Alfa_Mode)
5581            and then Comes_From_Source (N)
5582          then
5583             return;
5584          end if;
5585
5586          --  Suppress/Unsuppress can appear as a configuration pragma, or in a
5587          --  declarative part or a package spec (RM 11.5(5)).
5588
5589          if not Is_Configuration_Pragma then
5590             Check_Is_In_Decl_Part_Or_Package_Spec;
5591          end if;
5592
5593          Check_At_Least_N_Arguments (1);
5594          Check_At_Most_N_Arguments (2);
5595          Check_No_Identifier (Arg1);
5596          Check_Arg_Is_Identifier (Arg1);
5597
5598          C := Get_Check_Id (Chars (Get_Pragma_Arg (Arg1)));
5599
5600          if C = No_Check_Id then
5601             Error_Pragma_Arg
5602               ("argument of pragma% is not valid check name", Arg1);
5603          end if;
5604
5605          if not Suppress_Case
5606            and then (C = All_Checks or else C = Overflow_Check)
5607          then
5608             Opt.Overflow_Checks_Unsuppressed := True;
5609          end if;
5610
5611          if Arg_Count = 1 then
5612
5613             --  Make an entry in the local scope suppress table. This is the
5614             --  table that directly shows the current value of the scope
5615             --  suppress check for any check id value.
5616
5617             if C = All_Checks then
5618
5619                --  For All_Checks, we set all specific predefined checks with
5620                --  the exception of Elaboration_Check, which is handled
5621                --  specially because of not wanting All_Checks to have the
5622                --  effect of deactivating static elaboration order processing.
5623                --  Atomic_Synchronization is also not affected, since this is
5624                --  not a real check.
5625
5626                for J in Scope_Suppress'Range loop
5627                   if J /= Elaboration_Check
5628                     and then J /= Atomic_Synchronization
5629                   then
5630                      Scope_Suppress (J) := Suppress_Case;
5631                   end if;
5632                end loop;
5633
5634             --  If not All_Checks, and predefined check, then set appropriate
5635             --  scope entry. Note that we will set Elaboration_Check if this
5636             --  is explicitly specified. Atomic_Synchronization is allowed
5637             --  only if internally generated and entity is atomic.
5638
5639             elsif C in Predefined_Check_Id
5640               and then (not Comes_From_Source (N)
5641                          or else C /= Atomic_Synchronization)
5642             then
5643                Scope_Suppress (C) := Suppress_Case;
5644             end if;
5645
5646             --  Also make an entry in the Local_Entity_Suppress table
5647
5648             Push_Local_Suppress_Stack_Entry
5649               (Entity   => Empty,
5650                Check    => C,
5651                Suppress => Suppress_Case);
5652
5653          --  Case of two arguments present, where the check is suppressed for
5654          --  a specified entity (given as the second argument of the pragma)
5655
5656          else
5657             --  This is obsolescent in Ada 2005 mode
5658
5659             if Ada_Version >= Ada_2005 then
5660                Check_Restriction (No_Obsolescent_Features, Arg2);
5661             end if;
5662
5663             Check_Optional_Identifier (Arg2, Name_On);
5664             E_Id := Get_Pragma_Arg (Arg2);
5665             Analyze (E_Id);
5666
5667             if not Is_Entity_Name (E_Id) then
5668                Error_Pragma_Arg
5669                  ("second argument of pragma% must be entity name", Arg2);
5670             end if;
5671
5672             E := Entity (E_Id);
5673
5674             if E = Any_Id then
5675                return;
5676             end if;
5677
5678             --  Enforce RM 11.5(7) which requires that for a pragma that
5679             --  appears within a package spec, the named entity must be
5680             --  within the package spec. We allow the package name itself
5681             --  to be mentioned since that makes sense, although it is not
5682             --  strictly allowed by 11.5(7).
5683
5684             if In_Package_Spec
5685               and then E /= Current_Scope
5686               and then Scope (E) /= Current_Scope
5687             then
5688                Error_Pragma_Arg
5689                  ("entity in pragma% is not in package spec (RM 11.5(7))",
5690                   Arg2);
5691             end if;
5692
5693             --  Loop through homonyms. As noted below, in the case of a package
5694             --  spec, only homonyms within the package spec are considered.
5695
5696             loop
5697                Suppress_Unsuppress_Echeck (E, C);
5698
5699                if Is_Generic_Instance (E)
5700                  and then Is_Subprogram (E)
5701                  and then Present (Alias (E))
5702                then
5703                   Suppress_Unsuppress_Echeck (Alias (E), C);
5704                end if;
5705
5706                --  Move to next homonym if not aspect spec case
5707
5708                exit when From_Aspect_Specification (N);
5709                E := Homonym (E);
5710                exit when No (E);
5711
5712                --  If we are within a package specification, the pragma only
5713                --  applies to homonyms in the same scope.
5714
5715                exit when In_Package_Spec
5716                  and then Scope (E) /= Current_Scope;
5717             end loop;
5718          end if;
5719       end Process_Suppress_Unsuppress;
5720
5721       ------------------
5722       -- Set_Exported --
5723       ------------------
5724
5725       procedure Set_Exported (E : Entity_Id; Arg : Node_Id) is
5726       begin
5727          if Is_Imported (E) then
5728             Error_Pragma_Arg
5729               ("cannot export entity& that was previously imported", Arg);
5730
5731          elsif Present (Address_Clause (E)) and then not CodePeer_Mode then
5732             Error_Pragma_Arg
5733               ("cannot export entity& that has an address clause", Arg);
5734          end if;
5735
5736          Set_Is_Exported (E);
5737
5738          --  Generate a reference for entity explicitly, because the
5739          --  identifier may be overloaded and name resolution will not
5740          --  generate one.
5741
5742          Generate_Reference (E, Arg);
5743
5744          --  Deal with exporting non-library level entity
5745
5746          if not Is_Library_Level_Entity (E) then
5747
5748             --  Not allowed at all for subprograms
5749
5750             if Is_Subprogram (E) then
5751                Error_Pragma_Arg ("local subprogram& cannot be exported", Arg);
5752
5753             --  Otherwise set public and statically allocated
5754
5755             else
5756                Set_Is_Public (E);
5757                Set_Is_Statically_Allocated (E);
5758
5759                --  Warn if the corresponding W flag is set and the pragma comes
5760                --  from source. The latter may not be true e.g. on VMS where we
5761                --  expand export pragmas for exception codes associated with
5762                --  imported or exported exceptions. We do not want to generate
5763                --  a warning for something that the user did not write.
5764
5765                if Warn_On_Export_Import
5766                  and then Comes_From_Source (Arg)
5767                then
5768                   Error_Msg_NE
5769                     ("?& has been made static as a result of Export", Arg, E);
5770                   Error_Msg_N
5771                     ("\this usage is non-standard and non-portable", Arg);
5772                end if;
5773             end if;
5774          end if;
5775
5776          if Warn_On_Export_Import and then Is_Type (E) then
5777             Error_Msg_NE ("exporting a type has no effect?", Arg, E);
5778          end if;
5779
5780          if Warn_On_Export_Import and Inside_A_Generic then
5781             Error_Msg_NE
5782               ("all instances of& will have the same external name?", Arg, E);
5783          end if;
5784       end Set_Exported;
5785
5786       ----------------------------------------------
5787       -- Set_Extended_Import_Export_External_Name --
5788       ----------------------------------------------
5789
5790       procedure Set_Extended_Import_Export_External_Name
5791         (Internal_Ent : Entity_Id;
5792          Arg_External : Node_Id)
5793       is
5794          Old_Name : constant Node_Id := Interface_Name (Internal_Ent);
5795          New_Name : Node_Id;
5796
5797       begin
5798          if No (Arg_External) then
5799             return;
5800          end if;
5801
5802          Check_Arg_Is_External_Name (Arg_External);
5803
5804          if Nkind (Arg_External) = N_String_Literal then
5805             if String_Length (Strval (Arg_External)) = 0 then
5806                return;
5807             else
5808                New_Name := Adjust_External_Name_Case (Arg_External);
5809             end if;
5810
5811          elsif Nkind (Arg_External) = N_Identifier then
5812             New_Name := Get_Default_External_Name (Arg_External);
5813
5814          --  Check_Arg_Is_External_Name should let through only identifiers and
5815          --  string literals or static string expressions (which are folded to
5816          --  string literals).
5817
5818          else
5819             raise Program_Error;
5820          end if;
5821
5822          --  If we already have an external name set (by a prior normal Import
5823          --  or Export pragma), then the external names must match
5824
5825          if Present (Interface_Name (Internal_Ent)) then
5826             Check_Matching_Internal_Names : declare
5827                S1 : constant String_Id := Strval (Old_Name);
5828                S2 : constant String_Id := Strval (New_Name);
5829
5830                procedure Mismatch;
5831                --  Called if names do not match
5832
5833                --------------
5834                -- Mismatch --
5835                --------------
5836
5837                procedure Mismatch is
5838                begin
5839                   Error_Msg_Sloc := Sloc (Old_Name);
5840                   Error_Pragma_Arg
5841                     ("external name does not match that given #",
5842                      Arg_External);
5843                end Mismatch;
5844
5845             --  Start of processing for Check_Matching_Internal_Names
5846
5847             begin
5848                if String_Length (S1) /= String_Length (S2) then
5849                   Mismatch;
5850
5851                else
5852                   for J in 1 .. String_Length (S1) loop
5853                      if Get_String_Char (S1, J) /= Get_String_Char (S2, J) then
5854                         Mismatch;
5855                      end if;
5856                   end loop;
5857                end if;
5858             end Check_Matching_Internal_Names;
5859
5860          --  Otherwise set the given name
5861
5862          else
5863             Set_Encoded_Interface_Name (Internal_Ent, New_Name);
5864             Check_Duplicated_Export_Name (New_Name);
5865          end if;
5866       end Set_Extended_Import_Export_External_Name;
5867
5868       ------------------
5869       -- Set_Imported --
5870       ------------------
5871
5872       procedure Set_Imported (E : Entity_Id) is
5873       begin
5874          --  Error message if already imported or exported
5875
5876          if Is_Exported (E) or else Is_Imported (E) then
5877
5878             --  Error if being set Exported twice
5879
5880             if Is_Exported (E) then
5881                Error_Msg_NE ("entity& was previously exported", N, E);
5882
5883             --  OK if Import/Interface case
5884
5885             elsif Import_Interface_Present (N) then
5886                goto OK;
5887
5888             --  Error if being set Imported twice
5889
5890             else
5891                Error_Msg_NE ("entity& was previously imported", N, E);
5892             end if;
5893
5894             Error_Msg_Name_1 := Pname;
5895             Error_Msg_N
5896               ("\(pragma% applies to all previous entities)", N);
5897
5898             Error_Msg_Sloc  := Sloc (E);
5899             Error_Msg_NE ("\import not allowed for& declared#", N, E);
5900
5901          --  Here if not previously imported or exported, OK to import
5902
5903          else
5904             Set_Is_Imported (E);
5905
5906             --  If the entity is an object that is not at the library level,
5907             --  then it is statically allocated. We do not worry about objects
5908             --  with address clauses in this context since they are not really
5909             --  imported in the linker sense.
5910
5911             if Is_Object (E)
5912               and then not Is_Library_Level_Entity (E)
5913               and then No (Address_Clause (E))
5914             then
5915                Set_Is_Statically_Allocated (E);
5916             end if;
5917          end if;
5918
5919          <<OK>> null;
5920       end Set_Imported;
5921
5922       -------------------------
5923       -- Set_Mechanism_Value --
5924       -------------------------
5925
5926       --  Note: the mechanism name has not been analyzed (and cannot indeed be
5927       --  analyzed, since it is semantic nonsense), so we get it in the exact
5928       --  form created by the parser.
5929
5930       procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id) is
5931          Class        : Node_Id;
5932          Param        : Node_Id;
5933          Mech_Name_Id : Name_Id;
5934
5935          procedure Bad_Class;
5936          --  Signal bad descriptor class name
5937
5938          procedure Bad_Mechanism;
5939          --  Signal bad mechanism name
5940
5941          ---------------
5942          -- Bad_Class --
5943          ---------------
5944
5945          procedure Bad_Class is
5946          begin
5947             Error_Pragma_Arg ("unrecognized descriptor class name", Class);
5948          end Bad_Class;
5949
5950          -------------------------
5951          -- Bad_Mechanism_Value --
5952          -------------------------
5953
5954          procedure Bad_Mechanism is
5955          begin
5956             Error_Pragma_Arg ("unrecognized mechanism name", Mech_Name);
5957          end Bad_Mechanism;
5958
5959       --  Start of processing for Set_Mechanism_Value
5960
5961       begin
5962          if Mechanism (Ent) /= Default_Mechanism then
5963             Error_Msg_NE
5964               ("mechanism for & has already been set", Mech_Name, Ent);
5965          end if;
5966
5967          --  MECHANISM_NAME ::= value | reference | descriptor |
5968          --                     short_descriptor
5969
5970          if Nkind (Mech_Name) = N_Identifier then
5971             if Chars (Mech_Name) = Name_Value then
5972                Set_Mechanism (Ent, By_Copy);
5973                return;
5974
5975             elsif Chars (Mech_Name) = Name_Reference then
5976                Set_Mechanism (Ent, By_Reference);
5977                return;
5978
5979             elsif Chars (Mech_Name) = Name_Descriptor then
5980                Check_VMS (Mech_Name);
5981
5982                --  Descriptor => Short_Descriptor if pragma was given
5983
5984                if Short_Descriptors then
5985                   Set_Mechanism (Ent, By_Short_Descriptor);
5986                else
5987                   Set_Mechanism (Ent, By_Descriptor);
5988                end if;
5989
5990                return;
5991
5992             elsif Chars (Mech_Name) = Name_Short_Descriptor then
5993                Check_VMS (Mech_Name);
5994                Set_Mechanism (Ent, By_Short_Descriptor);
5995                return;
5996
5997             elsif Chars (Mech_Name) = Name_Copy then
5998                Error_Pragma_Arg
5999                  ("bad mechanism name, Value assumed", Mech_Name);
6000
6001             else
6002                Bad_Mechanism;
6003             end if;
6004
6005          --  MECHANISM_NAME ::= descriptor (CLASS_NAME) |
6006          --                     short_descriptor (CLASS_NAME)
6007          --  CLASS_NAME     ::= ubs | ubsb | uba | s | sb | a | nca
6008
6009          --  Note: this form is parsed as an indexed component
6010
6011          elsif Nkind (Mech_Name) = N_Indexed_Component then
6012             Class := First (Expressions (Mech_Name));
6013
6014             if Nkind (Prefix (Mech_Name)) /= N_Identifier
6015              or else not (Chars (Prefix (Mech_Name)) = Name_Descriptor or else
6016                           Chars (Prefix (Mech_Name)) = Name_Short_Descriptor)
6017              or else Present (Next (Class))
6018             then
6019                Bad_Mechanism;
6020             else
6021                Mech_Name_Id := Chars (Prefix (Mech_Name));
6022
6023                --  Change Descriptor => Short_Descriptor if pragma was given
6024
6025                if Mech_Name_Id = Name_Descriptor
6026                  and then Short_Descriptors
6027                then
6028                   Mech_Name_Id := Name_Short_Descriptor;
6029                end if;
6030             end if;
6031
6032          --  MECHANISM_NAME ::= descriptor (Class => CLASS_NAME) |
6033          --                     short_descriptor (Class => CLASS_NAME)
6034          --  CLASS_NAME     ::= ubs | ubsb | uba | s | sb | a | nca
6035
6036          --  Note: this form is parsed as a function call
6037
6038          elsif Nkind (Mech_Name) = N_Function_Call then
6039             Param := First (Parameter_Associations (Mech_Name));
6040
6041             if Nkind (Name (Mech_Name)) /= N_Identifier
6042               or else not (Chars (Name (Mech_Name)) = Name_Descriptor or else
6043                            Chars (Name (Mech_Name)) = Name_Short_Descriptor)
6044               or else Present (Next (Param))
6045               or else No (Selector_Name (Param))
6046               or else Chars (Selector_Name (Param)) /= Name_Class
6047             then
6048                Bad_Mechanism;
6049             else
6050                Class := Explicit_Actual_Parameter (Param);
6051                Mech_Name_Id := Chars (Name (Mech_Name));
6052             end if;
6053
6054          else
6055             Bad_Mechanism;
6056          end if;
6057
6058          --  Fall through here with Class set to descriptor class name
6059
6060          Check_VMS (Mech_Name);
6061
6062          if Nkind (Class) /= N_Identifier then
6063             Bad_Class;
6064
6065          elsif Mech_Name_Id = Name_Descriptor
6066            and then Chars (Class) = Name_UBS
6067          then
6068             Set_Mechanism (Ent, By_Descriptor_UBS);
6069
6070          elsif Mech_Name_Id = Name_Descriptor
6071            and then Chars (Class) = Name_UBSB
6072          then
6073             Set_Mechanism (Ent, By_Descriptor_UBSB);
6074
6075          elsif Mech_Name_Id = Name_Descriptor
6076            and then Chars (Class) = Name_UBA
6077          then
6078             Set_Mechanism (Ent, By_Descriptor_UBA);
6079
6080          elsif Mech_Name_Id = Name_Descriptor
6081            and then Chars (Class) = Name_S
6082          then
6083             Set_Mechanism (Ent, By_Descriptor_S);
6084
6085          elsif Mech_Name_Id = Name_Descriptor
6086            and then Chars (Class) = Name_SB
6087          then
6088             Set_Mechanism (Ent, By_Descriptor_SB);
6089
6090          elsif Mech_Name_Id = Name_Descriptor
6091            and then Chars (Class) = Name_A
6092          then
6093             Set_Mechanism (Ent, By_Descriptor_A);
6094
6095          elsif Mech_Name_Id = Name_Descriptor
6096            and then Chars (Class) = Name_NCA
6097          then
6098             Set_Mechanism (Ent, By_Descriptor_NCA);
6099
6100          elsif Mech_Name_Id = Name_Short_Descriptor
6101            and then Chars (Class) = Name_UBS
6102          then
6103             Set_Mechanism (Ent, By_Short_Descriptor_UBS);
6104
6105          elsif Mech_Name_Id = Name_Short_Descriptor
6106            and then Chars (Class) = Name_UBSB
6107          then
6108             Set_Mechanism (Ent, By_Short_Descriptor_UBSB);
6109
6110          elsif Mech_Name_Id = Name_Short_Descriptor
6111            and then Chars (Class) = Name_UBA
6112          then
6113             Set_Mechanism (Ent, By_Short_Descriptor_UBA);
6114
6115          elsif Mech_Name_Id = Name_Short_Descriptor
6116            and then Chars (Class) = Name_S
6117          then
6118             Set_Mechanism (Ent, By_Short_Descriptor_S);
6119
6120          elsif Mech_Name_Id = Name_Short_Descriptor
6121            and then Chars (Class) = Name_SB
6122          then
6123             Set_Mechanism (Ent, By_Short_Descriptor_SB);
6124
6125          elsif Mech_Name_Id = Name_Short_Descriptor
6126            and then Chars (Class) = Name_A
6127          then
6128             Set_Mechanism (Ent, By_Short_Descriptor_A);
6129
6130          elsif Mech_Name_Id = Name_Short_Descriptor
6131            and then Chars (Class) = Name_NCA
6132          then
6133             Set_Mechanism (Ent, By_Short_Descriptor_NCA);
6134
6135          else
6136             Bad_Class;
6137          end if;
6138       end Set_Mechanism_Value;
6139
6140       ---------------------------
6141       -- Set_Ravenscar_Profile --
6142       ---------------------------
6143
6144       --  The tasks to be done here are
6145
6146       --    Set required policies
6147
6148       --      pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
6149       --      pragma Locking_Policy (Ceiling_Locking)
6150
6151       --    Set Detect_Blocking mode
6152
6153       --    Set required restrictions (see System.Rident for detailed list)
6154
6155       --    Set the No_Dependence rules
6156       --      No_Dependence => Ada.Asynchronous_Task_Control
6157       --      No_Dependence => Ada.Calendar
6158       --      No_Dependence => Ada.Execution_Time.Group_Budget
6159       --      No_Dependence => Ada.Execution_Time.Timers
6160       --      No_Dependence => Ada.Task_Attributes
6161       --      No_Dependence => System.Multiprocessors.Dispatching_Domains
6162
6163       procedure Set_Ravenscar_Profile (N : Node_Id) is
6164          Prefix_Entity   : Entity_Id;
6165          Selector_Entity : Entity_Id;
6166          Prefix_Node     : Node_Id;
6167          Node            : Node_Id;
6168
6169       begin
6170          --  pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
6171
6172          if Task_Dispatching_Policy /= ' '
6173            and then Task_Dispatching_Policy /= 'F'
6174          then
6175             Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
6176             Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
6177
6178          --  Set the FIFO_Within_Priorities policy, but always preserve
6179          --  System_Location since we like the error message with the run time
6180          --  name.
6181
6182          else
6183             Task_Dispatching_Policy := 'F';
6184
6185             if Task_Dispatching_Policy_Sloc /= System_Location then
6186                Task_Dispatching_Policy_Sloc := Loc;
6187             end if;
6188          end if;
6189
6190          --  pragma Locking_Policy (Ceiling_Locking)
6191
6192          if Locking_Policy /= ' '
6193            and then Locking_Policy /= 'C'
6194          then
6195             Error_Msg_Sloc := Locking_Policy_Sloc;
6196             Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
6197
6198          --  Set the Ceiling_Locking policy, but preserve System_Location since
6199          --  we like the error message with the run time name.
6200
6201          else
6202             Locking_Policy := 'C';
6203
6204             if Locking_Policy_Sloc /= System_Location then
6205                Locking_Policy_Sloc := Loc;
6206             end if;
6207          end if;
6208
6209          --  pragma Detect_Blocking
6210
6211          Detect_Blocking := True;
6212
6213          --  Set the corresponding restrictions
6214
6215          Set_Profile_Restrictions
6216            (Ravenscar, N, Warn => Treat_Restrictions_As_Warnings);
6217
6218          --  Set the No_Dependence restrictions
6219
6220          --  The following No_Dependence restrictions:
6221          --    No_Dependence => Ada.Asynchronous_Task_Control
6222          --    No_Dependence => Ada.Calendar
6223          --    No_Dependence => Ada.Task_Attributes
6224          --  are already set by previous call to Set_Profile_Restrictions.
6225
6226          --  Set the following restrictions which were added to Ada 2005:
6227          --    No_Dependence => Ada.Execution_Time.Group_Budget
6228          --    No_Dependence => Ada.Execution_Time.Timers
6229
6230          if Ada_Version >= Ada_2005 then
6231             Name_Buffer (1 .. 3) := "ada";
6232             Name_Len := 3;
6233
6234             Prefix_Entity := Make_Identifier (Loc, Name_Find);
6235
6236             Name_Buffer (1 .. 14) := "execution_time";
6237             Name_Len := 14;
6238
6239             Selector_Entity := Make_Identifier (Loc, Name_Find);
6240
6241             Prefix_Node :=
6242               Make_Selected_Component
6243                 (Sloc          => Loc,
6244                  Prefix        => Prefix_Entity,
6245                  Selector_Name => Selector_Entity);
6246
6247             Name_Buffer (1 .. 13) := "group_budgets";
6248             Name_Len := 13;
6249
6250             Selector_Entity := Make_Identifier (Loc, Name_Find);
6251
6252             Node :=
6253               Make_Selected_Component
6254                 (Sloc          => Loc,
6255                  Prefix        => Prefix_Node,
6256                  Selector_Name => Selector_Entity);
6257
6258             Set_Restriction_No_Dependence
6259               (Unit    => Node,
6260                Warn    => Treat_Restrictions_As_Warnings,
6261                Profile => Ravenscar);
6262
6263             Name_Buffer (1 .. 6) := "timers";
6264             Name_Len := 6;
6265
6266             Selector_Entity := Make_Identifier (Loc, Name_Find);
6267
6268             Node :=
6269               Make_Selected_Component
6270                 (Sloc          => Loc,
6271                  Prefix        => Prefix_Node,
6272                  Selector_Name => Selector_Entity);
6273
6274             Set_Restriction_No_Dependence
6275               (Unit    => Node,
6276                Warn    => Treat_Restrictions_As_Warnings,
6277                Profile => Ravenscar);
6278          end if;
6279
6280          --  Set the following restrictions which was added to Ada 2012 (see
6281          --  AI-0171):
6282          --    No_Dependence => System.Multiprocessors.Dispatching_Domains
6283
6284          if Ada_Version >= Ada_2012 then
6285             Name_Buffer (1 .. 6) := "system";
6286             Name_Len := 6;
6287
6288             Prefix_Entity := Make_Identifier (Loc, Name_Find);
6289
6290             Name_Buffer (1 .. 15) := "multiprocessors";
6291             Name_Len := 15;
6292
6293             Selector_Entity := Make_Identifier (Loc, Name_Find);
6294
6295             Prefix_Node :=
6296               Make_Selected_Component
6297                 (Sloc          => Loc,
6298                  Prefix        => Prefix_Entity,
6299                  Selector_Name => Selector_Entity);
6300
6301             Name_Buffer (1 .. 19) := "dispatching_domains";
6302             Name_Len := 19;
6303
6304             Selector_Entity := Make_Identifier (Loc, Name_Find);
6305
6306             Node :=
6307               Make_Selected_Component
6308                 (Sloc          => Loc,
6309                  Prefix        => Prefix_Node,
6310                  Selector_Name => Selector_Entity);
6311
6312             Set_Restriction_No_Dependence
6313               (Unit    => Node,
6314                Warn    => Treat_Restrictions_As_Warnings,
6315                Profile => Ravenscar);
6316          end if;
6317       end Set_Ravenscar_Profile;
6318
6319    --  Start of processing for Analyze_Pragma
6320
6321    begin
6322       --  The following code is a defense against recursion. Not clear that
6323       --  this can happen legitimately, but perhaps some error situations
6324       --  can cause it, and we did see this recursion during testing.
6325
6326       if Analyzed (N) then
6327          return;
6328       else
6329          Set_Analyzed (N, True);
6330       end if;
6331
6332       --  Deal with unrecognized pragma
6333
6334       Pname := Pragma_Name (N);
6335
6336       if not Is_Pragma_Name (Pname) then
6337          if Warn_On_Unrecognized_Pragma then
6338             Error_Msg_Name_1 := Pname;
6339             Error_Msg_N ("?unrecognized pragma%!", Pragma_Identifier (N));
6340
6341             for PN in First_Pragma_Name .. Last_Pragma_Name loop
6342                if Is_Bad_Spelling_Of (Pname, PN) then
6343                   Error_Msg_Name_1 := PN;
6344                   Error_Msg_N -- CODEFIX
6345                     ("\?possible misspelling of %!", Pragma_Identifier (N));
6346                   exit;
6347                end if;
6348             end loop;
6349          end if;
6350
6351          return;
6352       end if;
6353
6354       --  Here to start processing for recognized pragma
6355
6356       Prag_Id := Get_Pragma_Id (Pname);
6357
6358       if Present (Corresponding_Aspect (N)) then
6359          Pname := Chars (Identifier (Corresponding_Aspect (N)));
6360       end if;
6361
6362       --  Preset arguments
6363
6364       Arg_Count := 0;
6365       Arg1      := Empty;
6366       Arg2      := Empty;
6367       Arg3      := Empty;
6368       Arg4      := Empty;
6369
6370       if Present (Pragma_Argument_Associations (N)) then
6371          Arg_Count := List_Length (Pragma_Argument_Associations (N));
6372          Arg1 := First (Pragma_Argument_Associations (N));
6373
6374          if Present (Arg1) then
6375             Arg2 := Next (Arg1);
6376
6377             if Present (Arg2) then
6378                Arg3 := Next (Arg2);
6379
6380                if Present (Arg3) then
6381                   Arg4 := Next (Arg3);
6382                end if;
6383             end if;
6384          end if;
6385       end if;
6386
6387       --  An enumeration type defines the pragmas that are supported by the
6388       --  implementation. Get_Pragma_Id (in package Prag) transforms a name
6389       --  into the corresponding enumeration value for the following case.
6390
6391       case Prag_Id is
6392
6393          -----------------
6394          -- Abort_Defer --
6395          -----------------
6396
6397          --  pragma Abort_Defer;
6398
6399          when Pragma_Abort_Defer =>
6400             GNAT_Pragma;
6401             Check_Arg_Count (0);
6402
6403             --  The only required semantic processing is to check the
6404             --  placement. This pragma must appear at the start of the
6405             --  statement sequence of a handled sequence of statements.
6406
6407             if Nkind (Parent (N)) /= N_Handled_Sequence_Of_Statements
6408               or else N /= First (Statements (Parent (N)))
6409             then
6410                Pragma_Misplaced;
6411             end if;
6412
6413          ------------
6414          -- Ada_83 --
6415          ------------
6416
6417          --  pragma Ada_83;
6418
6419          --  Note: this pragma also has some specific processing in Par.Prag
6420          --  because we want to set the Ada version mode during parsing.
6421
6422          when Pragma_Ada_83 =>
6423             GNAT_Pragma;
6424             Check_Arg_Count (0);
6425
6426             --  We really should check unconditionally for proper configuration
6427             --  pragma placement, since we really don't want mixed Ada modes
6428             --  within a single unit, and the GNAT reference manual has always
6429             --  said this was a configuration pragma, but we did not check and
6430             --  are hesitant to add the check now.
6431
6432             --  However, we really cannot tolerate mixing Ada 2005 or Ada 2012
6433             --  with Ada 83 or Ada 95, so we must check if we are in Ada 2005
6434             --  or Ada 2012 mode.
6435
6436             if Ada_Version >= Ada_2005 then
6437                Check_Valid_Configuration_Pragma;
6438             end if;
6439
6440             --  Now set Ada 83 mode
6441
6442             Ada_Version := Ada_83;
6443             Ada_Version_Explicit := Ada_Version;
6444
6445          ------------
6446          -- Ada_95 --
6447          ------------
6448
6449          --  pragma Ada_95;
6450
6451          --  Note: this pragma also has some specific processing in Par.Prag
6452          --  because we want to set the Ada 83 version mode during parsing.
6453
6454          when Pragma_Ada_95 =>
6455             GNAT_Pragma;
6456             Check_Arg_Count (0);
6457
6458             --  We really should check unconditionally for proper configuration
6459             --  pragma placement, since we really don't want mixed Ada modes
6460             --  within a single unit, and the GNAT reference manual has always
6461             --  said this was a configuration pragma, but we did not check and
6462             --  are hesitant to add the check now.
6463
6464             --  However, we really cannot tolerate mixing Ada 2005 with Ada 83
6465             --  or Ada 95, so we must check if we are in Ada 2005 mode.
6466
6467             if Ada_Version >= Ada_2005 then
6468                Check_Valid_Configuration_Pragma;
6469             end if;
6470
6471             --  Now set Ada 95 mode
6472
6473             Ada_Version := Ada_95;
6474             Ada_Version_Explicit := Ada_Version;
6475
6476          ---------------------
6477          -- Ada_05/Ada_2005 --
6478          ---------------------
6479
6480          --  pragma Ada_05;
6481          --  pragma Ada_05 (LOCAL_NAME);
6482
6483          --  pragma Ada_2005;
6484          --  pragma Ada_2005 (LOCAL_NAME):
6485
6486          --  Note: these pragmas also have some specific processing in Par.Prag
6487          --  because we want to set the Ada 2005 version mode during parsing.
6488
6489          when Pragma_Ada_05 | Pragma_Ada_2005 => declare
6490             E_Id : Node_Id;
6491
6492          begin
6493             GNAT_Pragma;
6494
6495             if Arg_Count = 1 then
6496                Check_Arg_Is_Local_Name (Arg1);
6497                E_Id := Get_Pragma_Arg (Arg1);
6498
6499                if Etype (E_Id) = Any_Type then
6500                   return;
6501                end if;
6502
6503                Set_Is_Ada_2005_Only (Entity (E_Id));
6504
6505             else
6506                Check_Arg_Count (0);
6507
6508                --  For Ada_2005 we unconditionally enforce the documented
6509                --  configuration pragma placement, since we do not want to
6510                --  tolerate mixed modes in a unit involving Ada 2005. That
6511                --  would cause real difficulties for those cases where there
6512                --  are incompatibilities between Ada 95 and Ada 2005.
6513
6514                Check_Valid_Configuration_Pragma;
6515
6516                --  Now set appropriate Ada mode
6517
6518                Ada_Version          := Ada_2005;
6519                Ada_Version_Explicit := Ada_2005;
6520             end if;
6521          end;
6522
6523          ---------------------
6524          -- Ada_12/Ada_2012 --
6525          ---------------------
6526
6527          --  pragma Ada_12;
6528          --  pragma Ada_12 (LOCAL_NAME);
6529
6530          --  pragma Ada_2012;
6531          --  pragma Ada_2012 (LOCAL_NAME):
6532
6533          --  Note: these pragmas also have some specific processing in Par.Prag
6534          --  because we want to set the Ada 2012 version mode during parsing.
6535
6536          when Pragma_Ada_12 | Pragma_Ada_2012 => declare
6537             E_Id : Node_Id;
6538
6539          begin
6540             GNAT_Pragma;
6541
6542             if Arg_Count = 1 then
6543                Check_Arg_Is_Local_Name (Arg1);
6544                E_Id := Get_Pragma_Arg (Arg1);
6545
6546                if Etype (E_Id) = Any_Type then
6547                   return;
6548                end if;
6549
6550                Set_Is_Ada_2012_Only (Entity (E_Id));
6551
6552             else
6553                Check_Arg_Count (0);
6554
6555                --  For Ada_2012 we unconditionally enforce the documented
6556                --  configuration pragma placement, since we do not want to
6557                --  tolerate mixed modes in a unit involving Ada 2012. That
6558                --  would cause real difficulties for those cases where there
6559                --  are incompatibilities between Ada 95 and Ada 2012. We could
6560                --  allow mixing of Ada 2005 and Ada 2012 but it's not worth it.
6561
6562                Check_Valid_Configuration_Pragma;
6563
6564                --  Now set appropriate Ada mode
6565
6566                Ada_Version          := Ada_2012;
6567                Ada_Version_Explicit := Ada_2012;
6568             end if;
6569          end;
6570
6571          ----------------------
6572          -- All_Calls_Remote --
6573          ----------------------
6574
6575          --  pragma All_Calls_Remote [(library_package_NAME)];
6576
6577          when Pragma_All_Calls_Remote => All_Calls_Remote : declare
6578             Lib_Entity : Entity_Id;
6579
6580          begin
6581             Check_Ada_83_Warning;
6582             Check_Valid_Library_Unit_Pragma;
6583
6584             if Nkind (N) = N_Null_Statement then
6585                return;
6586             end if;
6587
6588             Lib_Entity := Find_Lib_Unit_Name;
6589
6590             --  This pragma should only apply to a RCI unit (RM E.2.3(23))
6591
6592             if Present (Lib_Entity)
6593               and then not Debug_Flag_U
6594             then
6595                if not Is_Remote_Call_Interface (Lib_Entity) then
6596                   Error_Pragma ("pragma% only apply to rci unit");
6597
6598                --  Set flag for entity of the library unit
6599
6600                else
6601                   Set_Has_All_Calls_Remote (Lib_Entity);
6602                end if;
6603
6604             end if;
6605          end All_Calls_Remote;
6606
6607          --------------
6608          -- Annotate --
6609          --------------
6610
6611          --  pragma Annotate (IDENTIFIER [, IDENTIFIER {, ARG}]);
6612          --  ARG ::= NAME | EXPRESSION
6613
6614          --  The first two arguments are by convention intended to refer to an
6615          --  external tool and a tool-specific function. These arguments are
6616          --  not analyzed.
6617
6618          when Pragma_Annotate => Annotate : declare
6619             Arg : Node_Id;
6620             Exp : Node_Id;
6621
6622          begin
6623             GNAT_Pragma;
6624             Check_At_Least_N_Arguments (1);
6625             Check_Arg_Is_Identifier (Arg1);
6626             Check_No_Identifiers;
6627             Store_Note (N);
6628
6629             --  Second parameter is optional, it is never analyzed
6630
6631             if No (Arg2) then
6632                null;
6633
6634             --  Here if we have a second parameter
6635
6636             else
6637                --  Second parameter must be identifier
6638
6639                Check_Arg_Is_Identifier (Arg2);
6640
6641                --  Process remaining parameters if any
6642
6643                Arg := Next (Arg2);
6644                while Present (Arg) loop
6645                   Exp := Get_Pragma_Arg (Arg);
6646                   Analyze (Exp);
6647
6648                   if Is_Entity_Name (Exp) then
6649                      null;
6650
6651                   --  For string literals, we assume Standard_String as the
6652                   --  type, unless the string contains wide or wide_wide
6653                   --  characters.
6654
6655                   elsif Nkind (Exp) = N_String_Literal then
6656                      if Has_Wide_Wide_Character (Exp) then
6657                         Resolve (Exp, Standard_Wide_Wide_String);
6658                      elsif Has_Wide_Character (Exp) then
6659                         Resolve (Exp, Standard_Wide_String);
6660                      else
6661                         Resolve (Exp, Standard_String);
6662                      end if;
6663
6664                   elsif Is_Overloaded (Exp) then
6665                         Error_Pragma_Arg
6666                           ("ambiguous argument for pragma%", Exp);
6667
6668                   else
6669                      Resolve (Exp);
6670                   end if;
6671
6672                   Next (Arg);
6673                end loop;
6674             end if;
6675          end Annotate;
6676
6677          ------------
6678          -- Assert --
6679          ------------
6680
6681          --  pragma Assert ([Check =>] Boolean_EXPRESSION
6682          --                 [, [Message =>] Static_String_EXPRESSION]);
6683
6684          when Pragma_Assert => Assert : declare
6685             Expr : Node_Id;
6686             Newa : List_Id;
6687
6688          begin
6689             Ada_2005_Pragma;
6690             Check_At_Least_N_Arguments (1);
6691             Check_At_Most_N_Arguments (2);
6692             Check_Arg_Order ((Name_Check, Name_Message));
6693             Check_Optional_Identifier (Arg1, Name_Check);
6694
6695             --  We treat pragma Assert as equivalent to:
6696
6697             --    pragma Check (Assertion, condition [, msg]);
6698
6699             --  So rewrite pragma in this manner, and analyze the result
6700
6701             Expr := Get_Pragma_Arg (Arg1);
6702             Newa := New_List (
6703               Make_Pragma_Argument_Association (Loc,
6704                 Expression => Make_Identifier (Loc, Name_Assertion)),
6705
6706               Make_Pragma_Argument_Association (Sloc (Expr),
6707                 Expression => Expr));
6708
6709             if Arg_Count > 1 then
6710                Check_Optional_Identifier (Arg2, Name_Message);
6711                Analyze_And_Resolve (Get_Pragma_Arg (Arg2), Standard_String);
6712                Append_To (Newa, Relocate_Node (Arg2));
6713             end if;
6714
6715             Rewrite (N,
6716               Make_Pragma (Loc,
6717                 Chars                        => Name_Check,
6718                 Pragma_Argument_Associations => Newa));
6719             Analyze (N);
6720          end Assert;
6721
6722          ----------------------
6723          -- Assertion_Policy --
6724          ----------------------
6725
6726          --  pragma Assertion_Policy (Check | Disable |Ignore)
6727
6728          when Pragma_Assertion_Policy => Assertion_Policy : declare
6729             Policy : Node_Id;
6730
6731          begin
6732             Ada_2005_Pragma;
6733             Check_Valid_Configuration_Pragma;
6734             Check_Arg_Count (1);
6735             Check_No_Identifiers;
6736             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Disable, Name_Ignore);
6737
6738             --  We treat pragma Assertion_Policy as equivalent to:
6739
6740             --    pragma Check_Policy (Assertion, policy)
6741
6742             --  So rewrite the pragma in that manner and link on to the chain
6743             --  of Check_Policy pragmas, marking the pragma as analyzed.
6744
6745             Policy := Get_Pragma_Arg (Arg1);
6746
6747             Rewrite (N,
6748               Make_Pragma (Loc,
6749                 Chars => Name_Check_Policy,
6750
6751                 Pragma_Argument_Associations => New_List (
6752                   Make_Pragma_Argument_Association (Loc,
6753                     Expression => Make_Identifier (Loc, Name_Assertion)),
6754
6755                   Make_Pragma_Argument_Association (Loc,
6756                     Expression =>
6757                       Make_Identifier (Sloc (Policy), Chars (Policy))))));
6758
6759             Set_Analyzed (N);
6760             Set_Next_Pragma (N, Opt.Check_Policy_List);
6761             Opt.Check_Policy_List := N;
6762          end Assertion_Policy;
6763
6764          ------------------------------
6765          -- Assume_No_Invalid_Values --
6766          ------------------------------
6767
6768          --  pragma Assume_No_Invalid_Values (On | Off);
6769
6770          when Pragma_Assume_No_Invalid_Values =>
6771             GNAT_Pragma;
6772             Check_Valid_Configuration_Pragma;
6773             Check_Arg_Count (1);
6774             Check_No_Identifiers;
6775             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
6776
6777             if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
6778                Assume_No_Invalid_Values := True;
6779             else
6780                Assume_No_Invalid_Values := False;
6781             end if;
6782
6783          ---------------
6784          -- AST_Entry --
6785          ---------------
6786
6787          --  pragma AST_Entry (entry_IDENTIFIER);
6788
6789          when Pragma_AST_Entry => AST_Entry : declare
6790             Ent : Node_Id;
6791
6792          begin
6793             GNAT_Pragma;
6794             Check_VMS (N);
6795             Check_Arg_Count (1);
6796             Check_No_Identifiers;
6797             Check_Arg_Is_Local_Name (Arg1);
6798             Ent := Entity (Get_Pragma_Arg (Arg1));
6799
6800             --  Note: the implementation of the AST_Entry pragma could handle
6801             --  the entry family case fine, but for now we are consistent with
6802             --  the DEC rules, and do not allow the pragma, which of course
6803             --  has the effect of also forbidding the attribute.
6804
6805             if Ekind (Ent) /= E_Entry then
6806                Error_Pragma_Arg
6807                  ("pragma% argument must be simple entry name", Arg1);
6808
6809             elsif Is_AST_Entry (Ent) then
6810                Error_Pragma_Arg
6811                  ("duplicate % pragma for entry", Arg1);
6812
6813             elsif Has_Homonym (Ent) then
6814                Error_Pragma_Arg
6815                  ("pragma% argument cannot specify overloaded entry", Arg1);
6816
6817             else
6818                declare
6819                   FF : constant Entity_Id := First_Formal (Ent);
6820
6821                begin
6822                   if Present (FF) then
6823                      if Present (Next_Formal (FF)) then
6824                         Error_Pragma_Arg
6825                           ("entry for pragma% can have only one argument",
6826                            Arg1);
6827
6828                      elsif Parameter_Mode (FF) /= E_In_Parameter then
6829                         Error_Pragma_Arg
6830                           ("entry parameter for pragma% must have mode IN",
6831                            Arg1);
6832                      end if;
6833                   end if;
6834                end;
6835
6836                Set_Is_AST_Entry (Ent);
6837             end if;
6838          end AST_Entry;
6839
6840          ------------------
6841          -- Asynchronous --
6842          ------------------
6843
6844          --  pragma Asynchronous (LOCAL_NAME);
6845
6846          when Pragma_Asynchronous => Asynchronous : declare
6847             Nm     : Entity_Id;
6848             C_Ent  : Entity_Id;
6849             L      : List_Id;
6850             S      : Node_Id;
6851             N      : Node_Id;
6852             Formal : Entity_Id;
6853
6854             procedure Process_Async_Pragma;
6855             --  Common processing for procedure and access-to-procedure case
6856
6857             --------------------------
6858             -- Process_Async_Pragma --
6859             --------------------------
6860
6861             procedure Process_Async_Pragma is
6862             begin
6863                if No (L) then
6864                   Set_Is_Asynchronous (Nm);
6865                   return;
6866                end if;
6867
6868                --  The formals should be of mode IN (RM E.4.1(6))
6869
6870                S := First (L);
6871                while Present (S) loop
6872                   Formal := Defining_Identifier (S);
6873
6874                   if Nkind (Formal) = N_Defining_Identifier
6875                     and then Ekind (Formal) /= E_In_Parameter
6876                   then
6877                      Error_Pragma_Arg
6878                        ("pragma% procedure can only have IN parameter",
6879                         Arg1);
6880                   end if;
6881
6882                   Next (S);
6883                end loop;
6884
6885                Set_Is_Asynchronous (Nm);
6886             end Process_Async_Pragma;
6887
6888          --  Start of processing for pragma Asynchronous
6889
6890          begin
6891             Check_Ada_83_Warning;
6892             Check_No_Identifiers;
6893             Check_Arg_Count (1);
6894             Check_Arg_Is_Local_Name (Arg1);
6895
6896             if Debug_Flag_U then
6897                return;
6898             end if;
6899
6900             C_Ent := Cunit_Entity (Current_Sem_Unit);
6901             Analyze (Get_Pragma_Arg (Arg1));
6902             Nm := Entity (Get_Pragma_Arg (Arg1));
6903
6904             if not Is_Remote_Call_Interface (C_Ent)
6905               and then not Is_Remote_Types (C_Ent)
6906             then
6907                --  This pragma should only appear in an RCI or Remote Types
6908                --  unit (RM E.4.1(4)).
6909
6910                Error_Pragma
6911                  ("pragma% not in Remote_Call_Interface or " &
6912                   "Remote_Types unit");
6913             end if;
6914
6915             if Ekind (Nm) = E_Procedure
6916               and then Nkind (Parent (Nm)) = N_Procedure_Specification
6917             then
6918                if not Is_Remote_Call_Interface (Nm) then
6919                   Error_Pragma_Arg
6920                     ("pragma% cannot be applied on non-remote procedure",
6921                      Arg1);
6922                end if;
6923
6924                L := Parameter_Specifications (Parent (Nm));
6925                Process_Async_Pragma;
6926                return;
6927
6928             elsif Ekind (Nm) = E_Function then
6929                Error_Pragma_Arg
6930                  ("pragma% cannot be applied to function", Arg1);
6931
6932             elsif Is_Remote_Access_To_Subprogram_Type (Nm) then
6933                   if Is_Record_Type (Nm) then
6934
6935                   --  A record type that is the Equivalent_Type for a remote
6936                   --  access-to-subprogram type.
6937
6938                      N := Declaration_Node (Corresponding_Remote_Type (Nm));
6939
6940                   else
6941                      --  A non-expanded RAS type (distribution is not enabled)
6942
6943                      N := Declaration_Node (Nm);
6944                   end if;
6945
6946                if Nkind (N) = N_Full_Type_Declaration
6947                  and then Nkind (Type_Definition (N)) =
6948                                      N_Access_Procedure_Definition
6949                then
6950                   L := Parameter_Specifications (Type_Definition (N));
6951                   Process_Async_Pragma;
6952
6953                   if Is_Asynchronous (Nm)
6954                     and then Expander_Active
6955                     and then Get_PCS_Name /= Name_No_DSA
6956                   then
6957                      RACW_Type_Is_Asynchronous (Underlying_RACW_Type (Nm));
6958                   end if;
6959
6960                else
6961                   Error_Pragma_Arg
6962                     ("pragma% cannot reference access-to-function type",
6963                     Arg1);
6964                end if;
6965
6966             --  Only other possibility is Access-to-class-wide type
6967
6968             elsif Is_Access_Type (Nm)
6969               and then Is_Class_Wide_Type (Designated_Type (Nm))
6970             then
6971                Check_First_Subtype (Arg1);
6972                Set_Is_Asynchronous (Nm);
6973                if Expander_Active then
6974                   RACW_Type_Is_Asynchronous (Nm);
6975                end if;
6976
6977             else
6978                Error_Pragma_Arg ("inappropriate argument for pragma%", Arg1);
6979             end if;
6980          end Asynchronous;
6981
6982          ------------
6983          -- Atomic --
6984          ------------
6985
6986          --  pragma Atomic (LOCAL_NAME);
6987
6988          when Pragma_Atomic =>
6989             Process_Atomic_Shared_Volatile;
6990
6991          -----------------------
6992          -- Atomic_Components --
6993          -----------------------
6994
6995          --  pragma Atomic_Components (array_LOCAL_NAME);
6996
6997          --  This processing is shared by Volatile_Components
6998
6999          when Pragma_Atomic_Components   |
7000               Pragma_Volatile_Components =>
7001
7002          Atomic_Components : declare
7003             E_Id : Node_Id;
7004             E    : Entity_Id;
7005             D    : Node_Id;
7006             K    : Node_Kind;
7007
7008          begin
7009             Check_Ada_83_Warning;
7010             Check_No_Identifiers;
7011             Check_Arg_Count (1);
7012             Check_Arg_Is_Local_Name (Arg1);
7013             E_Id := Get_Pragma_Arg (Arg1);
7014
7015             if Etype (E_Id) = Any_Type then
7016                return;
7017             end if;
7018
7019             E := Entity (E_Id);
7020
7021             Check_Duplicate_Pragma (E);
7022
7023             if Rep_Item_Too_Early (E, N)
7024                  or else
7025                Rep_Item_Too_Late (E, N)
7026             then
7027                return;
7028             end if;
7029
7030             D := Declaration_Node (E);
7031             K := Nkind (D);
7032
7033             if (K = N_Full_Type_Declaration and then Is_Array_Type (E))
7034               or else
7035                 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
7036                    and then Nkind (D) = N_Object_Declaration
7037                    and then Nkind (Object_Definition (D)) =
7038                                        N_Constrained_Array_Definition)
7039             then
7040                --  The flag is set on the object, or on the base type
7041
7042                if Nkind (D) /= N_Object_Declaration then
7043                   E := Base_Type (E);
7044                end if;
7045
7046                Set_Has_Volatile_Components (E);
7047
7048                if Prag_Id = Pragma_Atomic_Components then
7049                   Set_Has_Atomic_Components (E);
7050                end if;
7051
7052             else
7053                Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
7054             end if;
7055          end Atomic_Components;
7056          --------------------
7057          -- Attach_Handler --
7058          --------------------
7059
7060          --  pragma Attach_Handler (handler_NAME, EXPRESSION);
7061
7062          when Pragma_Attach_Handler =>
7063             Check_Ada_83_Warning;
7064             Check_No_Identifiers;
7065             Check_Arg_Count (2);
7066
7067             if No_Run_Time_Mode then
7068                Error_Msg_CRT ("Attach_Handler pragma", N);
7069             else
7070                Check_Interrupt_Or_Attach_Handler;
7071
7072                --  The expression that designates the attribute may depend on a
7073                --  discriminant, and is therefore a per- object expression, to
7074                --  be expanded in the init proc. If expansion is enabled, then
7075                --  perform semantic checks on a copy only.
7076
7077                if Expander_Active then
7078                   declare
7079                      Temp : constant Node_Id :=
7080                               New_Copy_Tree (Get_Pragma_Arg (Arg2));
7081                   begin
7082                      Set_Parent (Temp, N);
7083                      Preanalyze_And_Resolve (Temp, RTE (RE_Interrupt_ID));
7084                   end;
7085
7086                else
7087                   Analyze (Get_Pragma_Arg (Arg2));
7088                   Resolve (Get_Pragma_Arg (Arg2), RTE (RE_Interrupt_ID));
7089                end if;
7090
7091                Process_Interrupt_Or_Attach_Handler;
7092             end if;
7093
7094          --------------------
7095          -- C_Pass_By_Copy --
7096          --------------------
7097
7098          --  pragma C_Pass_By_Copy ([Max_Size =>] static_integer_EXPRESSION);
7099
7100          when Pragma_C_Pass_By_Copy => C_Pass_By_Copy : declare
7101             Arg : Node_Id;
7102             Val : Uint;
7103
7104          begin
7105             GNAT_Pragma;
7106             Check_Valid_Configuration_Pragma;
7107             Check_Arg_Count (1);
7108             Check_Optional_Identifier (Arg1, "max_size");
7109
7110             Arg := Get_Pragma_Arg (Arg1);
7111             Check_Arg_Is_Static_Expression (Arg, Any_Integer);
7112
7113             Val := Expr_Value (Arg);
7114
7115             if Val <= 0 then
7116                Error_Pragma_Arg
7117                  ("maximum size for pragma% must be positive", Arg1);
7118
7119             elsif UI_Is_In_Int_Range (Val) then
7120                Default_C_Record_Mechanism := UI_To_Int (Val);
7121
7122             --  If a giant value is given, Int'Last will do well enough.
7123             --  If sometime someone complains that a record larger than
7124             --  two gigabytes is not copied, we will worry about it then!
7125
7126             else
7127                Default_C_Record_Mechanism := Mechanism_Type'Last;
7128             end if;
7129          end C_Pass_By_Copy;
7130
7131          -----------
7132          -- Check --
7133          -----------
7134
7135          --  pragma Check ([Name    =>] IDENTIFIER,
7136          --                [Check   =>] Boolean_EXPRESSION
7137          --              [,[Message =>] String_EXPRESSION]);
7138
7139          when Pragma_Check => Check : declare
7140             Expr : Node_Id;
7141             Eloc : Source_Ptr;
7142
7143             Check_On : Boolean;
7144             --  Set True if category of assertions referenced by Name enabled
7145
7146          begin
7147             GNAT_Pragma;
7148             Check_At_Least_N_Arguments (2);
7149             Check_At_Most_N_Arguments (3);
7150             Check_Optional_Identifier (Arg1, Name_Name);
7151             Check_Optional_Identifier (Arg2, Name_Check);
7152
7153             if Arg_Count = 3 then
7154                Check_Optional_Identifier (Arg3, Name_Message);
7155                Analyze_And_Resolve (Get_Pragma_Arg (Arg3), Standard_String);
7156             end if;
7157
7158             Check_Arg_Is_Identifier (Arg1);
7159
7160             --  Completely ignore if disabled
7161
7162             if Check_Disabled (Chars (Get_Pragma_Arg (Arg1))) then
7163                Rewrite (N, Make_Null_Statement (Loc));
7164                Analyze (N);
7165                return;
7166             end if;
7167
7168             --  Indicate if pragma is enabled. The Original_Node reference here
7169             --  is to deal with pragma Assert rewritten as a Check pragma.
7170
7171             Check_On := Check_Enabled (Chars (Get_Pragma_Arg (Arg1)));
7172
7173             if Check_On then
7174                Set_SCO_Pragma_Enabled (Loc);
7175             end if;
7176
7177             --  If expansion is active and the check is not enabled then we
7178             --  rewrite the Check as:
7179
7180             --    if False and then condition then
7181             --       null;
7182             --    end if;
7183
7184             --  The reason we do this rewriting during semantic analysis rather
7185             --  than as part of normal expansion is that we cannot analyze and
7186             --  expand the code for the boolean expression directly, or it may
7187             --  cause insertion of actions that would escape the attempt to
7188             --  suppress the check code.
7189
7190             --  Note that the Sloc for the if statement corresponds to the
7191             --  argument condition, not the pragma itself. The reason for this
7192             --  is that we may generate a warning if the condition is False at
7193             --  compile time, and we do not want to delete this warning when we
7194             --  delete the if statement.
7195
7196             Expr := Get_Pragma_Arg (Arg2);
7197
7198             if Expander_Active and then not Check_On then
7199                Eloc := Sloc (Expr);
7200
7201                Rewrite (N,
7202                  Make_If_Statement (Eloc,
7203                    Condition =>
7204                      Make_And_Then (Eloc,
7205                        Left_Opnd  => New_Occurrence_Of (Standard_False, Eloc),
7206                        Right_Opnd => Expr),
7207                    Then_Statements => New_List (
7208                      Make_Null_Statement (Eloc))));
7209
7210                Analyze (N);
7211
7212             --  Check is active
7213
7214             else
7215                Analyze_And_Resolve (Expr, Any_Boolean);
7216             end if;
7217          end Check;
7218
7219          ----------------
7220          -- Check_Name --
7221          ----------------
7222
7223          --  pragma Check_Name (check_IDENTIFIER);
7224
7225          when Pragma_Check_Name =>
7226             Check_No_Identifiers;
7227             GNAT_Pragma;
7228             Check_Valid_Configuration_Pragma;
7229             Check_Arg_Count (1);
7230             Check_Arg_Is_Identifier (Arg1);
7231
7232             declare
7233                Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
7234
7235             begin
7236                for J in Check_Names.First .. Check_Names.Last loop
7237                   if Check_Names.Table (J) = Nam then
7238                      return;
7239                   end if;
7240                end loop;
7241
7242                Check_Names.Append (Nam);
7243             end;
7244
7245          ------------------
7246          -- Check_Policy --
7247          ------------------
7248
7249          --  pragma Check_Policy (
7250          --    [Name   =>] IDENTIFIER,
7251          --    [Policy =>] POLICY_IDENTIFIER);
7252
7253          --  POLICY_IDENTIFIER ::= ON | OFF | CHECK | DISABLE | IGNORE
7254
7255          --  Note: this is a configuration pragma, but it is allowed to appear
7256          --  anywhere else.
7257
7258          when Pragma_Check_Policy =>
7259             GNAT_Pragma;
7260             Check_Arg_Count (2);
7261             Check_Optional_Identifier (Arg1, Name_Name);
7262             Check_Optional_Identifier (Arg2, Name_Policy);
7263             Check_Arg_Is_One_Of
7264               (Arg2, Name_On, Name_Off, Name_Check, Name_Disable, Name_Ignore);
7265
7266             --  A Check_Policy pragma can appear either as a configuration
7267             --  pragma, or in a declarative part or a package spec (see RM
7268             --  11.5(5) for rules for Suppress/Unsuppress which are also
7269             --  followed for Check_Policy).
7270
7271             if not Is_Configuration_Pragma then
7272                Check_Is_In_Decl_Part_Or_Package_Spec;
7273             end if;
7274
7275             Set_Next_Pragma (N, Opt.Check_Policy_List);
7276             Opt.Check_Policy_List := N;
7277
7278          ---------------------
7279          -- CIL_Constructor --
7280          ---------------------
7281
7282          --  pragma CIL_Constructor ([Entity =>] LOCAL_NAME);
7283
7284          --  Processing for this pragma is shared with Java_Constructor
7285
7286          -------------
7287          -- Comment --
7288          -------------
7289
7290          --  pragma Comment (static_string_EXPRESSION)
7291
7292          --  Processing for pragma Comment shares the circuitry for pragma
7293          --  Ident. The only differences are that Ident enforces a limit of 31
7294          --  characters on its argument, and also enforces limitations on
7295          --  placement for DEC compatibility. Pragma Comment shares neither of
7296          --  these restrictions.
7297
7298          -------------------
7299          -- Common_Object --
7300          -------------------
7301
7302          --  pragma Common_Object (
7303          --        [Internal =>] LOCAL_NAME
7304          --     [, [External =>] EXTERNAL_SYMBOL]
7305          --     [, [Size     =>] EXTERNAL_SYMBOL]);
7306
7307          --  Processing for this pragma is shared with Psect_Object
7308
7309          ------------------------
7310          -- Compile_Time_Error --
7311          ------------------------
7312
7313          --  pragma Compile_Time_Error
7314          --    (boolean_EXPRESSION, static_string_EXPRESSION);
7315
7316          when Pragma_Compile_Time_Error =>
7317             GNAT_Pragma;
7318             Process_Compile_Time_Warning_Or_Error;
7319
7320          --------------------------
7321          -- Compile_Time_Warning --
7322          --------------------------
7323
7324          --  pragma Compile_Time_Warning
7325          --    (boolean_EXPRESSION, static_string_EXPRESSION);
7326
7327          when Pragma_Compile_Time_Warning =>
7328             GNAT_Pragma;
7329             Process_Compile_Time_Warning_Or_Error;
7330
7331          -------------------
7332          -- Compiler_Unit --
7333          -------------------
7334
7335          when Pragma_Compiler_Unit =>
7336             GNAT_Pragma;
7337             Check_Arg_Count (0);
7338             Set_Is_Compiler_Unit (Get_Source_Unit (N));
7339
7340          -----------------------------
7341          -- Complete_Representation --
7342          -----------------------------
7343
7344          --  pragma Complete_Representation;
7345
7346          when Pragma_Complete_Representation =>
7347             GNAT_Pragma;
7348             Check_Arg_Count (0);
7349
7350             if Nkind (Parent (N)) /= N_Record_Representation_Clause then
7351                Error_Pragma
7352                  ("pragma & must appear within record representation clause");
7353             end if;
7354
7355          ----------------------------
7356          -- Complex_Representation --
7357          ----------------------------
7358
7359          --  pragma Complex_Representation ([Entity =>] LOCAL_NAME);
7360
7361          when Pragma_Complex_Representation => Complex_Representation : declare
7362             E_Id : Entity_Id;
7363             E    : Entity_Id;
7364             Ent  : Entity_Id;
7365
7366          begin
7367             GNAT_Pragma;
7368             Check_Arg_Count (1);
7369             Check_Optional_Identifier (Arg1, Name_Entity);
7370             Check_Arg_Is_Local_Name (Arg1);
7371             E_Id := Get_Pragma_Arg (Arg1);
7372
7373             if Etype (E_Id) = Any_Type then
7374                return;
7375             end if;
7376
7377             E := Entity (E_Id);
7378
7379             if not Is_Record_Type (E) then
7380                Error_Pragma_Arg
7381                  ("argument for pragma% must be record type", Arg1);
7382             end if;
7383
7384             Ent := First_Entity (E);
7385
7386             if No (Ent)
7387               or else No (Next_Entity (Ent))
7388               or else Present (Next_Entity (Next_Entity (Ent)))
7389               or else not Is_Floating_Point_Type (Etype (Ent))
7390               or else Etype (Ent) /= Etype (Next_Entity (Ent))
7391             then
7392                Error_Pragma_Arg
7393                  ("record for pragma% must have two fields of the same "
7394                   & "floating-point type", Arg1);
7395
7396             else
7397                Set_Has_Complex_Representation (Base_Type (E));
7398
7399                --  We need to treat the type has having a non-standard
7400                --  representation, for back-end purposes, even though in
7401                --  general a complex will have the default representation
7402                --  of a record with two real components.
7403
7404                Set_Has_Non_Standard_Rep (Base_Type (E));
7405             end if;
7406          end Complex_Representation;
7407
7408          -------------------------
7409          -- Component_Alignment --
7410          -------------------------
7411
7412          --  pragma Component_Alignment (
7413          --        [Form =>] ALIGNMENT_CHOICE
7414          --     [, [Name =>] type_LOCAL_NAME]);
7415          --
7416          --   ALIGNMENT_CHOICE ::=
7417          --     Component_Size
7418          --   | Component_Size_4
7419          --   | Storage_Unit
7420          --   | Default
7421
7422          when Pragma_Component_Alignment => Component_AlignmentP : declare
7423             Args  : Args_List (1 .. 2);
7424             Names : constant Name_List (1 .. 2) := (
7425                       Name_Form,
7426                       Name_Name);
7427
7428             Form  : Node_Id renames Args (1);
7429             Name  : Node_Id renames Args (2);
7430
7431             Atype : Component_Alignment_Kind;
7432             Typ   : Entity_Id;
7433
7434          begin
7435             GNAT_Pragma;
7436             Gather_Associations (Names, Args);
7437
7438             if No (Form) then
7439                Error_Pragma ("missing Form argument for pragma%");
7440             end if;
7441
7442             Check_Arg_Is_Identifier (Form);
7443
7444             --  Get proper alignment, note that Default = Component_Size on all
7445             --  machines we have so far, and we want to set this value rather
7446             --  than the default value to indicate that it has been explicitly
7447             --  set (and thus will not get overridden by the default component
7448             --  alignment for the current scope)
7449
7450             if Chars (Form) = Name_Component_Size then
7451                Atype := Calign_Component_Size;
7452
7453             elsif Chars (Form) = Name_Component_Size_4 then
7454                Atype := Calign_Component_Size_4;
7455
7456             elsif Chars (Form) = Name_Default then
7457                Atype := Calign_Component_Size;
7458
7459             elsif Chars (Form) = Name_Storage_Unit then
7460                Atype := Calign_Storage_Unit;
7461
7462             else
7463                Error_Pragma_Arg
7464                  ("invalid Form parameter for pragma%", Form);
7465             end if;
7466
7467             --  Case with no name, supplied, affects scope table entry
7468
7469             if No (Name) then
7470                Scope_Stack.Table
7471                  (Scope_Stack.Last).Component_Alignment_Default := Atype;
7472
7473             --  Case of name supplied
7474
7475             else
7476                Check_Arg_Is_Local_Name (Name);
7477                Find_Type (Name);
7478                Typ := Entity (Name);
7479
7480                if Typ = Any_Type
7481                  or else Rep_Item_Too_Early (Typ, N)
7482                then
7483                   return;
7484                else
7485                   Typ := Underlying_Type (Typ);
7486                end if;
7487
7488                if not Is_Record_Type (Typ)
7489                  and then not Is_Array_Type (Typ)
7490                then
7491                   Error_Pragma_Arg
7492                     ("Name parameter of pragma% must identify record or " &
7493                      "array type", Name);
7494                end if;
7495
7496                --  An explicit Component_Alignment pragma overrides an
7497                --  implicit pragma Pack, but not an explicit one.
7498
7499                if not Has_Pragma_Pack (Base_Type (Typ)) then
7500                   Set_Is_Packed (Base_Type (Typ), False);
7501                   Set_Component_Alignment (Base_Type (Typ), Atype);
7502                end if;
7503             end if;
7504          end Component_AlignmentP;
7505
7506          ----------------
7507          -- Controlled --
7508          ----------------
7509
7510          --  pragma Controlled (first_subtype_LOCAL_NAME);
7511
7512          when Pragma_Controlled => Controlled : declare
7513             Arg : Node_Id;
7514
7515          begin
7516             Check_No_Identifiers;
7517             Check_Arg_Count (1);
7518             Check_Arg_Is_Local_Name (Arg1);
7519             Arg := Get_Pragma_Arg (Arg1);
7520
7521             if not Is_Entity_Name (Arg)
7522               or else not Is_Access_Type (Entity (Arg))
7523             then
7524                Error_Pragma_Arg ("pragma% requires access type", Arg1);
7525             else
7526                Set_Has_Pragma_Controlled (Base_Type (Entity (Arg)));
7527             end if;
7528          end Controlled;
7529
7530          ----------------
7531          -- Convention --
7532          ----------------
7533
7534          --  pragma Convention ([Convention =>] convention_IDENTIFIER,
7535          --    [Entity =>] LOCAL_NAME);
7536
7537          when Pragma_Convention => Convention : declare
7538             C : Convention_Id;
7539             E : Entity_Id;
7540             pragma Warnings (Off, C);
7541             pragma Warnings (Off, E);
7542          begin
7543             Check_Arg_Order ((Name_Convention, Name_Entity));
7544             Check_Ada_83_Warning;
7545             Check_Arg_Count (2);
7546             Process_Convention (C, E);
7547          end Convention;
7548
7549          ---------------------------
7550          -- Convention_Identifier --
7551          ---------------------------
7552
7553          --  pragma Convention_Identifier ([Name =>] IDENTIFIER,
7554          --    [Convention =>] convention_IDENTIFIER);
7555
7556          when Pragma_Convention_Identifier => Convention_Identifier : declare
7557             Idnam : Name_Id;
7558             Cname : Name_Id;
7559
7560          begin
7561             GNAT_Pragma;
7562             Check_Arg_Order ((Name_Name, Name_Convention));
7563             Check_Arg_Count (2);
7564             Check_Optional_Identifier (Arg1, Name_Name);
7565             Check_Optional_Identifier (Arg2, Name_Convention);
7566             Check_Arg_Is_Identifier (Arg1);
7567             Check_Arg_Is_Identifier (Arg2);
7568             Idnam := Chars (Get_Pragma_Arg (Arg1));
7569             Cname := Chars (Get_Pragma_Arg (Arg2));
7570
7571             if Is_Convention_Name (Cname) then
7572                Record_Convention_Identifier
7573                  (Idnam, Get_Convention_Id (Cname));
7574             else
7575                Error_Pragma_Arg
7576                  ("second arg for % pragma must be convention", Arg2);
7577             end if;
7578          end Convention_Identifier;
7579
7580          ---------------
7581          -- CPP_Class --
7582          ---------------
7583
7584          --  pragma CPP_Class ([Entity =>] local_NAME)
7585
7586          when Pragma_CPP_Class => CPP_Class : declare
7587             Arg : Node_Id;
7588             Typ : Entity_Id;
7589
7590          begin
7591             if Warn_On_Obsolescent_Feature then
7592                Error_Msg_N
7593                  ("'G'N'A'T pragma cpp'_class is now obsolete; replace it" &
7594                   " by pragma import?", N);
7595             end if;
7596
7597             GNAT_Pragma;
7598             Check_Arg_Count (1);
7599             Check_Optional_Identifier (Arg1, Name_Entity);
7600             Check_Arg_Is_Local_Name (Arg1);
7601
7602             Arg := Get_Pragma_Arg (Arg1);
7603             Analyze (Arg);
7604
7605             if Etype (Arg) = Any_Type then
7606                return;
7607             end if;
7608
7609             if not Is_Entity_Name (Arg)
7610               or else not Is_Type (Entity (Arg))
7611             then
7612                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
7613             end if;
7614
7615             Typ := Entity (Arg);
7616
7617             if not Is_Tagged_Type (Typ) then
7618                Error_Pragma_Arg ("pragma% applicable to tagged types ", Arg1);
7619             end if;
7620
7621             --  Types treated as CPP classes must be declared limited (note:
7622             --  this used to be a warning but there is no real benefit to it
7623             --  since we did effectively intend to treat the type as limited
7624             --  anyway).
7625
7626             if not Is_Limited_Type (Typ) then
7627                Error_Msg_N
7628                  ("imported 'C'P'P type must be limited",
7629                   Get_Pragma_Arg (Arg1));
7630             end if;
7631
7632             Set_Is_CPP_Class      (Typ);
7633             Set_Convention        (Typ, Convention_CPP);
7634
7635             --  Imported CPP types must not have discriminants (because C++
7636             --  classes do not have discriminants).
7637
7638             if Has_Discriminants (Typ) then
7639                Error_Msg_N
7640                  ("imported 'C'P'P type cannot have discriminants",
7641                   First (Discriminant_Specifications
7642                           (Declaration_Node (Typ))));
7643             end if;
7644
7645             --  Components of imported CPP types must not have default
7646             --  expressions because the constructor (if any) is in the
7647             --  C++ side.
7648
7649             if Is_Incomplete_Or_Private_Type (Typ)
7650               and then No (Underlying_Type (Typ))
7651             then
7652                --  It should be an error to apply pragma CPP to a private
7653                --  type if the underlying type is not visible (as it is
7654                --  for any representation item). For now, for backward
7655                --  compatibility we do nothing but we cannot check components
7656                --  because they are not available at this stage. All this code
7657                --  will be removed when we cleanup this obsolete GNAT pragma???
7658
7659                null;
7660
7661             else
7662                declare
7663                   Tdef  : constant Node_Id :=
7664                             Type_Definition (Declaration_Node (Typ));
7665                   Clist : Node_Id;
7666                   Comp  : Node_Id;
7667
7668                begin
7669                   if Nkind (Tdef) = N_Record_Definition then
7670                      Clist := Component_List (Tdef);
7671                   else
7672                      pragma Assert (Nkind (Tdef) = N_Derived_Type_Definition);
7673                      Clist := Component_List (Record_Extension_Part (Tdef));
7674                   end if;
7675
7676                   if Present (Clist) then
7677                      Comp := First (Component_Items (Clist));
7678                      while Present (Comp) loop
7679                         if Present (Expression (Comp)) then
7680                            Error_Msg_N
7681                              ("component of imported 'C'P'P type cannot have" &
7682                               " default expression", Expression (Comp));
7683                         end if;
7684
7685                         Next (Comp);
7686                      end loop;
7687                   end if;
7688                end;
7689             end if;
7690          end CPP_Class;
7691
7692          ---------------------
7693          -- CPP_Constructor --
7694          ---------------------
7695
7696          --  pragma CPP_Constructor ([Entity =>] LOCAL_NAME
7697          --    [, [External_Name =>] static_string_EXPRESSION ]
7698          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
7699
7700          when Pragma_CPP_Constructor => CPP_Constructor : declare
7701             Elmt    : Elmt_Id;
7702             Id      : Entity_Id;
7703             Def_Id  : Entity_Id;
7704             Tag_Typ : Entity_Id;
7705
7706          begin
7707             GNAT_Pragma;
7708             Check_At_Least_N_Arguments (1);
7709             Check_At_Most_N_Arguments (3);
7710             Check_Optional_Identifier (Arg1, Name_Entity);
7711             Check_Arg_Is_Local_Name (Arg1);
7712
7713             Id := Get_Pragma_Arg (Arg1);
7714             Find_Program_Unit_Name (Id);
7715
7716             --  If we did not find the name, we are done
7717
7718             if Etype (Id) = Any_Type then
7719                return;
7720             end if;
7721
7722             Def_Id := Entity (Id);
7723
7724             --  Check if already defined as constructor
7725
7726             if Is_Constructor (Def_Id) then
7727                Error_Msg_N
7728                  ("?duplicate argument for pragma 'C'P'P_Constructor", Arg1);
7729                return;
7730             end if;
7731
7732             if Ekind (Def_Id) = E_Function
7733               and then (Is_CPP_Class (Etype (Def_Id))
7734                          or else (Is_Class_Wide_Type (Etype (Def_Id))
7735                                    and then
7736                                   Is_CPP_Class (Root_Type (Etype (Def_Id)))))
7737             then
7738                if Arg_Count >= 2 then
7739                   Set_Imported (Def_Id);
7740                   Set_Is_Public (Def_Id);
7741                   Process_Interface_Name (Def_Id, Arg2, Arg3);
7742                end if;
7743
7744                Set_Has_Completion (Def_Id);
7745                Set_Is_Constructor (Def_Id);
7746
7747                --  Imported C++ constructors are not dispatching primitives
7748                --  because in C++ they don't have a dispatch table slot.
7749                --  However, in Ada the constructor has the profile of a
7750                --  function that returns a tagged type and therefore it has
7751                --  been treated as a primitive operation during semantic
7752                --  analysis. We now remove it from the list of primitive
7753                --  operations of the type.
7754
7755                if Is_Tagged_Type (Etype (Def_Id))
7756                  and then not Is_Class_Wide_Type (Etype (Def_Id))
7757                then
7758                   pragma Assert (Is_Dispatching_Operation (Def_Id));
7759                   Tag_Typ := Etype (Def_Id);
7760
7761                   Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
7762                   while Present (Elmt) and then Node (Elmt) /= Def_Id loop
7763                      Next_Elmt (Elmt);
7764                   end loop;
7765
7766                   Remove_Elmt (Primitive_Operations (Tag_Typ), Elmt);
7767                   Set_Is_Dispatching_Operation (Def_Id, False);
7768                end if;
7769
7770                --  For backward compatibility, if the constructor returns a
7771                --  class wide type, and we internally change the return type to
7772                --  the corresponding root type.
7773
7774                if Is_Class_Wide_Type (Etype (Def_Id)) then
7775                   Set_Etype (Def_Id, Root_Type (Etype (Def_Id)));
7776                end if;
7777             else
7778                Error_Pragma_Arg
7779                  ("pragma% requires function returning a 'C'P'P_Class type",
7780                    Arg1);
7781             end if;
7782          end CPP_Constructor;
7783
7784          -----------------
7785          -- CPP_Virtual --
7786          -----------------
7787
7788          when Pragma_CPP_Virtual => CPP_Virtual : declare
7789          begin
7790             GNAT_Pragma;
7791
7792             if Warn_On_Obsolescent_Feature then
7793                Error_Msg_N
7794                  ("'G'N'A'T pragma cpp'_virtual is now obsolete and has " &
7795                   "no effect?", N);
7796             end if;
7797          end CPP_Virtual;
7798
7799          ----------------
7800          -- CPP_Vtable --
7801          ----------------
7802
7803          when Pragma_CPP_Vtable => CPP_Vtable : declare
7804          begin
7805             GNAT_Pragma;
7806
7807             if Warn_On_Obsolescent_Feature then
7808                Error_Msg_N
7809                  ("'G'N'A'T pragma cpp'_vtable is now obsolete and has " &
7810                   "no effect?", N);
7811             end if;
7812          end CPP_Vtable;
7813
7814          ---------
7815          -- CPU --
7816          ---------
7817
7818          --  pragma CPU (EXPRESSION);
7819
7820          when Pragma_CPU => CPU : declare
7821             P   : constant Node_Id := Parent (N);
7822             Arg : Node_Id;
7823
7824          begin
7825             Ada_2012_Pragma;
7826             Check_No_Identifiers;
7827             Check_Arg_Count (1);
7828
7829             --  Subprogram case
7830
7831             if Nkind (P) = N_Subprogram_Body then
7832                Check_In_Main_Program;
7833
7834                Arg := Get_Pragma_Arg (Arg1);
7835                Analyze_And_Resolve (Arg, Any_Integer);
7836
7837                --  Must be static
7838
7839                if not Is_Static_Expression (Arg) then
7840                   Flag_Non_Static_Expr
7841                     ("main subprogram affinity is not static!", Arg);
7842                   raise Pragma_Exit;
7843
7844                --  If constraint error, then we already signalled an error
7845
7846                elsif Raises_Constraint_Error (Arg) then
7847                   null;
7848
7849                --  Otherwise check in range
7850
7851                else
7852                   declare
7853                      CPU_Id : constant Entity_Id := RTE (RE_CPU_Range);
7854                      --  This is the entity System.Multiprocessors.CPU_Range;
7855
7856                      Val : constant Uint := Expr_Value (Arg);
7857
7858                   begin
7859                      if Val < Expr_Value (Type_Low_Bound (CPU_Id))
7860                           or else
7861                         Val > Expr_Value (Type_High_Bound (CPU_Id))
7862                      then
7863                         Error_Pragma_Arg
7864                           ("main subprogram CPU is out of range", Arg1);
7865                      end if;
7866                   end;
7867                end if;
7868
7869                Set_Main_CPU
7870                     (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
7871
7872             --  Task case
7873
7874             elsif Nkind (P) = N_Task_Definition then
7875                Arg := Get_Pragma_Arg (Arg1);
7876
7877                --  The expression must be analyzed in the special manner
7878                --  described in "Handling of Default and Per-Object
7879                --  Expressions" in sem.ads.
7880
7881                Preanalyze_Spec_Expression (Arg, RTE (RE_CPU_Range));
7882
7883             --  Anything else is incorrect
7884
7885             else
7886                Pragma_Misplaced;
7887             end if;
7888
7889             if Has_Pragma_CPU (P) then
7890                Error_Pragma ("duplicate pragma% not allowed");
7891             else
7892                Set_Has_Pragma_CPU (P, True);
7893
7894                if Nkind (P) = N_Task_Definition then
7895                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
7896                end if;
7897             end if;
7898          end CPU;
7899
7900          -----------
7901          -- Debug --
7902          -----------
7903
7904          --  pragma Debug ([boolean_EXPRESSION,] PROCEDURE_CALL_STATEMENT);
7905
7906          when Pragma_Debug => Debug : declare
7907             Cond : Node_Id;
7908             Call : Node_Id;
7909
7910          begin
7911             GNAT_Pragma;
7912
7913             --  Skip analysis if disabled
7914
7915             if Debug_Pragmas_Disabled then
7916                Rewrite (N, Make_Null_Statement (Loc));
7917                Analyze (N);
7918                return;
7919             end if;
7920
7921             Cond :=
7922               New_Occurrence_Of
7923                 (Boolean_Literals (Debug_Pragmas_Enabled and Expander_Active),
7924                  Loc);
7925
7926             if Debug_Pragmas_Enabled then
7927                Set_SCO_Pragma_Enabled (Loc);
7928             end if;
7929
7930             if Arg_Count = 2 then
7931                Cond :=
7932                  Make_And_Then (Loc,
7933                    Left_Opnd  => Relocate_Node (Cond),
7934                    Right_Opnd => Get_Pragma_Arg (Arg1));
7935                Call := Get_Pragma_Arg (Arg2);
7936             else
7937                Call := Get_Pragma_Arg (Arg1);
7938             end if;
7939
7940             if Nkind_In (Call,
7941                  N_Indexed_Component,
7942                  N_Function_Call,
7943                  N_Identifier,
7944                  N_Expanded_Name,
7945                  N_Selected_Component)
7946             then
7947                --  If this pragma Debug comes from source, its argument was
7948                --  parsed as a name form (which is syntactically identical).
7949                --  In a generic context a parameterless call will be left as
7950                --  an expanded name (if global) or selected_component if local.
7951                --  Change it to a procedure call statement now.
7952
7953                Change_Name_To_Procedure_Call_Statement (Call);
7954
7955             elsif Nkind (Call) = N_Procedure_Call_Statement then
7956
7957                --  Already in the form of a procedure call statement: nothing
7958                --  to do (could happen in case of an internally generated
7959                --  pragma Debug).
7960
7961                null;
7962
7963             else
7964                --  All other cases: diagnose error
7965
7966                Error_Msg
7967                  ("argument of pragma ""Debug"" is not procedure call",
7968                   Sloc (Call));
7969                return;
7970             end if;
7971
7972             --  Rewrite into a conditional with an appropriate condition. We
7973             --  wrap the procedure call in a block so that overhead from e.g.
7974             --  use of the secondary stack does not generate execution overhead
7975             --  for suppressed conditions.
7976
7977             Rewrite (N, Make_Implicit_If_Statement (N,
7978               Condition => Cond,
7979                  Then_Statements => New_List (
7980                    Make_Block_Statement (Loc,
7981                      Handled_Statement_Sequence =>
7982                        Make_Handled_Sequence_Of_Statements (Loc,
7983                          Statements => New_List (Relocate_Node (Call)))))));
7984             Analyze (N);
7985          end Debug;
7986
7987          ------------------
7988          -- Debug_Policy --
7989          ------------------
7990
7991          --  pragma Debug_Policy (Check | Ignore)
7992
7993          when Pragma_Debug_Policy =>
7994             GNAT_Pragma;
7995             Check_Arg_Count (1);
7996             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Disable, Name_Ignore);
7997             Debug_Pragmas_Enabled :=
7998               Chars (Get_Pragma_Arg (Arg1)) = Name_Check;
7999             Debug_Pragmas_Disabled :=
8000               Chars (Get_Pragma_Arg (Arg1)) = Name_Disable;
8001
8002          ---------------------
8003          -- Detect_Blocking --
8004          ---------------------
8005
8006          --  pragma Detect_Blocking;
8007
8008          when Pragma_Detect_Blocking =>
8009             Ada_2005_Pragma;
8010             Check_Arg_Count (0);
8011             Check_Valid_Configuration_Pragma;
8012             Detect_Blocking := True;
8013
8014          --------------------------
8015          -- Default_Storage_Pool --
8016          --------------------------
8017
8018          --  pragma Default_Storage_Pool (storage_pool_NAME | null);
8019
8020          when Pragma_Default_Storage_Pool =>
8021             Ada_2012_Pragma;
8022             Check_Arg_Count (1);
8023
8024             --  Default_Storage_Pool can appear as a configuration pragma, or
8025             --  in a declarative part or a package spec.
8026
8027             if not Is_Configuration_Pragma then
8028                Check_Is_In_Decl_Part_Or_Package_Spec;
8029             end if;
8030
8031             --  Case of Default_Storage_Pool (null);
8032
8033             if Nkind (Expression (Arg1)) = N_Null then
8034                Analyze (Expression (Arg1));
8035
8036                --  This is an odd case, this is not really an expression, so
8037                --  we don't have a type for it. So just set the type to Empty.
8038
8039                Set_Etype (Expression (Arg1), Empty);
8040
8041             --  Case of Default_Storage_Pool (storage_pool_NAME);
8042
8043             else
8044                --  If it's a configuration pragma, then the only allowed
8045                --  argument is "null".
8046
8047                if Is_Configuration_Pragma then
8048                   Error_Pragma_Arg ("NULL expected", Arg1);
8049                end if;
8050
8051                --  The expected type for a non-"null" argument is
8052                --  Root_Storage_Pool'Class.
8053
8054                Analyze_And_Resolve
8055                  (Get_Pragma_Arg (Arg1),
8056                   Typ => Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
8057             end if;
8058
8059             --  Finally, record the pool name (or null). Freeze.Freeze_Entity
8060             --  for an access type will use this information to set the
8061             --  appropriate attributes of the access type.
8062
8063             Default_Pool := Expression (Arg1);
8064
8065          ---------------
8066          -- Dimension --
8067          ---------------
8068
8069          when Pragma_Dimension =>
8070             GNAT_Pragma;
8071             Check_Arg_Count (4);
8072             Check_No_Identifiers;
8073             Check_Arg_Is_Local_Name (Arg1);
8074
8075             if not Is_Type (Arg1) then
8076                Error_Pragma ("first argument for pragma% must be subtype");
8077             end if;
8078
8079             Check_Arg_Is_Static_Expression (Arg2, Standard_Integer);
8080             Check_Arg_Is_Static_Expression (Arg3, Standard_Integer);
8081             Check_Arg_Is_Static_Expression (Arg4, Standard_Integer);
8082
8083          ------------------------------------
8084          -- Disable_Atomic_Synchronization --
8085          ------------------------------------
8086
8087          --  pragma Disable_Atomic_Synchronization [(Entity)];
8088
8089          when Pragma_Disable_Atomic_Synchronization =>
8090             Process_Disable_Enable_Atomic_Sync (Name_Suppress);
8091
8092          -------------------
8093          -- Discard_Names --
8094          -------------------
8095
8096          --  pragma Discard_Names [([On =>] LOCAL_NAME)];
8097
8098          when Pragma_Discard_Names => Discard_Names : declare
8099             E    : Entity_Id;
8100             E_Id : Entity_Id;
8101
8102          begin
8103             Check_Ada_83_Warning;
8104
8105             --  Deal with configuration pragma case
8106
8107             if Arg_Count = 0 and then Is_Configuration_Pragma then
8108                Global_Discard_Names := True;
8109                return;
8110
8111             --  Otherwise, check correct appropriate context
8112
8113             else
8114                Check_Is_In_Decl_Part_Or_Package_Spec;
8115
8116                if Arg_Count = 0 then
8117
8118                   --  If there is no parameter, then from now on this pragma
8119                   --  applies to any enumeration, exception or tagged type
8120                   --  defined in the current declarative part, and recursively
8121                   --  to any nested scope.
8122
8123                   Set_Discard_Names (Current_Scope);
8124                   return;
8125
8126                else
8127                   Check_Arg_Count (1);
8128                   Check_Optional_Identifier (Arg1, Name_On);
8129                   Check_Arg_Is_Local_Name (Arg1);
8130
8131                   E_Id := Get_Pragma_Arg (Arg1);
8132
8133                   if Etype (E_Id) = Any_Type then
8134                      return;
8135                   else
8136                      E := Entity (E_Id);
8137                   end if;
8138
8139                   if (Is_First_Subtype (E)
8140                       and then
8141                         (Is_Enumeration_Type (E) or else Is_Tagged_Type (E)))
8142                     or else Ekind (E) = E_Exception
8143                   then
8144                      Set_Discard_Names (E);
8145                   else
8146                      Error_Pragma_Arg
8147                        ("inappropriate entity for pragma%", Arg1);
8148                   end if;
8149
8150                end if;
8151             end if;
8152          end Discard_Names;
8153
8154          ------------------------
8155          -- Dispatching_Domain --
8156          ------------------------
8157
8158          --  pragma Dispatching_Domain (EXPRESSION);
8159
8160          when Pragma_Dispatching_Domain => Dispatching_Domain : declare
8161             P   : constant Node_Id := Parent (N);
8162             Arg : Node_Id;
8163
8164          begin
8165             Ada_2012_Pragma;
8166             Check_No_Identifiers;
8167             Check_Arg_Count (1);
8168
8169             --  This pragma is born obsolete, but not the aspect
8170
8171             if not From_Aspect_Specification (N) then
8172                Check_Restriction
8173                  (No_Obsolescent_Features, Pragma_Identifier (N));
8174             end if;
8175
8176             if Nkind (P) = N_Task_Definition then
8177                Arg := Get_Pragma_Arg (Arg1);
8178
8179                --  The expression must be analyzed in the special manner
8180                --  described in "Handling of Default and Per-Object
8181                --  Expressions" in sem.ads.
8182
8183                Preanalyze_Spec_Expression (Arg, RTE (RE_Dispatching_Domain));
8184
8185             --  Anything else is incorrect
8186
8187             else
8188                Pragma_Misplaced;
8189             end if;
8190
8191             if Has_Pragma_Dispatching_Domain (P) then
8192                Error_Pragma ("duplicate pragma% not allowed");
8193             else
8194                Set_Has_Pragma_Dispatching_Domain (P, True);
8195
8196                if Nkind (P) = N_Task_Definition then
8197                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
8198                end if;
8199             end if;
8200          end Dispatching_Domain;
8201
8202          ---------------
8203          -- Elaborate --
8204          ---------------
8205
8206          --  pragma Elaborate (library_unit_NAME {, library_unit_NAME});
8207
8208          when Pragma_Elaborate => Elaborate : declare
8209             Arg   : Node_Id;
8210             Citem : Node_Id;
8211
8212          begin
8213             --  Pragma must be in context items list of a compilation unit
8214
8215             if not Is_In_Context_Clause then
8216                Pragma_Misplaced;
8217             end if;
8218
8219             --  Must be at least one argument
8220
8221             if Arg_Count = 0 then
8222                Error_Pragma ("pragma% requires at least one argument");
8223             end if;
8224
8225             --  In Ada 83 mode, there can be no items following it in the
8226             --  context list except other pragmas and implicit with clauses
8227             --  (e.g. those added by use of Rtsfind). In Ada 95 mode, this
8228             --  placement rule does not apply.
8229
8230             if Ada_Version = Ada_83 and then Comes_From_Source (N) then
8231                Citem := Next (N);
8232                while Present (Citem) loop
8233                   if Nkind (Citem) = N_Pragma
8234                     or else (Nkind (Citem) = N_With_Clause
8235                               and then Implicit_With (Citem))
8236                   then
8237                      null;
8238                   else
8239                      Error_Pragma
8240                        ("(Ada 83) pragma% must be at end of context clause");
8241                   end if;
8242
8243                   Next (Citem);
8244                end loop;
8245             end if;
8246
8247             --  Finally, the arguments must all be units mentioned in a with
8248             --  clause in the same context clause. Note we already checked (in
8249             --  Par.Prag) that the arguments are all identifiers or selected
8250             --  components.
8251
8252             Arg := Arg1;
8253             Outer : while Present (Arg) loop
8254                Citem := First (List_Containing (N));
8255                Inner : while Citem /= N loop
8256                   if Nkind (Citem) = N_With_Clause
8257                     and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
8258                   then
8259                      Set_Elaborate_Present (Citem, True);
8260                      Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
8261                      Generate_Reference (Entity (Name (Citem)), Citem);
8262
8263                      --  With the pragma present, elaboration calls on
8264                      --  subprograms from the named unit need no further
8265                      --  checks, as long as the pragma appears in the current
8266                      --  compilation unit. If the pragma appears in some unit
8267                      --  in the context, there might still be a need for an
8268                      --  Elaborate_All_Desirable from the current compilation
8269                      --  to the named unit, so we keep the check enabled.
8270
8271                      if In_Extended_Main_Source_Unit (N) then
8272                         Set_Suppress_Elaboration_Warnings
8273                           (Entity (Name (Citem)));
8274                      end if;
8275
8276                      exit Inner;
8277                   end if;
8278
8279                   Next (Citem);
8280                end loop Inner;
8281
8282                if Citem = N then
8283                   Error_Pragma_Arg
8284                     ("argument of pragma% is not with'ed unit", Arg);
8285                end if;
8286
8287                Next (Arg);
8288             end loop Outer;
8289
8290             --  Give a warning if operating in static mode with -gnatwl
8291             --  (elaboration warnings enabled) switch set.
8292
8293             if Elab_Warnings and not Dynamic_Elaboration_Checks then
8294                Error_Msg_N
8295                  ("?use of pragma Elaborate may not be safe", N);
8296                Error_Msg_N
8297                  ("?use pragma Elaborate_All instead if possible", N);
8298             end if;
8299          end Elaborate;
8300
8301          -------------------
8302          -- Elaborate_All --
8303          -------------------
8304
8305          --  pragma Elaborate_All (library_unit_NAME {, library_unit_NAME});
8306
8307          when Pragma_Elaborate_All => Elaborate_All : declare
8308             Arg   : Node_Id;
8309             Citem : Node_Id;
8310
8311          begin
8312             Check_Ada_83_Warning;
8313
8314             --  Pragma must be in context items list of a compilation unit
8315
8316             if not Is_In_Context_Clause then
8317                Pragma_Misplaced;
8318             end if;
8319
8320             --  Must be at least one argument
8321
8322             if Arg_Count = 0 then
8323                Error_Pragma ("pragma% requires at least one argument");
8324             end if;
8325
8326             --  Note: unlike pragma Elaborate, pragma Elaborate_All does not
8327             --  have to appear at the end of the context clause, but may
8328             --  appear mixed in with other items, even in Ada 83 mode.
8329
8330             --  Final check: the arguments must all be units mentioned in
8331             --  a with clause in the same context clause. Note that we
8332             --  already checked (in Par.Prag) that all the arguments are
8333             --  either identifiers or selected components.
8334
8335             Arg := Arg1;
8336             Outr : while Present (Arg) loop
8337                Citem := First (List_Containing (N));
8338                Innr : while Citem /= N loop
8339                   if Nkind (Citem) = N_With_Clause
8340                     and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
8341                   then
8342                      Set_Elaborate_All_Present (Citem, True);
8343                      Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
8344
8345                      --  Suppress warnings and elaboration checks on the named
8346                      --  unit if the pragma is in the current compilation, as
8347                      --  for pragma Elaborate.
8348
8349                      if In_Extended_Main_Source_Unit (N) then
8350                         Set_Suppress_Elaboration_Warnings
8351                           (Entity (Name (Citem)));
8352                      end if;
8353                      exit Innr;
8354                   end if;
8355
8356                   Next (Citem);
8357                end loop Innr;
8358
8359                if Citem = N then
8360                   Set_Error_Posted (N);
8361                   Error_Pragma_Arg
8362                     ("argument of pragma% is not with'ed unit", Arg);
8363                end if;
8364
8365                Next (Arg);
8366             end loop Outr;
8367          end Elaborate_All;
8368
8369          --------------------
8370          -- Elaborate_Body --
8371          --------------------
8372
8373          --  pragma Elaborate_Body [( library_unit_NAME )];
8374
8375          when Pragma_Elaborate_Body => Elaborate_Body : declare
8376             Cunit_Node : Node_Id;
8377             Cunit_Ent  : Entity_Id;
8378
8379          begin
8380             Check_Ada_83_Warning;
8381             Check_Valid_Library_Unit_Pragma;
8382
8383             if Nkind (N) = N_Null_Statement then
8384                return;
8385             end if;
8386
8387             Cunit_Node := Cunit (Current_Sem_Unit);
8388             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
8389
8390             if Nkind_In (Unit (Cunit_Node), N_Package_Body,
8391                                             N_Subprogram_Body)
8392             then
8393                Error_Pragma ("pragma% must refer to a spec, not a body");
8394             else
8395                Set_Body_Required (Cunit_Node, True);
8396                Set_Has_Pragma_Elaborate_Body (Cunit_Ent);
8397
8398                --  If we are in dynamic elaboration mode, then we suppress
8399                --  elaboration warnings for the unit, since it is definitely
8400                --  fine NOT to do dynamic checks at the first level (and such
8401                --  checks will be suppressed because no elaboration boolean
8402                --  is created for Elaborate_Body packages).
8403
8404                --  But in the static model of elaboration, Elaborate_Body is
8405                --  definitely NOT good enough to ensure elaboration safety on
8406                --  its own, since the body may WITH other units that are not
8407                --  safe from an elaboration point of view, so a client must
8408                --  still do an Elaborate_All on such units.
8409
8410                --  Debug flag -gnatdD restores the old behavior of 3.13, where
8411                --  Elaborate_Body always suppressed elab warnings.
8412
8413                if Dynamic_Elaboration_Checks or Debug_Flag_DD then
8414                   Set_Suppress_Elaboration_Warnings (Cunit_Ent);
8415                end if;
8416             end if;
8417          end Elaborate_Body;
8418
8419          ------------------------
8420          -- Elaboration_Checks --
8421          ------------------------
8422
8423          --  pragma Elaboration_Checks (Static | Dynamic);
8424
8425          when Pragma_Elaboration_Checks =>
8426             GNAT_Pragma;
8427             Check_Arg_Count (1);
8428             Check_Arg_Is_One_Of (Arg1, Name_Static, Name_Dynamic);
8429             Dynamic_Elaboration_Checks :=
8430               (Chars (Get_Pragma_Arg (Arg1)) = Name_Dynamic);
8431
8432          ---------------
8433          -- Eliminate --
8434          ---------------
8435
8436          --  pragma Eliminate (
8437          --      [Unit_Name  =>] IDENTIFIER | SELECTED_COMPONENT,
8438          --    [,[Entity     =>] IDENTIFIER |
8439          --                      SELECTED_COMPONENT |
8440          --                      STRING_LITERAL]
8441          --    [,                OVERLOADING_RESOLUTION]);
8442
8443          --  OVERLOADING_RESOLUTION ::= PARAMETER_AND_RESULT_TYPE_PROFILE |
8444          --                             SOURCE_LOCATION
8445
8446          --  PARAMETER_AND_RESULT_TYPE_PROFILE ::= PROCEDURE_PROFILE |
8447          --                                        FUNCTION_PROFILE
8448
8449          --  PROCEDURE_PROFILE ::= Parameter_Types => PARAMETER_TYPES
8450
8451          --  FUNCTION_PROFILE ::= [Parameter_Types => PARAMETER_TYPES,]
8452          --                       Result_Type => result_SUBTYPE_NAME]
8453
8454          --  PARAMETER_TYPES ::= (SUBTYPE_NAME {, SUBTYPE_NAME})
8455          --  SUBTYPE_NAME    ::= STRING_LITERAL
8456
8457          --  SOURCE_LOCATION ::= Source_Location => SOURCE_TRACE
8458          --  SOURCE_TRACE    ::= STRING_LITERAL
8459
8460          when Pragma_Eliminate => Eliminate : declare
8461             Args  : Args_List (1 .. 5);
8462             Names : constant Name_List (1 .. 5) := (
8463                       Name_Unit_Name,
8464                       Name_Entity,
8465                       Name_Parameter_Types,
8466                       Name_Result_Type,
8467                       Name_Source_Location);
8468
8469             Unit_Name       : Node_Id renames Args (1);
8470             Entity          : Node_Id renames Args (2);
8471             Parameter_Types : Node_Id renames Args (3);
8472             Result_Type     : Node_Id renames Args (4);
8473             Source_Location : Node_Id renames Args (5);
8474
8475          begin
8476             GNAT_Pragma;
8477             Check_Valid_Configuration_Pragma;
8478             Gather_Associations (Names, Args);
8479
8480             if No (Unit_Name) then
8481                Error_Pragma ("missing Unit_Name argument for pragma%");
8482             end if;
8483
8484             if No (Entity)
8485               and then (Present (Parameter_Types)
8486                           or else
8487                         Present (Result_Type)
8488                           or else
8489                         Present (Source_Location))
8490             then
8491                Error_Pragma ("missing Entity argument for pragma%");
8492             end if;
8493
8494             if (Present (Parameter_Types)
8495                   or else
8496                 Present (Result_Type))
8497               and then
8498                 Present (Source_Location)
8499             then
8500                Error_Pragma
8501                  ("parameter profile and source location cannot " &
8502                   "be used together in pragma%");
8503             end if;
8504
8505             Process_Eliminate_Pragma
8506               (N,
8507                Unit_Name,
8508                Entity,
8509                Parameter_Types,
8510                Result_Type,
8511                Source_Location);
8512          end Eliminate;
8513
8514          -----------------------------------
8515          -- Enable_Atomic_Synchronization --
8516          -----------------------------------
8517
8518          --  pragma Enable_Atomic_Synchronization [(Entity)];
8519
8520          when Pragma_Enable_Atomic_Synchronization =>
8521             Process_Disable_Enable_Atomic_Sync (Name_Unsuppress);
8522
8523          ------------
8524          -- Export --
8525          ------------
8526
8527          --  pragma Export (
8528          --    [   Convention    =>] convention_IDENTIFIER,
8529          --    [   Entity        =>] local_NAME
8530          --    [, [External_Name =>] static_string_EXPRESSION ]
8531          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
8532
8533          when Pragma_Export => Export : declare
8534             C      : Convention_Id;
8535             Def_Id : Entity_Id;
8536
8537             pragma Warnings (Off, C);
8538
8539          begin
8540             Check_Ada_83_Warning;
8541             Check_Arg_Order
8542               ((Name_Convention,
8543                 Name_Entity,
8544                 Name_External_Name,
8545                 Name_Link_Name));
8546             Check_At_Least_N_Arguments (2);
8547             Check_At_Most_N_Arguments  (4);
8548             Process_Convention (C, Def_Id);
8549
8550             if Ekind (Def_Id) /= E_Constant then
8551                Note_Possible_Modification
8552                  (Get_Pragma_Arg (Arg2), Sure => False);
8553             end if;
8554
8555             Process_Interface_Name (Def_Id, Arg3, Arg4);
8556             Set_Exported (Def_Id, Arg2);
8557
8558             --  If the entity is a deferred constant, propagate the information
8559             --  to the full view, because gigi elaborates the full view only.
8560
8561             if Ekind (Def_Id) = E_Constant
8562               and then Present (Full_View (Def_Id))
8563             then
8564                declare
8565                   Id2 : constant Entity_Id := Full_View (Def_Id);
8566                begin
8567                   Set_Is_Exported    (Id2, Is_Exported          (Def_Id));
8568                   Set_First_Rep_Item (Id2, First_Rep_Item       (Def_Id));
8569                   Set_Interface_Name (Id2, Einfo.Interface_Name (Def_Id));
8570                end;
8571             end if;
8572          end Export;
8573
8574          ----------------------
8575          -- Export_Exception --
8576          ----------------------
8577
8578          --  pragma Export_Exception (
8579          --        [Internal         =>] LOCAL_NAME
8580          --     [, [External         =>] EXTERNAL_SYMBOL]
8581          --     [, [Form     =>] Ada | VMS]
8582          --     [, [Code     =>] static_integer_EXPRESSION]);
8583
8584          when Pragma_Export_Exception => Export_Exception : declare
8585             Args  : Args_List (1 .. 4);
8586             Names : constant Name_List (1 .. 4) := (
8587                       Name_Internal,
8588                       Name_External,
8589                       Name_Form,
8590                       Name_Code);
8591
8592             Internal : Node_Id renames Args (1);
8593             External : Node_Id renames Args (2);
8594             Form     : Node_Id renames Args (3);
8595             Code     : Node_Id renames Args (4);
8596
8597          begin
8598             GNAT_Pragma;
8599
8600             if Inside_A_Generic then
8601                Error_Pragma ("pragma% cannot be used for generic entities");
8602             end if;
8603
8604             Gather_Associations (Names, Args);
8605             Process_Extended_Import_Export_Exception_Pragma (
8606               Arg_Internal => Internal,
8607               Arg_External => External,
8608               Arg_Form     => Form,
8609               Arg_Code     => Code);
8610
8611             if not Is_VMS_Exception (Entity (Internal)) then
8612                Set_Exported (Entity (Internal), Internal);
8613             end if;
8614          end Export_Exception;
8615
8616          ---------------------
8617          -- Export_Function --
8618          ---------------------
8619
8620          --  pragma Export_Function (
8621          --        [Internal         =>] LOCAL_NAME
8622          --     [, [External         =>] EXTERNAL_SYMBOL]
8623          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8624          --     [, [Result_Type      =>] TYPE_DESIGNATOR]
8625          --     [, [Mechanism        =>] MECHANISM]
8626          --     [, [Result_Mechanism =>] MECHANISM_NAME]);
8627
8628          --  EXTERNAL_SYMBOL ::=
8629          --    IDENTIFIER
8630          --  | static_string_EXPRESSION
8631
8632          --  PARAMETER_TYPES ::=
8633          --    null
8634          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8635
8636          --  TYPE_DESIGNATOR ::=
8637          --    subtype_NAME
8638          --  | subtype_Name ' Access
8639
8640          --  MECHANISM ::=
8641          --    MECHANISM_NAME
8642          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8643
8644          --  MECHANISM_ASSOCIATION ::=
8645          --    [formal_parameter_NAME =>] MECHANISM_NAME
8646
8647          --  MECHANISM_NAME ::=
8648          --    Value
8649          --  | Reference
8650          --  | Descriptor [([Class =>] CLASS_NAME)]
8651
8652          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8653
8654          when Pragma_Export_Function => Export_Function : declare
8655             Args  : Args_List (1 .. 6);
8656             Names : constant Name_List (1 .. 6) := (
8657                       Name_Internal,
8658                       Name_External,
8659                       Name_Parameter_Types,
8660                       Name_Result_Type,
8661                       Name_Mechanism,
8662                       Name_Result_Mechanism);
8663
8664             Internal         : Node_Id renames Args (1);
8665             External         : Node_Id renames Args (2);
8666             Parameter_Types  : Node_Id renames Args (3);
8667             Result_Type      : Node_Id renames Args (4);
8668             Mechanism        : Node_Id renames Args (5);
8669             Result_Mechanism : Node_Id renames Args (6);
8670
8671          begin
8672             GNAT_Pragma;
8673             Gather_Associations (Names, Args);
8674             Process_Extended_Import_Export_Subprogram_Pragma (
8675               Arg_Internal         => Internal,
8676               Arg_External         => External,
8677               Arg_Parameter_Types  => Parameter_Types,
8678               Arg_Result_Type      => Result_Type,
8679               Arg_Mechanism        => Mechanism,
8680               Arg_Result_Mechanism => Result_Mechanism);
8681          end Export_Function;
8682
8683          -------------------
8684          -- Export_Object --
8685          -------------------
8686
8687          --  pragma Export_Object (
8688          --        [Internal =>] LOCAL_NAME
8689          --     [, [External =>] EXTERNAL_SYMBOL]
8690          --     [, [Size     =>] EXTERNAL_SYMBOL]);
8691
8692          --  EXTERNAL_SYMBOL ::=
8693          --    IDENTIFIER
8694          --  | static_string_EXPRESSION
8695
8696          --  PARAMETER_TYPES ::=
8697          --    null
8698          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8699
8700          --  TYPE_DESIGNATOR ::=
8701          --    subtype_NAME
8702          --  | subtype_Name ' Access
8703
8704          --  MECHANISM ::=
8705          --    MECHANISM_NAME
8706          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8707
8708          --  MECHANISM_ASSOCIATION ::=
8709          --    [formal_parameter_NAME =>] MECHANISM_NAME
8710
8711          --  MECHANISM_NAME ::=
8712          --    Value
8713          --  | Reference
8714          --  | Descriptor [([Class =>] CLASS_NAME)]
8715
8716          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8717
8718          when Pragma_Export_Object => Export_Object : declare
8719             Args  : Args_List (1 .. 3);
8720             Names : constant Name_List (1 .. 3) := (
8721                       Name_Internal,
8722                       Name_External,
8723                       Name_Size);
8724
8725             Internal : Node_Id renames Args (1);
8726             External : Node_Id renames Args (2);
8727             Size     : Node_Id renames Args (3);
8728
8729          begin
8730             GNAT_Pragma;
8731             Gather_Associations (Names, Args);
8732             Process_Extended_Import_Export_Object_Pragma (
8733               Arg_Internal => Internal,
8734               Arg_External => External,
8735               Arg_Size     => Size);
8736          end Export_Object;
8737
8738          ----------------------
8739          -- Export_Procedure --
8740          ----------------------
8741
8742          --  pragma Export_Procedure (
8743          --        [Internal         =>] LOCAL_NAME
8744          --     [, [External         =>] EXTERNAL_SYMBOL]
8745          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8746          --     [, [Mechanism        =>] MECHANISM]);
8747
8748          --  EXTERNAL_SYMBOL ::=
8749          --    IDENTIFIER
8750          --  | static_string_EXPRESSION
8751
8752          --  PARAMETER_TYPES ::=
8753          --    null
8754          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8755
8756          --  TYPE_DESIGNATOR ::=
8757          --    subtype_NAME
8758          --  | subtype_Name ' Access
8759
8760          --  MECHANISM ::=
8761          --    MECHANISM_NAME
8762          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8763
8764          --  MECHANISM_ASSOCIATION ::=
8765          --    [formal_parameter_NAME =>] MECHANISM_NAME
8766
8767          --  MECHANISM_NAME ::=
8768          --    Value
8769          --  | Reference
8770          --  | Descriptor [([Class =>] CLASS_NAME)]
8771
8772          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8773
8774          when Pragma_Export_Procedure => Export_Procedure : declare
8775             Args  : Args_List (1 .. 4);
8776             Names : constant Name_List (1 .. 4) := (
8777                       Name_Internal,
8778                       Name_External,
8779                       Name_Parameter_Types,
8780                       Name_Mechanism);
8781
8782             Internal        : Node_Id renames Args (1);
8783             External        : Node_Id renames Args (2);
8784             Parameter_Types : Node_Id renames Args (3);
8785             Mechanism       : Node_Id renames Args (4);
8786
8787          begin
8788             GNAT_Pragma;
8789             Gather_Associations (Names, Args);
8790             Process_Extended_Import_Export_Subprogram_Pragma (
8791               Arg_Internal        => Internal,
8792               Arg_External        => External,
8793               Arg_Parameter_Types => Parameter_Types,
8794               Arg_Mechanism       => Mechanism);
8795          end Export_Procedure;
8796
8797          ------------------
8798          -- Export_Value --
8799          ------------------
8800
8801          --  pragma Export_Value (
8802          --     [Value     =>] static_integer_EXPRESSION,
8803          --     [Link_Name =>] static_string_EXPRESSION);
8804
8805          when Pragma_Export_Value =>
8806             GNAT_Pragma;
8807             Check_Arg_Order ((Name_Value, Name_Link_Name));
8808             Check_Arg_Count (2);
8809
8810             Check_Optional_Identifier (Arg1, Name_Value);
8811             Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
8812
8813             Check_Optional_Identifier (Arg2, Name_Link_Name);
8814             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
8815
8816          -----------------------------
8817          -- Export_Valued_Procedure --
8818          -----------------------------
8819
8820          --  pragma Export_Valued_Procedure (
8821          --        [Internal         =>] LOCAL_NAME
8822          --     [, [External         =>] EXTERNAL_SYMBOL,]
8823          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8824          --     [, [Mechanism        =>] MECHANISM]);
8825
8826          --  EXTERNAL_SYMBOL ::=
8827          --    IDENTIFIER
8828          --  | static_string_EXPRESSION
8829
8830          --  PARAMETER_TYPES ::=
8831          --    null
8832          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8833
8834          --  TYPE_DESIGNATOR ::=
8835          --    subtype_NAME
8836          --  | subtype_Name ' Access
8837
8838          --  MECHANISM ::=
8839          --    MECHANISM_NAME
8840          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8841
8842          --  MECHANISM_ASSOCIATION ::=
8843          --    [formal_parameter_NAME =>] MECHANISM_NAME
8844
8845          --  MECHANISM_NAME ::=
8846          --    Value
8847          --  | Reference
8848          --  | Descriptor [([Class =>] CLASS_NAME)]
8849
8850          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8851
8852          when Pragma_Export_Valued_Procedure =>
8853          Export_Valued_Procedure : declare
8854             Args  : Args_List (1 .. 4);
8855             Names : constant Name_List (1 .. 4) := (
8856                       Name_Internal,
8857                       Name_External,
8858                       Name_Parameter_Types,
8859                       Name_Mechanism);
8860
8861             Internal        : Node_Id renames Args (1);
8862             External        : Node_Id renames Args (2);
8863             Parameter_Types : Node_Id renames Args (3);
8864             Mechanism       : Node_Id renames Args (4);
8865
8866          begin
8867             GNAT_Pragma;
8868             Gather_Associations (Names, Args);
8869             Process_Extended_Import_Export_Subprogram_Pragma (
8870               Arg_Internal        => Internal,
8871               Arg_External        => External,
8872               Arg_Parameter_Types => Parameter_Types,
8873               Arg_Mechanism       => Mechanism);
8874          end Export_Valued_Procedure;
8875
8876          -------------------
8877          -- Extend_System --
8878          -------------------
8879
8880          --  pragma Extend_System ([Name =>] Identifier);
8881
8882          when Pragma_Extend_System => Extend_System : declare
8883          begin
8884             GNAT_Pragma;
8885             Check_Valid_Configuration_Pragma;
8886             Check_Arg_Count (1);
8887             Check_Optional_Identifier (Arg1, Name_Name);
8888             Check_Arg_Is_Identifier (Arg1);
8889
8890             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
8891
8892             if Name_Len > 4
8893               and then Name_Buffer (1 .. 4) = "aux_"
8894             then
8895                if Present (System_Extend_Pragma_Arg) then
8896                   if Chars (Get_Pragma_Arg (Arg1)) =
8897                      Chars (Expression (System_Extend_Pragma_Arg))
8898                   then
8899                      null;
8900                   else
8901                      Error_Msg_Sloc := Sloc (System_Extend_Pragma_Arg);
8902                      Error_Pragma ("pragma% conflicts with that #");
8903                   end if;
8904
8905                else
8906                   System_Extend_Pragma_Arg := Arg1;
8907
8908                   if not GNAT_Mode then
8909                      System_Extend_Unit := Arg1;
8910                   end if;
8911                end if;
8912             else
8913                Error_Pragma ("incorrect name for pragma%, must be Aux_xxx");
8914             end if;
8915          end Extend_System;
8916
8917          ------------------------
8918          -- Extensions_Allowed --
8919          ------------------------
8920
8921          --  pragma Extensions_Allowed (ON | OFF);
8922
8923          when Pragma_Extensions_Allowed =>
8924             GNAT_Pragma;
8925             Check_Arg_Count (1);
8926             Check_No_Identifiers;
8927             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
8928
8929             if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
8930                Extensions_Allowed := True;
8931                Ada_Version := Ada_Version_Type'Last;
8932
8933             else
8934                Extensions_Allowed := False;
8935                Ada_Version := Ada_Version_Explicit;
8936             end if;
8937
8938          --------------
8939          -- External --
8940          --------------
8941
8942          --  pragma External (
8943          --    [   Convention    =>] convention_IDENTIFIER,
8944          --    [   Entity        =>] local_NAME
8945          --    [, [External_Name =>] static_string_EXPRESSION ]
8946          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
8947
8948          when Pragma_External => External : declare
8949                Def_Id : Entity_Id;
8950
8951                C : Convention_Id;
8952                pragma Warnings (Off, C);
8953
8954          begin
8955             GNAT_Pragma;
8956             Check_Arg_Order
8957               ((Name_Convention,
8958                 Name_Entity,
8959                 Name_External_Name,
8960                 Name_Link_Name));
8961             Check_At_Least_N_Arguments (2);
8962             Check_At_Most_N_Arguments  (4);
8963             Process_Convention (C, Def_Id);
8964             Note_Possible_Modification
8965               (Get_Pragma_Arg (Arg2), Sure => False);
8966             Process_Interface_Name (Def_Id, Arg3, Arg4);
8967             Set_Exported (Def_Id, Arg2);
8968          end External;
8969
8970          --------------------------
8971          -- External_Name_Casing --
8972          --------------------------
8973
8974          --  pragma External_Name_Casing (
8975          --    UPPERCASE | LOWERCASE
8976          --    [, AS_IS | UPPERCASE | LOWERCASE]);
8977
8978          when Pragma_External_Name_Casing => External_Name_Casing : declare
8979          begin
8980             GNAT_Pragma;
8981             Check_No_Identifiers;
8982
8983             if Arg_Count = 2 then
8984                Check_Arg_Is_One_Of
8985                  (Arg2, Name_As_Is, Name_Uppercase, Name_Lowercase);
8986
8987                case Chars (Get_Pragma_Arg (Arg2)) is
8988                   when Name_As_Is     =>
8989                      Opt.External_Name_Exp_Casing := As_Is;
8990
8991                   when Name_Uppercase =>
8992                      Opt.External_Name_Exp_Casing := Uppercase;
8993
8994                   when Name_Lowercase =>
8995                      Opt.External_Name_Exp_Casing := Lowercase;
8996
8997                   when others =>
8998                      null;
8999                end case;
9000
9001             else
9002                Check_Arg_Count (1);
9003             end if;
9004
9005             Check_Arg_Is_One_Of (Arg1, Name_Uppercase, Name_Lowercase);
9006
9007             case Chars (Get_Pragma_Arg (Arg1)) is
9008                when Name_Uppercase =>
9009                   Opt.External_Name_Imp_Casing := Uppercase;
9010
9011                when Name_Lowercase =>
9012                   Opt.External_Name_Imp_Casing := Lowercase;
9013
9014                when others =>
9015                   null;
9016             end case;
9017          end External_Name_Casing;
9018
9019          --------------------------
9020          -- Favor_Top_Level --
9021          --------------------------
9022
9023          --  pragma Favor_Top_Level (type_NAME);
9024
9025          when Pragma_Favor_Top_Level => Favor_Top_Level : declare
9026                Named_Entity : Entity_Id;
9027
9028          begin
9029             GNAT_Pragma;
9030             Check_No_Identifiers;
9031             Check_Arg_Count (1);
9032             Check_Arg_Is_Local_Name (Arg1);
9033             Named_Entity := Entity (Get_Pragma_Arg (Arg1));
9034
9035             --  If it's an access-to-subprogram type (in particular, not a
9036             --  subtype), set the flag on that type.
9037
9038             if Is_Access_Subprogram_Type (Named_Entity) then
9039                Set_Can_Use_Internal_Rep (Named_Entity, False);
9040
9041             --  Otherwise it's an error (name denotes the wrong sort of entity)
9042
9043             else
9044                Error_Pragma_Arg
9045                  ("access-to-subprogram type expected",
9046                   Get_Pragma_Arg (Arg1));
9047             end if;
9048          end Favor_Top_Level;
9049
9050          ---------------
9051          -- Fast_Math --
9052          ---------------
9053
9054          --  pragma Fast_Math;
9055
9056          when Pragma_Fast_Math =>
9057             GNAT_Pragma;
9058             Check_No_Identifiers;
9059             Check_Valid_Configuration_Pragma;
9060             Fast_Math := True;
9061
9062          ---------------------------
9063          -- Finalize_Storage_Only --
9064          ---------------------------
9065
9066          --  pragma Finalize_Storage_Only (first_subtype_LOCAL_NAME);
9067
9068          when Pragma_Finalize_Storage_Only => Finalize_Storage : declare
9069             Assoc   : constant Node_Id := Arg1;
9070             Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
9071             Typ     : Entity_Id;
9072
9073          begin
9074             GNAT_Pragma;
9075             Check_No_Identifiers;
9076             Check_Arg_Count (1);
9077             Check_Arg_Is_Local_Name (Arg1);
9078
9079             Find_Type (Type_Id);
9080             Typ := Entity (Type_Id);
9081
9082             if Typ = Any_Type
9083               or else Rep_Item_Too_Early (Typ, N)
9084             then
9085                return;
9086             else
9087                Typ := Underlying_Type (Typ);
9088             end if;
9089
9090             if not Is_Controlled (Typ) then
9091                Error_Pragma ("pragma% must specify controlled type");
9092             end if;
9093
9094             Check_First_Subtype (Arg1);
9095
9096             if Finalize_Storage_Only (Typ) then
9097                Error_Pragma ("duplicate pragma%, only one allowed");
9098
9099             elsif not Rep_Item_Too_Late (Typ, N) then
9100                Set_Finalize_Storage_Only (Base_Type (Typ), True);
9101             end if;
9102          end Finalize_Storage;
9103
9104          --------------------------
9105          -- Float_Representation --
9106          --------------------------
9107
9108          --  pragma Float_Representation (FLOAT_REP[, float_type_LOCAL_NAME]);
9109
9110          --  FLOAT_REP ::= VAX_Float | IEEE_Float
9111
9112          when Pragma_Float_Representation => Float_Representation : declare
9113             Argx : Node_Id;
9114             Digs : Nat;
9115             Ent  : Entity_Id;
9116
9117          begin
9118             GNAT_Pragma;
9119
9120             if Arg_Count = 1 then
9121                Check_Valid_Configuration_Pragma;
9122             else
9123                Check_Arg_Count (2);
9124                Check_Optional_Identifier (Arg2, Name_Entity);
9125                Check_Arg_Is_Local_Name (Arg2);
9126             end if;
9127
9128             Check_No_Identifier (Arg1);
9129             Check_Arg_Is_One_Of (Arg1, Name_VAX_Float, Name_IEEE_Float);
9130
9131             if not OpenVMS_On_Target then
9132                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9133                   Error_Pragma
9134                     ("?pragma% ignored (applies only to Open'V'M'S)");
9135                end if;
9136
9137                return;
9138             end if;
9139
9140             --  One argument case
9141
9142             if Arg_Count = 1 then
9143                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9144                   if Opt.Float_Format = 'I' then
9145                      Error_Pragma ("'I'E'E'E format previously specified");
9146                   end if;
9147
9148                   Opt.Float_Format := 'V';
9149
9150                else
9151                   if Opt.Float_Format = 'V' then
9152                      Error_Pragma ("'V'A'X format previously specified");
9153                   end if;
9154
9155                   Opt.Float_Format := 'I';
9156                end if;
9157
9158                Set_Standard_Fpt_Formats;
9159
9160             --  Two argument case
9161
9162             else
9163                Argx := Get_Pragma_Arg (Arg2);
9164
9165                if not Is_Entity_Name (Argx)
9166                  or else not Is_Floating_Point_Type (Entity (Argx))
9167                then
9168                   Error_Pragma_Arg
9169                     ("second argument of% pragma must be floating-point type",
9170                      Arg2);
9171                end if;
9172
9173                Ent  := Entity (Argx);
9174                Digs := UI_To_Int (Digits_Value (Ent));
9175
9176                --  Two arguments, VAX_Float case
9177
9178                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9179                   case Digs is
9180                      when  6 => Set_F_Float (Ent);
9181                      when  9 => Set_D_Float (Ent);
9182                      when 15 => Set_G_Float (Ent);
9183
9184                      when others =>
9185                         Error_Pragma_Arg
9186                           ("wrong digits value, must be 6,9 or 15", Arg2);
9187                   end case;
9188
9189                --  Two arguments, IEEE_Float case
9190
9191                else
9192                   case Digs is
9193                      when  6 => Set_IEEE_Short (Ent);
9194                      when 15 => Set_IEEE_Long  (Ent);
9195
9196                      when others =>
9197                         Error_Pragma_Arg
9198                           ("wrong digits value, must be 6 or 15", Arg2);
9199                   end case;
9200                end if;
9201             end if;
9202          end Float_Representation;
9203
9204          -----------
9205          -- Ident --
9206          -----------
9207
9208          --  pragma Ident (static_string_EXPRESSION)
9209
9210          --  Note: pragma Comment shares this processing. Pragma Comment is
9211          --  identical to Ident, except that the restriction of the argument to
9212          --  31 characters and the placement restrictions are not enforced for
9213          --  pragma Comment.
9214
9215          when Pragma_Ident | Pragma_Comment => Ident : declare
9216             Str : Node_Id;
9217
9218          begin
9219             GNAT_Pragma;
9220             Check_Arg_Count (1);
9221             Check_No_Identifiers;
9222             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
9223             Store_Note (N);
9224
9225             --  For pragma Ident, preserve DEC compatibility by requiring the
9226             --  pragma to appear in a declarative part or package spec.
9227
9228             if Prag_Id = Pragma_Ident then
9229                Check_Is_In_Decl_Part_Or_Package_Spec;
9230             end if;
9231
9232             Str := Expr_Value_S (Get_Pragma_Arg (Arg1));
9233
9234             declare
9235                CS : Node_Id;
9236                GP : Node_Id;
9237
9238             begin
9239                GP := Parent (Parent (N));
9240
9241                if Nkind_In (GP, N_Package_Declaration,
9242                                 N_Generic_Package_Declaration)
9243                then
9244                   GP := Parent (GP);
9245                end if;
9246
9247                --  If we have a compilation unit, then record the ident value,
9248                --  checking for improper duplication.
9249
9250                if Nkind (GP) = N_Compilation_Unit then
9251                   CS := Ident_String (Current_Sem_Unit);
9252
9253                   if Present (CS) then
9254
9255                      --  For Ident, we do not permit multiple instances
9256
9257                      if Prag_Id = Pragma_Ident then
9258                         Error_Pragma ("duplicate% pragma not permitted");
9259
9260                      --  For Comment, we concatenate the string, unless we want
9261                      --  to preserve the tree structure for ASIS.
9262
9263                      elsif not ASIS_Mode then
9264                         Start_String (Strval (CS));
9265                         Store_String_Char (' ');
9266                         Store_String_Chars (Strval (Str));
9267                         Set_Strval (CS, End_String);
9268                      end if;
9269
9270                   else
9271                      --  In VMS, the effect of IDENT is achieved by passing
9272                      --  --identification=name as a --for-linker switch.
9273
9274                      if OpenVMS_On_Target then
9275                         Start_String;
9276                         Store_String_Chars
9277                           ("--for-linker=--identification=");
9278                         String_To_Name_Buffer (Strval (Str));
9279                         Store_String_Chars (Name_Buffer (1 .. Name_Len));
9280
9281                         --  Only the last processed IDENT is saved. The main
9282                         --  purpose is so an IDENT associated with a main
9283                         --  procedure will be used in preference to an IDENT
9284                         --  associated with a with'd package.
9285
9286                         Replace_Linker_Option_String
9287                           (End_String, "--for-linker=--identification=");
9288                      end if;
9289
9290                      Set_Ident_String (Current_Sem_Unit, Str);
9291                   end if;
9292
9293                --  For subunits, we just ignore the Ident, since in GNAT these
9294                --  are not separate object files, and hence not separate units
9295                --  in the unit table.
9296
9297                elsif Nkind (GP) = N_Subunit then
9298                   null;
9299
9300                --  Otherwise we have a misplaced pragma Ident, but we ignore
9301                --  this if we are in an instantiation, since it comes from
9302                --  a generic, and has no relevance to the instantiation.
9303
9304                elsif Prag_Id = Pragma_Ident then
9305                   if Instantiation_Location (Loc) = No_Location then
9306                      Error_Pragma ("pragma% only allowed at outer level");
9307                   end if;
9308                end if;
9309             end;
9310          end Ident;
9311
9312          ----------------------------
9313          -- Implementation_Defined --
9314          ----------------------------
9315
9316          --  pragma Implementation_Defined (local_NAME);
9317
9318          --  Marks previously declared entity as implementation defined. For
9319          --  an overloaded entity, applies to the most recent homonym.
9320
9321          --  pragma Implementation_Defined;
9322
9323          --  The form with no arguments appears anywhere within a scope, most
9324          --  typically a package spec, and indicates that all entities that are
9325          --  defined within the package spec are Implementation_Defined.
9326
9327          when Pragma_Implementation_Defined => Implementation_Defined : declare
9328             Ent : Entity_Id;
9329
9330          begin
9331             Check_No_Identifiers;
9332
9333             --  Form with no arguments
9334
9335             if Arg_Count = 0 then
9336                Set_Is_Implementation_Defined (Current_Scope);
9337
9338             --  Form with one argument
9339
9340             else
9341                Check_Arg_Count (1);
9342                Check_Arg_Is_Local_Name (Arg1);
9343                Ent := Entity (Get_Pragma_Arg (Arg1));
9344                Set_Is_Implementation_Defined (Ent);
9345             end if;
9346          end Implementation_Defined;
9347
9348          -----------------
9349          -- Implemented --
9350          -----------------
9351
9352          --  pragma Implemented (procedure_LOCAL_NAME, implementation_kind);
9353          --  implementation_kind ::= By_Entry | By_Protected_Procedure | By_Any
9354
9355          when Pragma_Implemented => Implemented : declare
9356             Proc_Id : Entity_Id;
9357             Typ     : Entity_Id;
9358
9359          begin
9360             Ada_2012_Pragma;
9361             Check_Arg_Count (2);
9362             Check_No_Identifiers;
9363             Check_Arg_Is_Identifier (Arg1);
9364             Check_Arg_Is_Local_Name (Arg1);
9365             Check_Arg_Is_One_Of
9366               (Arg2, Name_By_Any, Name_By_Entry, Name_By_Protected_Procedure);
9367
9368             --  Extract the name of the local procedure
9369
9370             Proc_Id := Entity (Get_Pragma_Arg (Arg1));
9371
9372             --  Ada 2012 (AI05-0030): The procedure_LOCAL_NAME must denote a
9373             --  primitive procedure of a synchronized tagged type.
9374
9375             if Ekind (Proc_Id) = E_Procedure
9376               and then Is_Primitive (Proc_Id)
9377               and then Present (First_Formal (Proc_Id))
9378             then
9379                Typ := Etype (First_Formal (Proc_Id));
9380
9381                if Is_Tagged_Type (Typ)
9382                  and then
9383
9384                   --  Check for a protected, a synchronized or a task interface
9385
9386                    ((Is_Interface (Typ)
9387                        and then Is_Synchronized_Interface (Typ))
9388
9389                   --  Check for a protected type or a task type that implements
9390                   --  an interface.
9391
9392                    or else
9393                     (Is_Concurrent_Record_Type (Typ)
9394                        and then Present (Interfaces (Typ)))
9395
9396                   --  Check for a private record extension with keyword
9397                   --  "synchronized".
9398
9399                    or else
9400                     (Ekind_In (Typ, E_Record_Type_With_Private,
9401                                     E_Record_Subtype_With_Private)
9402                        and then Synchronized_Present (Parent (Typ))))
9403                then
9404                   null;
9405                else
9406                   Error_Pragma_Arg
9407                     ("controlling formal must be of synchronized " &
9408                      "tagged type", Arg1);
9409                   return;
9410                end if;
9411
9412             --  Procedures declared inside a protected type must be accepted
9413
9414             elsif Ekind (Proc_Id) = E_Procedure
9415               and then Is_Protected_Type (Scope (Proc_Id))
9416             then
9417                null;
9418
9419             --  The first argument is not a primitive procedure
9420
9421             else
9422                Error_Pragma_Arg
9423                  ("pragma % must be applied to a primitive procedure", Arg1);
9424                return;
9425             end if;
9426
9427             --  Ada 2012 (AI05-0030): Cannot apply the implementation_kind
9428             --  By_Protected_Procedure to the primitive procedure of a task
9429             --  interface.
9430
9431             if Chars (Arg2) = Name_By_Protected_Procedure
9432               and then Is_Interface (Typ)
9433               and then Is_Task_Interface (Typ)
9434             then
9435                Error_Pragma_Arg
9436                  ("implementation kind By_Protected_Procedure cannot be " &
9437                   "applied to a task interface primitive", Arg2);
9438                return;
9439             end if;
9440
9441             Record_Rep_Item (Proc_Id, N);
9442          end Implemented;
9443
9444          ----------------------
9445          -- Implicit_Packing --
9446          ----------------------
9447
9448          --  pragma Implicit_Packing;
9449
9450          when Pragma_Implicit_Packing =>
9451             GNAT_Pragma;
9452             Check_Arg_Count (0);
9453             Implicit_Packing := True;
9454
9455          ------------
9456          -- Import --
9457          ------------
9458
9459          --  pragma Import (
9460          --       [Convention    =>] convention_IDENTIFIER,
9461          --       [Entity        =>] local_NAME
9462          --    [, [External_Name =>] static_string_EXPRESSION ]
9463          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
9464
9465          when Pragma_Import =>
9466             Check_Ada_83_Warning;
9467             Check_Arg_Order
9468               ((Name_Convention,
9469                 Name_Entity,
9470                 Name_External_Name,
9471                 Name_Link_Name));
9472             Check_At_Least_N_Arguments (2);
9473             Check_At_Most_N_Arguments  (4);
9474             Process_Import_Or_Interface;
9475
9476          ----------------------
9477          -- Import_Exception --
9478          ----------------------
9479
9480          --  pragma Import_Exception (
9481          --        [Internal         =>] LOCAL_NAME
9482          --     [, [External         =>] EXTERNAL_SYMBOL]
9483          --     [, [Form     =>] Ada | VMS]
9484          --     [, [Code     =>] static_integer_EXPRESSION]);
9485
9486          when Pragma_Import_Exception => Import_Exception : declare
9487             Args  : Args_List (1 .. 4);
9488             Names : constant Name_List (1 .. 4) := (
9489                       Name_Internal,
9490                       Name_External,
9491                       Name_Form,
9492                       Name_Code);
9493
9494             Internal : Node_Id renames Args (1);
9495             External : Node_Id renames Args (2);
9496             Form     : Node_Id renames Args (3);
9497             Code     : Node_Id renames Args (4);
9498
9499          begin
9500             GNAT_Pragma;
9501             Gather_Associations (Names, Args);
9502
9503             if Present (External) and then Present (Code) then
9504                Error_Pragma
9505                  ("cannot give both External and Code options for pragma%");
9506             end if;
9507
9508             Process_Extended_Import_Export_Exception_Pragma (
9509               Arg_Internal => Internal,
9510               Arg_External => External,
9511               Arg_Form     => Form,
9512               Arg_Code     => Code);
9513
9514             if not Is_VMS_Exception (Entity (Internal)) then
9515                Set_Imported (Entity (Internal));
9516             end if;
9517          end Import_Exception;
9518
9519          ---------------------
9520          -- Import_Function --
9521          ---------------------
9522
9523          --  pragma Import_Function (
9524          --        [Internal                 =>] LOCAL_NAME,
9525          --     [, [External                 =>] EXTERNAL_SYMBOL]
9526          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9527          --     [, [Result_Type              =>] SUBTYPE_MARK]
9528          --     [, [Mechanism                =>] MECHANISM]
9529          --     [, [Result_Mechanism         =>] MECHANISM_NAME]
9530          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9531
9532          --  EXTERNAL_SYMBOL ::=
9533          --    IDENTIFIER
9534          --  | static_string_EXPRESSION
9535
9536          --  PARAMETER_TYPES ::=
9537          --    null
9538          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9539
9540          --  TYPE_DESIGNATOR ::=
9541          --    subtype_NAME
9542          --  | subtype_Name ' Access
9543
9544          --  MECHANISM ::=
9545          --    MECHANISM_NAME
9546          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9547
9548          --  MECHANISM_ASSOCIATION ::=
9549          --    [formal_parameter_NAME =>] MECHANISM_NAME
9550
9551          --  MECHANISM_NAME ::=
9552          --    Value
9553          --  | Reference
9554          --  | Descriptor [([Class =>] CLASS_NAME)]
9555
9556          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9557
9558          when Pragma_Import_Function => Import_Function : declare
9559             Args  : Args_List (1 .. 7);
9560             Names : constant Name_List (1 .. 7) := (
9561                       Name_Internal,
9562                       Name_External,
9563                       Name_Parameter_Types,
9564                       Name_Result_Type,
9565                       Name_Mechanism,
9566                       Name_Result_Mechanism,
9567                       Name_First_Optional_Parameter);
9568
9569             Internal                 : Node_Id renames Args (1);
9570             External                 : Node_Id renames Args (2);
9571             Parameter_Types          : Node_Id renames Args (3);
9572             Result_Type              : Node_Id renames Args (4);
9573             Mechanism                : Node_Id renames Args (5);
9574             Result_Mechanism         : Node_Id renames Args (6);
9575             First_Optional_Parameter : Node_Id renames Args (7);
9576
9577          begin
9578             GNAT_Pragma;
9579             Gather_Associations (Names, Args);
9580             Process_Extended_Import_Export_Subprogram_Pragma (
9581               Arg_Internal                 => Internal,
9582               Arg_External                 => External,
9583               Arg_Parameter_Types          => Parameter_Types,
9584               Arg_Result_Type              => Result_Type,
9585               Arg_Mechanism                => Mechanism,
9586               Arg_Result_Mechanism         => Result_Mechanism,
9587               Arg_First_Optional_Parameter => First_Optional_Parameter);
9588          end Import_Function;
9589
9590          -------------------
9591          -- Import_Object --
9592          -------------------
9593
9594          --  pragma Import_Object (
9595          --        [Internal =>] LOCAL_NAME
9596          --     [, [External =>] EXTERNAL_SYMBOL]
9597          --     [, [Size     =>] EXTERNAL_SYMBOL]);
9598
9599          --  EXTERNAL_SYMBOL ::=
9600          --    IDENTIFIER
9601          --  | static_string_EXPRESSION
9602
9603          when Pragma_Import_Object => Import_Object : declare
9604             Args  : Args_List (1 .. 3);
9605             Names : constant Name_List (1 .. 3) := (
9606                       Name_Internal,
9607                       Name_External,
9608                       Name_Size);
9609
9610             Internal : Node_Id renames Args (1);
9611             External : Node_Id renames Args (2);
9612             Size     : Node_Id renames Args (3);
9613
9614          begin
9615             GNAT_Pragma;
9616             Gather_Associations (Names, Args);
9617             Process_Extended_Import_Export_Object_Pragma (
9618               Arg_Internal => Internal,
9619               Arg_External => External,
9620               Arg_Size     => Size);
9621          end Import_Object;
9622
9623          ----------------------
9624          -- Import_Procedure --
9625          ----------------------
9626
9627          --  pragma Import_Procedure (
9628          --        [Internal                 =>] LOCAL_NAME
9629          --     [, [External                 =>] EXTERNAL_SYMBOL]
9630          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9631          --     [, [Mechanism                =>] MECHANISM]
9632          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9633
9634          --  EXTERNAL_SYMBOL ::=
9635          --    IDENTIFIER
9636          --  | static_string_EXPRESSION
9637
9638          --  PARAMETER_TYPES ::=
9639          --    null
9640          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9641
9642          --  TYPE_DESIGNATOR ::=
9643          --    subtype_NAME
9644          --  | subtype_Name ' Access
9645
9646          --  MECHANISM ::=
9647          --    MECHANISM_NAME
9648          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9649
9650          --  MECHANISM_ASSOCIATION ::=
9651          --    [formal_parameter_NAME =>] MECHANISM_NAME
9652
9653          --  MECHANISM_NAME ::=
9654          --    Value
9655          --  | Reference
9656          --  | Descriptor [([Class =>] CLASS_NAME)]
9657
9658          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9659
9660          when Pragma_Import_Procedure => Import_Procedure : declare
9661             Args  : Args_List (1 .. 5);
9662             Names : constant Name_List (1 .. 5) := (
9663                       Name_Internal,
9664                       Name_External,
9665                       Name_Parameter_Types,
9666                       Name_Mechanism,
9667                       Name_First_Optional_Parameter);
9668
9669             Internal                 : Node_Id renames Args (1);
9670             External                 : Node_Id renames Args (2);
9671             Parameter_Types          : Node_Id renames Args (3);
9672             Mechanism                : Node_Id renames Args (4);
9673             First_Optional_Parameter : Node_Id renames Args (5);
9674
9675          begin
9676             GNAT_Pragma;
9677             Gather_Associations (Names, Args);
9678             Process_Extended_Import_Export_Subprogram_Pragma (
9679               Arg_Internal                 => Internal,
9680               Arg_External                 => External,
9681               Arg_Parameter_Types          => Parameter_Types,
9682               Arg_Mechanism                => Mechanism,
9683               Arg_First_Optional_Parameter => First_Optional_Parameter);
9684          end Import_Procedure;
9685
9686          -----------------------------
9687          -- Import_Valued_Procedure --
9688          -----------------------------
9689
9690          --  pragma Import_Valued_Procedure (
9691          --        [Internal                 =>] LOCAL_NAME
9692          --     [, [External                 =>] EXTERNAL_SYMBOL]
9693          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9694          --     [, [Mechanism                =>] MECHANISM]
9695          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9696
9697          --  EXTERNAL_SYMBOL ::=
9698          --    IDENTIFIER
9699          --  | static_string_EXPRESSION
9700
9701          --  PARAMETER_TYPES ::=
9702          --    null
9703          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9704
9705          --  TYPE_DESIGNATOR ::=
9706          --    subtype_NAME
9707          --  | subtype_Name ' Access
9708
9709          --  MECHANISM ::=
9710          --    MECHANISM_NAME
9711          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9712
9713          --  MECHANISM_ASSOCIATION ::=
9714          --    [formal_parameter_NAME =>] MECHANISM_NAME
9715
9716          --  MECHANISM_NAME ::=
9717          --    Value
9718          --  | Reference
9719          --  | Descriptor [([Class =>] CLASS_NAME)]
9720
9721          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9722
9723          when Pragma_Import_Valued_Procedure =>
9724          Import_Valued_Procedure : declare
9725             Args  : Args_List (1 .. 5);
9726             Names : constant Name_List (1 .. 5) := (
9727                       Name_Internal,
9728                       Name_External,
9729                       Name_Parameter_Types,
9730                       Name_Mechanism,
9731                       Name_First_Optional_Parameter);
9732
9733             Internal                 : Node_Id renames Args (1);
9734             External                 : Node_Id renames Args (2);
9735             Parameter_Types          : Node_Id renames Args (3);
9736             Mechanism                : Node_Id renames Args (4);
9737             First_Optional_Parameter : Node_Id renames Args (5);
9738
9739          begin
9740             GNAT_Pragma;
9741             Gather_Associations (Names, Args);
9742             Process_Extended_Import_Export_Subprogram_Pragma (
9743               Arg_Internal                 => Internal,
9744               Arg_External                 => External,
9745               Arg_Parameter_Types          => Parameter_Types,
9746               Arg_Mechanism                => Mechanism,
9747               Arg_First_Optional_Parameter => First_Optional_Parameter);
9748          end Import_Valued_Procedure;
9749
9750          -----------------
9751          -- Independent --
9752          -----------------
9753
9754          --  pragma Independent (LOCAL_NAME);
9755
9756          when Pragma_Independent => Independent : declare
9757             E_Id : Node_Id;
9758             E    : Entity_Id;
9759             D    : Node_Id;
9760             K    : Node_Kind;
9761
9762          begin
9763             Check_Ada_83_Warning;
9764             Ada_2012_Pragma;
9765             Check_No_Identifiers;
9766             Check_Arg_Count (1);
9767             Check_Arg_Is_Local_Name (Arg1);
9768             E_Id := Get_Pragma_Arg (Arg1);
9769
9770             if Etype (E_Id) = Any_Type then
9771                return;
9772             end if;
9773
9774             E := Entity (E_Id);
9775             D := Declaration_Node (E);
9776             K := Nkind (D);
9777
9778             --  Check duplicate before we chain ourselves!
9779
9780             Check_Duplicate_Pragma (E);
9781
9782             --  Check appropriate entity
9783
9784             if Is_Type (E) then
9785                if Rep_Item_Too_Early (E, N)
9786                     or else
9787                   Rep_Item_Too_Late (E, N)
9788                then
9789                   return;
9790                else
9791                   Check_First_Subtype (Arg1);
9792                end if;
9793
9794             elsif K = N_Object_Declaration
9795               or else (K = N_Component_Declaration
9796                        and then Original_Record_Component (E) = E)
9797             then
9798                if Rep_Item_Too_Late (E, N) then
9799                   return;
9800                end if;
9801
9802             else
9803                Error_Pragma_Arg
9804                  ("inappropriate entity for pragma%", Arg1);
9805             end if;
9806
9807             Independence_Checks.Append ((N, E));
9808          end Independent;
9809
9810          ----------------------------
9811          -- Independent_Components --
9812          ----------------------------
9813
9814          --  pragma Atomic_Components (array_LOCAL_NAME);
9815
9816          --  This processing is shared by Volatile_Components
9817
9818          when Pragma_Independent_Components => Independent_Components : declare
9819             E_Id : Node_Id;
9820             E    : Entity_Id;
9821             D    : Node_Id;
9822             K    : Node_Kind;
9823
9824          begin
9825             Check_Ada_83_Warning;
9826             Ada_2012_Pragma;
9827             Check_No_Identifiers;
9828             Check_Arg_Count (1);
9829             Check_Arg_Is_Local_Name (Arg1);
9830             E_Id := Get_Pragma_Arg (Arg1);
9831
9832             if Etype (E_Id) = Any_Type then
9833                return;
9834             end if;
9835
9836             E := Entity (E_Id);
9837
9838             --  Check duplicate before we chain ourselves!
9839
9840             Check_Duplicate_Pragma (E);
9841
9842             --  Check appropriate entity
9843
9844             if Rep_Item_Too_Early (E, N)
9845                  or else
9846                Rep_Item_Too_Late (E, N)
9847             then
9848                return;
9849             end if;
9850
9851             D := Declaration_Node (E);
9852             K := Nkind (D);
9853
9854             if (K = N_Full_Type_Declaration
9855                  and then (Is_Array_Type (E) or else Is_Record_Type (E)))
9856               or else
9857                 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
9858                    and then Nkind (D) = N_Object_Declaration
9859                    and then Nkind (Object_Definition (D)) =
9860                                        N_Constrained_Array_Definition)
9861             then
9862                Independence_Checks.Append ((N, E));
9863
9864             else
9865                Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
9866             end if;
9867          end Independent_Components;
9868
9869          ------------------------
9870          -- Initialize_Scalars --
9871          ------------------------
9872
9873          --  pragma Initialize_Scalars;
9874
9875          when Pragma_Initialize_Scalars =>
9876             GNAT_Pragma;
9877             Check_Arg_Count (0);
9878             Check_Valid_Configuration_Pragma;
9879             Check_Restriction (No_Initialize_Scalars, N);
9880
9881             --  Initialize_Scalars creates false positives in CodePeer, and
9882             --  incorrect negative results in Alfa mode, so ignore this pragma
9883             --  in these modes.
9884
9885             if not Restriction_Active (No_Initialize_Scalars)
9886               and then not (CodePeer_Mode or Alfa_Mode)
9887             then
9888                Init_Or_Norm_Scalars := True;
9889                Initialize_Scalars := True;
9890             end if;
9891
9892          ------------
9893          -- Inline --
9894          ------------
9895
9896          --  pragma Inline ( NAME {, NAME} );
9897
9898          when Pragma_Inline =>
9899
9900             --  Pragma is active if inlining option is active
9901
9902             Process_Inline (Inline_Active);
9903
9904          -------------------
9905          -- Inline_Always --
9906          -------------------
9907
9908          --  pragma Inline_Always ( NAME {, NAME} );
9909
9910          when Pragma_Inline_Always =>
9911             GNAT_Pragma;
9912
9913             --  Pragma always active unless in CodePeer or Alfa mode, since
9914             --  this causes walk order issues.
9915
9916             if not (CodePeer_Mode or Alfa_Mode) then
9917                Process_Inline (True);
9918             end if;
9919
9920          --------------------
9921          -- Inline_Generic --
9922          --------------------
9923
9924          --  pragma Inline_Generic (NAME {, NAME});
9925
9926          when Pragma_Inline_Generic =>
9927             GNAT_Pragma;
9928             Process_Generic_List;
9929
9930          ----------------------
9931          -- Inspection_Point --
9932          ----------------------
9933
9934          --  pragma Inspection_Point [(object_NAME {, object_NAME})];
9935
9936          when Pragma_Inspection_Point => Inspection_Point : declare
9937             Arg : Node_Id;
9938             Exp : Node_Id;
9939
9940          begin
9941             if Arg_Count > 0 then
9942                Arg := Arg1;
9943                loop
9944                   Exp := Get_Pragma_Arg (Arg);
9945                   Analyze (Exp);
9946
9947                   if not Is_Entity_Name (Exp)
9948                     or else not Is_Object (Entity (Exp))
9949                   then
9950                      Error_Pragma_Arg ("object name required", Arg);
9951                   end if;
9952
9953                   Next (Arg);
9954                   exit when No (Arg);
9955                end loop;
9956             end if;
9957          end Inspection_Point;
9958
9959          ---------------
9960          -- Interface --
9961          ---------------
9962
9963          --  pragma Interface (
9964          --    [   Convention    =>] convention_IDENTIFIER,
9965          --    [   Entity        =>] local_NAME
9966          --    [, [External_Name =>] static_string_EXPRESSION ]
9967          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
9968
9969          when Pragma_Interface =>
9970             GNAT_Pragma;
9971             Check_Arg_Order
9972               ((Name_Convention,
9973                 Name_Entity,
9974                 Name_External_Name,
9975                 Name_Link_Name));
9976             Check_At_Least_N_Arguments (2);
9977             Check_At_Most_N_Arguments  (4);
9978             Process_Import_Or_Interface;
9979
9980             --  In Ada 2005, the permission to use Interface (a reserved word)
9981             --  as a pragma name is considered an obsolescent feature.
9982
9983             if Ada_Version >= Ada_2005 then
9984                Check_Restriction
9985                  (No_Obsolescent_Features, Pragma_Identifier (N));
9986             end if;
9987
9988          --------------------
9989          -- Interface_Name --
9990          --------------------
9991
9992          --  pragma Interface_Name (
9993          --    [  Entity        =>] local_NAME
9994          --    [,[External_Name =>] static_string_EXPRESSION ]
9995          --    [,[Link_Name     =>] static_string_EXPRESSION ]);
9996
9997          when Pragma_Interface_Name => Interface_Name : declare
9998             Id     : Node_Id;
9999             Def_Id : Entity_Id;
10000             Hom_Id : Entity_Id;
10001             Found  : Boolean;
10002
10003          begin
10004             GNAT_Pragma;
10005             Check_Arg_Order
10006               ((Name_Entity, Name_External_Name, Name_Link_Name));
10007             Check_At_Least_N_Arguments (2);
10008             Check_At_Most_N_Arguments  (3);
10009             Id := Get_Pragma_Arg (Arg1);
10010             Analyze (Id);
10011
10012             if not Is_Entity_Name (Id) then
10013                Error_Pragma_Arg
10014                  ("first argument for pragma% must be entity name", Arg1);
10015             elsif Etype (Id) = Any_Type then
10016                return;
10017             else
10018                Def_Id := Entity (Id);
10019             end if;
10020
10021             --  Special DEC-compatible processing for the object case, forces
10022             --  object to be imported.
10023
10024             if Ekind (Def_Id) = E_Variable then
10025                Kill_Size_Check_Code (Def_Id);
10026                Note_Possible_Modification (Id, Sure => False);
10027
10028                --  Initialization is not allowed for imported variable
10029
10030                if Present (Expression (Parent (Def_Id)))
10031                  and then Comes_From_Source (Expression (Parent (Def_Id)))
10032                then
10033                   Error_Msg_Sloc := Sloc (Def_Id);
10034                   Error_Pragma_Arg
10035                     ("no initialization allowed for declaration of& #",
10036                      Arg2);
10037
10038                else
10039                   --  For compatibility, support VADS usage of providing both
10040                   --  pragmas Interface and Interface_Name to obtain the effect
10041                   --  of a single Import pragma.
10042
10043                   if Is_Imported (Def_Id)
10044                     and then Present (First_Rep_Item (Def_Id))
10045                     and then Nkind (First_Rep_Item (Def_Id)) = N_Pragma
10046                     and then
10047                       Pragma_Name (First_Rep_Item (Def_Id)) = Name_Interface
10048                   then
10049                      null;
10050                   else
10051                      Set_Imported (Def_Id);
10052                   end if;
10053
10054                   Set_Is_Public (Def_Id);
10055                   Process_Interface_Name (Def_Id, Arg2, Arg3);
10056                end if;
10057
10058             --  Otherwise must be subprogram
10059
10060             elsif not Is_Subprogram (Def_Id) then
10061                Error_Pragma_Arg
10062                  ("argument of pragma% is not subprogram", Arg1);
10063
10064             else
10065                Check_At_Most_N_Arguments (3);
10066                Hom_Id := Def_Id;
10067                Found := False;
10068
10069                --  Loop through homonyms
10070
10071                loop
10072                   Def_Id := Get_Base_Subprogram (Hom_Id);
10073
10074                   if Is_Imported (Def_Id) then
10075                      Process_Interface_Name (Def_Id, Arg2, Arg3);
10076                      Found := True;
10077                   end if;
10078
10079                   exit when From_Aspect_Specification (N);
10080                   Hom_Id := Homonym (Hom_Id);
10081
10082                   exit when No (Hom_Id)
10083                     or else Scope (Hom_Id) /= Current_Scope;
10084                end loop;
10085
10086                if not Found then
10087                   Error_Pragma_Arg
10088                     ("argument of pragma% is not imported subprogram",
10089                      Arg1);
10090                end if;
10091             end if;
10092          end Interface_Name;
10093
10094          -----------------------
10095          -- Interrupt_Handler --
10096          -----------------------
10097
10098          --  pragma Interrupt_Handler (handler_NAME);
10099
10100          when Pragma_Interrupt_Handler =>
10101             Check_Ada_83_Warning;
10102             Check_Arg_Count (1);
10103             Check_No_Identifiers;
10104
10105             if No_Run_Time_Mode then
10106                Error_Msg_CRT ("Interrupt_Handler pragma", N);
10107             else
10108                Check_Interrupt_Or_Attach_Handler;
10109                Process_Interrupt_Or_Attach_Handler;
10110             end if;
10111
10112          ------------------------
10113          -- Interrupt_Priority --
10114          ------------------------
10115
10116          --  pragma Interrupt_Priority [(EXPRESSION)];
10117
10118          when Pragma_Interrupt_Priority => Interrupt_Priority : declare
10119             P   : constant Node_Id := Parent (N);
10120             Arg : Node_Id;
10121
10122          begin
10123             Check_Ada_83_Warning;
10124
10125             if Arg_Count /= 0 then
10126                Arg := Get_Pragma_Arg (Arg1);
10127                Check_Arg_Count (1);
10128                Check_No_Identifiers;
10129
10130                --  The expression must be analyzed in the special manner
10131                --  described in "Handling of Default and Per-Object
10132                --  Expressions" in sem.ads.
10133
10134                Preanalyze_Spec_Expression (Arg, RTE (RE_Interrupt_Priority));
10135             end if;
10136
10137             if not Nkind_In (P, N_Task_Definition, N_Protected_Definition) then
10138                Pragma_Misplaced;
10139                return;
10140
10141             elsif Has_Pragma_Priority (P) then
10142                Error_Pragma ("duplicate pragma% not allowed");
10143
10144             else
10145                Set_Has_Pragma_Priority (P, True);
10146                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
10147             end if;
10148          end Interrupt_Priority;
10149
10150          ---------------------
10151          -- Interrupt_State --
10152          ---------------------
10153
10154          --  pragma Interrupt_State (
10155          --    [Name  =>] INTERRUPT_ID,
10156          --    [State =>] INTERRUPT_STATE);
10157
10158          --  INTERRUPT_ID => IDENTIFIER | static_integer_EXPRESSION
10159          --  INTERRUPT_STATE => System | Runtime | User
10160
10161          --  Note: if the interrupt id is given as an identifier, then it must
10162          --  be one of the identifiers in Ada.Interrupts.Names. Otherwise it is
10163          --  given as a static integer expression which must be in the range of
10164          --  Ada.Interrupts.Interrupt_ID.
10165
10166          when Pragma_Interrupt_State => Interrupt_State : declare
10167
10168             Int_Id : constant Entity_Id := RTE (RE_Interrupt_ID);
10169             --  This is the entity Ada.Interrupts.Interrupt_ID;
10170
10171             State_Type : Character;
10172             --  Set to 's'/'r'/'u' for System/Runtime/User
10173
10174             IST_Num : Pos;
10175             --  Index to entry in Interrupt_States table
10176
10177             Int_Val : Uint;
10178             --  Value of interrupt
10179
10180             Arg1X : constant Node_Id := Get_Pragma_Arg (Arg1);
10181             --  The first argument to the pragma
10182
10183             Int_Ent : Entity_Id;
10184             --  Interrupt entity in Ada.Interrupts.Names
10185
10186          begin
10187             GNAT_Pragma;
10188             Check_Arg_Order ((Name_Name, Name_State));
10189             Check_Arg_Count (2);
10190
10191             Check_Optional_Identifier (Arg1, Name_Name);
10192             Check_Optional_Identifier (Arg2, Name_State);
10193             Check_Arg_Is_Identifier (Arg2);
10194
10195             --  First argument is identifier
10196
10197             if Nkind (Arg1X) = N_Identifier then
10198
10199                --  Search list of names in Ada.Interrupts.Names
10200
10201                Int_Ent := First_Entity (RTE (RE_Names));
10202                loop
10203                   if No (Int_Ent) then
10204                      Error_Pragma_Arg ("invalid interrupt name", Arg1);
10205
10206                   elsif Chars (Int_Ent) = Chars (Arg1X) then
10207                      Int_Val := Expr_Value (Constant_Value (Int_Ent));
10208                      exit;
10209                   end if;
10210
10211                   Next_Entity (Int_Ent);
10212                end loop;
10213
10214             --  First argument is not an identifier, so it must be a static
10215             --  expression of type Ada.Interrupts.Interrupt_ID.
10216
10217             else
10218                Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
10219                Int_Val := Expr_Value (Arg1X);
10220
10221                if Int_Val < Expr_Value (Type_Low_Bound (Int_Id))
10222                     or else
10223                   Int_Val > Expr_Value (Type_High_Bound (Int_Id))
10224                then
10225                   Error_Pragma_Arg
10226                     ("value not in range of type " &
10227                      """Ada.Interrupts.Interrupt_'I'D""", Arg1);
10228                end if;
10229             end if;
10230
10231             --  Check OK state
10232
10233             case Chars (Get_Pragma_Arg (Arg2)) is
10234                when Name_Runtime => State_Type := 'r';
10235                when Name_System  => State_Type := 's';
10236                when Name_User    => State_Type := 'u';
10237
10238                when others =>
10239                   Error_Pragma_Arg ("invalid interrupt state", Arg2);
10240             end case;
10241
10242             --  Check if entry is already stored
10243
10244             IST_Num := Interrupt_States.First;
10245             loop
10246                --  If entry not found, add it
10247
10248                if IST_Num > Interrupt_States.Last then
10249                   Interrupt_States.Append
10250                     ((Interrupt_Number => UI_To_Int (Int_Val),
10251                       Interrupt_State  => State_Type,
10252                       Pragma_Loc       => Loc));
10253                   exit;
10254
10255                --  Case of entry for the same entry
10256
10257                elsif Int_Val = Interrupt_States.Table (IST_Num).
10258                                                            Interrupt_Number
10259                then
10260                   --  If state matches, done, no need to make redundant entry
10261
10262                   exit when
10263                     State_Type = Interrupt_States.Table (IST_Num).
10264                                                            Interrupt_State;
10265
10266                   --  Otherwise if state does not match, error
10267
10268                   Error_Msg_Sloc :=
10269                     Interrupt_States.Table (IST_Num).Pragma_Loc;
10270                   Error_Pragma_Arg
10271                     ("state conflicts with that given #", Arg2);
10272                   exit;
10273                end if;
10274
10275                IST_Num := IST_Num + 1;
10276             end loop;
10277          end Interrupt_State;
10278
10279          ---------------
10280          -- Invariant --
10281          ---------------
10282
10283          --  pragma Invariant
10284          --    ([Entity =>]    type_LOCAL_NAME,
10285          --     [Check  =>]    EXPRESSION
10286          --     [,[Message =>] String_Expression]);
10287
10288          when Pragma_Invariant => Invariant : declare
10289             Type_Id : Node_Id;
10290             Typ     : Entity_Id;
10291
10292             Discard : Boolean;
10293             pragma Unreferenced (Discard);
10294
10295          begin
10296             GNAT_Pragma;
10297             Check_At_Least_N_Arguments (2);
10298             Check_At_Most_N_Arguments (3);
10299             Check_Optional_Identifier (Arg1, Name_Entity);
10300             Check_Optional_Identifier (Arg2, Name_Check);
10301
10302             if Arg_Count = 3 then
10303                Check_Optional_Identifier (Arg3, Name_Message);
10304                Check_Arg_Is_Static_Expression (Arg3, Standard_String);
10305             end if;
10306
10307             Check_Arg_Is_Local_Name (Arg1);
10308
10309             Type_Id := Get_Pragma_Arg (Arg1);
10310             Find_Type (Type_Id);
10311             Typ := Entity (Type_Id);
10312
10313             if Typ = Any_Type then
10314                return;
10315
10316             --  An invariant must apply to a private type, or appear in the
10317             --  private part of a package spec and apply to a completion.
10318
10319             elsif Ekind_In (Typ, E_Private_Type,
10320                                  E_Record_Type_With_Private,
10321                                  E_Limited_Private_Type)
10322             then
10323                null;
10324
10325             elsif In_Private_Part (Current_Scope)
10326               and then Has_Private_Declaration (Typ)
10327             then
10328                null;
10329
10330             elsif In_Private_Part (Current_Scope) then
10331                Error_Pragma_Arg
10332                  ("pragma% only allowed for private type " &
10333                   "declared in visible part", Arg1);
10334
10335             else
10336                Error_Pragma_Arg
10337                  ("pragma% only allowed for private type", Arg1);
10338             end if;
10339
10340             --  Note that the type has at least one invariant, and also that
10341             --  it has inheritable invariants if we have Invariant'Class.
10342
10343             Set_Has_Invariants (Typ);
10344
10345             if Class_Present (N) then
10346                Set_Has_Inheritable_Invariants (Typ);
10347             end if;
10348
10349             --  The remaining processing is simply to link the pragma on to
10350             --  the rep item chain, for processing when the type is frozen.
10351             --  This is accomplished by a call to Rep_Item_Too_Late.
10352
10353             Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
10354          end Invariant;
10355
10356          ----------------------
10357          -- Java_Constructor --
10358          ----------------------
10359
10360          --  pragma Java_Constructor ([Entity =>] LOCAL_NAME);
10361
10362          --  Also handles pragma CIL_Constructor
10363
10364          when Pragma_CIL_Constructor | Pragma_Java_Constructor =>
10365          Java_Constructor : declare
10366             Convention  : Convention_Id;
10367             Def_Id      : Entity_Id;
10368             Hom_Id      : Entity_Id;
10369             Id          : Entity_Id;
10370             This_Formal : Entity_Id;
10371
10372          begin
10373             GNAT_Pragma;
10374             Check_Arg_Count (1);
10375             Check_Optional_Identifier (Arg1, Name_Entity);
10376             Check_Arg_Is_Local_Name (Arg1);
10377
10378             Id := Get_Pragma_Arg (Arg1);
10379             Find_Program_Unit_Name (Id);
10380
10381             --  If we did not find the name, we are done
10382
10383             if Etype (Id) = Any_Type then
10384                return;
10385             end if;
10386
10387             --  Check wrong use of pragma in wrong VM target
10388
10389             if VM_Target = No_VM then
10390                return;
10391
10392             elsif VM_Target = CLI_Target
10393               and then Prag_Id = Pragma_Java_Constructor
10394             then
10395                Error_Pragma ("must use pragma 'C'I'L_'Constructor");
10396
10397             elsif VM_Target = JVM_Target
10398               and then Prag_Id = Pragma_CIL_Constructor
10399             then
10400                Error_Pragma ("must use pragma 'Java_'Constructor");
10401             end if;
10402
10403             case Prag_Id is
10404                when Pragma_CIL_Constructor  => Convention := Convention_CIL;
10405                when Pragma_Java_Constructor => Convention := Convention_Java;
10406                when others                  => null;
10407             end case;
10408
10409             Hom_Id := Entity (Id);
10410
10411             --  Loop through homonyms
10412
10413             loop
10414                Def_Id := Get_Base_Subprogram (Hom_Id);
10415
10416                --  The constructor is required to be a function
10417
10418                if Ekind (Def_Id) /= E_Function then
10419                   if VM_Target = JVM_Target then
10420                      Error_Pragma_Arg
10421                        ("pragma% requires function returning a " &
10422                         "'Java access type", Def_Id);
10423                   else
10424                      Error_Pragma_Arg
10425                        ("pragma% requires function returning a " &
10426                         "'C'I'L access type", Def_Id);
10427                   end if;
10428                end if;
10429
10430                --  Check arguments: For tagged type the first formal must be
10431                --  named "this" and its type must be a named access type
10432                --  designating a class-wide tagged type that has convention
10433                --  CIL/Java. The first formal must also have a null default
10434                --  value. For example:
10435
10436                --      type Typ is tagged ...
10437                --      type Ref is access all Typ;
10438                --      pragma Convention (CIL, Typ);
10439
10440                --      function New_Typ (This : Ref) return Ref;
10441                --      function New_Typ (This : Ref; I : Integer) return Ref;
10442                --      pragma Cil_Constructor (New_Typ);
10443
10444                --  Reason: The first formal must NOT be a primitive of the
10445                --  tagged type.
10446
10447                --  This rule also applies to constructors of delegates used
10448                --  to interface with standard target libraries. For example:
10449
10450                --      type Delegate is access procedure ...
10451                --      pragma Import (CIL, Delegate, ...);
10452
10453                --      function new_Delegate
10454                --        (This : Delegate := null; ... ) return Delegate;
10455
10456                --  For value-types this rule does not apply.
10457
10458                if not Is_Value_Type (Etype (Def_Id)) then
10459                   if No (First_Formal (Def_Id)) then
10460                      Error_Msg_Name_1 := Pname;
10461                      Error_Msg_N ("% function must have parameters", Def_Id);
10462                      return;
10463                   end if;
10464
10465                   --  In the JRE library we have several occurrences in which
10466                   --  the "this" parameter is not the first formal.
10467
10468                   This_Formal := First_Formal (Def_Id);
10469
10470                   --  In the JRE library we have several occurrences in which
10471                   --  the "this" parameter is not the first formal. Search for
10472                   --  it.
10473
10474                   if VM_Target = JVM_Target then
10475                      while Present (This_Formal)
10476                        and then Get_Name_String (Chars (This_Formal)) /= "this"
10477                      loop
10478                         Next_Formal (This_Formal);
10479                      end loop;
10480
10481                      if No (This_Formal) then
10482                         This_Formal := First_Formal (Def_Id);
10483                      end if;
10484                   end if;
10485
10486                   --  Warning: The first parameter should be named "this".
10487                   --  We temporarily allow it because we have the following
10488                   --  case in the Java runtime (file s-osinte.ads) ???
10489
10490                   --    function new_Thread
10491                   --      (Self_Id : System.Address) return Thread_Id;
10492                   --    pragma Java_Constructor (new_Thread);
10493
10494                   if VM_Target = JVM_Target
10495                     and then Get_Name_String (Chars (First_Formal (Def_Id)))
10496                                = "self_id"
10497                     and then Etype (First_Formal (Def_Id)) = RTE (RE_Address)
10498                   then
10499                      null;
10500
10501                   elsif Get_Name_String (Chars (This_Formal)) /= "this" then
10502                      Error_Msg_Name_1 := Pname;
10503                      Error_Msg_N
10504                        ("first formal of % function must be named `this`",
10505                         Parent (This_Formal));
10506
10507                   elsif not Is_Access_Type (Etype (This_Formal)) then
10508                      Error_Msg_Name_1 := Pname;
10509                      Error_Msg_N
10510                        ("first formal of % function must be an access type",
10511                         Parameter_Type (Parent (This_Formal)));
10512
10513                   --  For delegates the type of the first formal must be a
10514                   --  named access-to-subprogram type (see previous example)
10515
10516                   elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type
10517                     and then Ekind (Etype (This_Formal))
10518                                /= E_Access_Subprogram_Type
10519                   then
10520                      Error_Msg_Name_1 := Pname;
10521                      Error_Msg_N
10522                        ("first formal of % function must be a named access" &
10523                         " to subprogram type",
10524                         Parameter_Type (Parent (This_Formal)));
10525
10526                   --  Warning: We should reject anonymous access types because
10527                   --  the constructor must not be handled as a primitive of the
10528                   --  tagged type. We temporarily allow it because this profile
10529                   --  is currently generated by cil2ada???
10530
10531                   elsif Ekind (Etype (Def_Id)) /= E_Access_Subprogram_Type
10532                     and then not Ekind_In (Etype (This_Formal),
10533                                              E_Access_Type,
10534                                              E_General_Access_Type,
10535                                              E_Anonymous_Access_Type)
10536                   then
10537                      Error_Msg_Name_1 := Pname;
10538                      Error_Msg_N
10539                        ("first formal of % function must be a named access" &
10540                         " type",
10541                         Parameter_Type (Parent (This_Formal)));
10542
10543                   elsif Atree.Convention
10544                          (Designated_Type (Etype (This_Formal))) /= Convention
10545                   then
10546                      Error_Msg_Name_1 := Pname;
10547
10548                      if Convention = Convention_Java then
10549                         Error_Msg_N
10550                           ("pragma% requires convention 'Cil in designated" &
10551                            " type",
10552                            Parameter_Type (Parent (This_Formal)));
10553                      else
10554                         Error_Msg_N
10555                           ("pragma% requires convention 'Java in designated" &
10556                            " type",
10557                            Parameter_Type (Parent (This_Formal)));
10558                      end if;
10559
10560                   elsif No (Expression (Parent (This_Formal)))
10561                     or else Nkind (Expression (Parent (This_Formal))) /= N_Null
10562                   then
10563                      Error_Msg_Name_1 := Pname;
10564                      Error_Msg_N
10565                        ("pragma% requires first formal with default `null`",
10566                         Parameter_Type (Parent (This_Formal)));
10567                   end if;
10568                end if;
10569
10570                --  Check result type: the constructor must be a function
10571                --  returning:
10572                --   * a value type (only allowed in the CIL compiler)
10573                --   * an access-to-subprogram type with convention Java/CIL
10574                --   * an access-type designating a type that has convention
10575                --     Java/CIL.
10576
10577                if Is_Value_Type (Etype (Def_Id)) then
10578                   null;
10579
10580                --  Access-to-subprogram type with convention Java/CIL
10581
10582                elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type then
10583                   if Atree.Convention (Etype (Def_Id)) /= Convention then
10584                      if Convention = Convention_Java then
10585                         Error_Pragma_Arg
10586                           ("pragma% requires function returning a " &
10587                            "'Java access type", Arg1);
10588                      else
10589                         pragma Assert (Convention = Convention_CIL);
10590                         Error_Pragma_Arg
10591                           ("pragma% requires function returning a " &
10592                            "'C'I'L access type", Arg1);
10593                      end if;
10594                   end if;
10595
10596                elsif Ekind (Etype (Def_Id)) in Access_Kind then
10597                   if not Ekind_In (Etype (Def_Id), E_Access_Type,
10598                                                    E_General_Access_Type)
10599                     or else
10600                       Atree.Convention
10601                         (Designated_Type (Etype (Def_Id))) /= Convention
10602                   then
10603                      Error_Msg_Name_1 := Pname;
10604
10605                      if Convention = Convention_Java then
10606                         Error_Pragma_Arg
10607                           ("pragma% requires function returning a named" &
10608                            "'Java access type", Arg1);
10609                      else
10610                         Error_Pragma_Arg
10611                           ("pragma% requires function returning a named" &
10612                            "'C'I'L access type", Arg1);
10613                      end if;
10614                   end if;
10615                end if;
10616
10617                Set_Is_Constructor (Def_Id);
10618                Set_Convention     (Def_Id, Convention);
10619                Set_Is_Imported    (Def_Id);
10620
10621                exit when From_Aspect_Specification (N);
10622                Hom_Id := Homonym (Hom_Id);
10623
10624                exit when No (Hom_Id) or else Scope (Hom_Id) /= Current_Scope;
10625             end loop;
10626          end Java_Constructor;
10627
10628          ----------------------
10629          -- Java_Interface --
10630          ----------------------
10631
10632          --  pragma Java_Interface ([Entity =>] LOCAL_NAME);
10633
10634          when Pragma_Java_Interface => Java_Interface : declare
10635             Arg : Node_Id;
10636             Typ : Entity_Id;
10637
10638          begin
10639             GNAT_Pragma;
10640             Check_Arg_Count (1);
10641             Check_Optional_Identifier (Arg1, Name_Entity);
10642             Check_Arg_Is_Local_Name (Arg1);
10643
10644             Arg := Get_Pragma_Arg (Arg1);
10645             Analyze (Arg);
10646
10647             if Etype (Arg) = Any_Type then
10648                return;
10649             end if;
10650
10651             if not Is_Entity_Name (Arg)
10652               or else not Is_Type (Entity (Arg))
10653             then
10654                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
10655             end if;
10656
10657             Typ := Underlying_Type (Entity (Arg));
10658
10659             --  For now simply check some of the semantic constraints on the
10660             --  type. This currently leaves out some restrictions on interface
10661             --  types, namely that the parent type must be java.lang.Object.Typ
10662             --  and that all primitives of the type should be declared
10663             --  abstract. ???
10664
10665             if not Is_Tagged_Type (Typ) or else not Is_Abstract_Type (Typ) then
10666                Error_Pragma_Arg ("pragma% requires an abstract "
10667                  & "tagged type", Arg1);
10668
10669             elsif not Has_Discriminants (Typ)
10670               or else Ekind (Etype (First_Discriminant (Typ)))
10671                         /= E_Anonymous_Access_Type
10672               or else
10673                 not Is_Class_Wide_Type
10674                       (Designated_Type (Etype (First_Discriminant (Typ))))
10675             then
10676                Error_Pragma_Arg
10677                  ("type must have a class-wide access discriminant", Arg1);
10678             end if;
10679          end Java_Interface;
10680
10681          ----------------
10682          -- Keep_Names --
10683          ----------------
10684
10685          --  pragma Keep_Names ([On => ] local_NAME);
10686
10687          when Pragma_Keep_Names => Keep_Names : declare
10688             Arg : Node_Id;
10689
10690          begin
10691             GNAT_Pragma;
10692             Check_Arg_Count (1);
10693             Check_Optional_Identifier (Arg1, Name_On);
10694             Check_Arg_Is_Local_Name (Arg1);
10695
10696             Arg := Get_Pragma_Arg (Arg1);
10697             Analyze (Arg);
10698
10699             if Etype (Arg) = Any_Type then
10700                return;
10701             end if;
10702
10703             if not Is_Entity_Name (Arg)
10704               or else Ekind (Entity (Arg)) /= E_Enumeration_Type
10705             then
10706                Error_Pragma_Arg
10707                  ("pragma% requires a local enumeration type", Arg1);
10708             end if;
10709
10710             Set_Discard_Names (Entity (Arg), False);
10711          end Keep_Names;
10712
10713          -------------
10714          -- License --
10715          -------------
10716
10717          --  pragma License (RESTRICTED | UNRESTRICTED | GPL | MODIFIED_GPL);
10718
10719          when Pragma_License =>
10720             GNAT_Pragma;
10721             Check_Arg_Count (1);
10722             Check_No_Identifiers;
10723             Check_Valid_Configuration_Pragma;
10724             Check_Arg_Is_Identifier (Arg1);
10725
10726             declare
10727                Sind : constant Source_File_Index :=
10728                         Source_Index (Current_Sem_Unit);
10729
10730             begin
10731                case Chars (Get_Pragma_Arg (Arg1)) is
10732                   when Name_GPL =>
10733                      Set_License (Sind, GPL);
10734
10735                   when Name_Modified_GPL =>
10736                      Set_License (Sind, Modified_GPL);
10737
10738                   when Name_Restricted =>
10739                      Set_License (Sind, Restricted);
10740
10741                   when Name_Unrestricted =>
10742                      Set_License (Sind, Unrestricted);
10743
10744                   when others =>
10745                      Error_Pragma_Arg ("invalid license name", Arg1);
10746                end case;
10747             end;
10748
10749          ---------------
10750          -- Link_With --
10751          ---------------
10752
10753          --  pragma Link_With (string_EXPRESSION {, string_EXPRESSION});
10754
10755          when Pragma_Link_With => Link_With : declare
10756             Arg : Node_Id;
10757
10758          begin
10759             GNAT_Pragma;
10760
10761             if Operating_Mode = Generate_Code
10762               and then In_Extended_Main_Source_Unit (N)
10763             then
10764                Check_At_Least_N_Arguments (1);
10765                Check_No_Identifiers;
10766                Check_Is_In_Decl_Part_Or_Package_Spec;
10767                Check_Arg_Is_Static_Expression (Arg1, Standard_String);
10768                Start_String;
10769
10770                Arg := Arg1;
10771                while Present (Arg) loop
10772                   Check_Arg_Is_Static_Expression (Arg, Standard_String);
10773
10774                   --  Store argument, converting sequences of spaces to a
10775                   --  single null character (this is one of the differences
10776                   --  in processing between Link_With and Linker_Options).
10777
10778                   Arg_Store : declare
10779                      C : constant Char_Code := Get_Char_Code (' ');
10780                      S : constant String_Id :=
10781                            Strval (Expr_Value_S (Get_Pragma_Arg (Arg)));
10782                      L : constant Nat := String_Length (S);
10783                      F : Nat := 1;
10784
10785                      procedure Skip_Spaces;
10786                      --  Advance F past any spaces
10787
10788                      -----------------
10789                      -- Skip_Spaces --
10790                      -----------------
10791
10792                      procedure Skip_Spaces is
10793                      begin
10794                         while F <= L and then Get_String_Char (S, F) = C loop
10795                            F := F + 1;
10796                         end loop;
10797                      end Skip_Spaces;
10798
10799                   --  Start of processing for Arg_Store
10800
10801                   begin
10802                      Skip_Spaces; -- skip leading spaces
10803
10804                      --  Loop through characters, changing any embedded
10805                      --  sequence of spaces to a single null character (this
10806                      --  is how Link_With/Linker_Options differ)
10807
10808                      while F <= L loop
10809                         if Get_String_Char (S, F) = C then
10810                            Skip_Spaces;
10811                            exit when F > L;
10812                            Store_String_Char (ASCII.NUL);
10813
10814                         else
10815                            Store_String_Char (Get_String_Char (S, F));
10816                            F := F + 1;
10817                         end if;
10818                      end loop;
10819                   end Arg_Store;
10820
10821                   Arg := Next (Arg);
10822
10823                   if Present (Arg) then
10824                      Store_String_Char (ASCII.NUL);
10825                   end if;
10826                end loop;
10827
10828                Store_Linker_Option_String (End_String);
10829             end if;
10830          end Link_With;
10831
10832          ------------------
10833          -- Linker_Alias --
10834          ------------------
10835
10836          --  pragma Linker_Alias (
10837          --      [Entity =>]  LOCAL_NAME
10838          --      [Target =>]  static_string_EXPRESSION);
10839
10840          when Pragma_Linker_Alias =>
10841             GNAT_Pragma;
10842             Check_Arg_Order ((Name_Entity, Name_Target));
10843             Check_Arg_Count (2);
10844             Check_Optional_Identifier (Arg1, Name_Entity);
10845             Check_Optional_Identifier (Arg2, Name_Target);
10846             Check_Arg_Is_Library_Level_Local_Name (Arg1);
10847             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10848
10849             --  The only processing required is to link this item on to the
10850             --  list of rep items for the given entity. This is accomplished
10851             --  by the call to Rep_Item_Too_Late (when no error is detected
10852             --  and False is returned).
10853
10854             if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
10855                return;
10856             else
10857                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10858             end if;
10859
10860          ------------------------
10861          -- Linker_Constructor --
10862          ------------------------
10863
10864          --  pragma Linker_Constructor (procedure_LOCAL_NAME);
10865
10866          --  Code is shared with Linker_Destructor
10867
10868          -----------------------
10869          -- Linker_Destructor --
10870          -----------------------
10871
10872          --  pragma Linker_Destructor (procedure_LOCAL_NAME);
10873
10874          when Pragma_Linker_Constructor |
10875               Pragma_Linker_Destructor =>
10876          Linker_Constructor : declare
10877             Arg1_X : Node_Id;
10878             Proc   : Entity_Id;
10879
10880          begin
10881             GNAT_Pragma;
10882             Check_Arg_Count (1);
10883             Check_No_Identifiers;
10884             Check_Arg_Is_Local_Name (Arg1);
10885             Arg1_X := Get_Pragma_Arg (Arg1);
10886             Analyze (Arg1_X);
10887             Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
10888
10889             if not Is_Library_Level_Entity (Proc) then
10890                Error_Pragma_Arg
10891                 ("argument for pragma% must be library level entity", Arg1);
10892             end if;
10893
10894             --  The only processing required is to link this item on to the
10895             --  list of rep items for the given entity. This is accomplished
10896             --  by the call to Rep_Item_Too_Late (when no error is detected
10897             --  and False is returned).
10898
10899             if Rep_Item_Too_Late (Proc, N) then
10900                return;
10901             else
10902                Set_Has_Gigi_Rep_Item (Proc);
10903             end if;
10904          end Linker_Constructor;
10905
10906          --------------------
10907          -- Linker_Options --
10908          --------------------
10909
10910          --  pragma Linker_Options (string_EXPRESSION {, string_EXPRESSION});
10911
10912          when Pragma_Linker_Options => Linker_Options : declare
10913             Arg : Node_Id;
10914
10915          begin
10916             Check_Ada_83_Warning;
10917             Check_No_Identifiers;
10918             Check_Arg_Count (1);
10919             Check_Is_In_Decl_Part_Or_Package_Spec;
10920             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
10921             Start_String (Strval (Expr_Value_S (Get_Pragma_Arg (Arg1))));
10922
10923             Arg := Arg2;
10924             while Present (Arg) loop
10925                Check_Arg_Is_Static_Expression (Arg, Standard_String);
10926                Store_String_Char (ASCII.NUL);
10927                Store_String_Chars
10928                  (Strval (Expr_Value_S (Get_Pragma_Arg (Arg))));
10929                Arg := Next (Arg);
10930             end loop;
10931
10932             if Operating_Mode = Generate_Code
10933               and then In_Extended_Main_Source_Unit (N)
10934             then
10935                Store_Linker_Option_String (End_String);
10936             end if;
10937          end Linker_Options;
10938
10939          --------------------
10940          -- Linker_Section --
10941          --------------------
10942
10943          --  pragma Linker_Section (
10944          --      [Entity  =>]  LOCAL_NAME
10945          --      [Section =>]  static_string_EXPRESSION);
10946
10947          when Pragma_Linker_Section =>
10948             GNAT_Pragma;
10949             Check_Arg_Order ((Name_Entity, Name_Section));
10950             Check_Arg_Count (2);
10951             Check_Optional_Identifier (Arg1, Name_Entity);
10952             Check_Optional_Identifier (Arg2, Name_Section);
10953             Check_Arg_Is_Library_Level_Local_Name (Arg1);
10954             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10955
10956             --  This pragma applies only to objects
10957
10958             if not Is_Object (Entity (Get_Pragma_Arg (Arg1))) then
10959                Error_Pragma_Arg ("pragma% applies only to objects", Arg1);
10960             end if;
10961
10962             --  The only processing required is to link this item on to the
10963             --  list of rep items for the given entity. This is accomplished
10964             --  by the call to Rep_Item_Too_Late (when no error is detected
10965             --  and False is returned).
10966
10967             if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
10968                return;
10969             else
10970                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10971             end if;
10972
10973          ----------
10974          -- List --
10975          ----------
10976
10977          --  pragma List (On | Off)
10978
10979          --  There is nothing to do here, since we did all the processing for
10980          --  this pragma in Par.Prag (so that it works properly even in syntax
10981          --  only mode).
10982
10983          when Pragma_List =>
10984             null;
10985
10986          --------------------
10987          -- Locking_Policy --
10988          --------------------
10989
10990          --  pragma Locking_Policy (policy_IDENTIFIER);
10991
10992          when Pragma_Locking_Policy => declare
10993             subtype LP_Range is Name_Id
10994               range First_Locking_Policy_Name .. Last_Locking_Policy_Name;
10995             LP_Val : LP_Range;
10996             LP     : Character;
10997          begin
10998             Check_Ada_83_Warning;
10999             Check_Arg_Count (1);
11000             Check_No_Identifiers;
11001             Check_Arg_Is_Locking_Policy (Arg1);
11002             Check_Valid_Configuration_Pragma;
11003             LP_Val := Chars (Get_Pragma_Arg (Arg1));
11004
11005             case LP_Val is
11006                when Name_Ceiling_Locking            => LP := 'C';
11007                when Name_Inheritance_Locking        => LP := 'I';
11008                when Name_Concurrent_Readers_Locking => LP := 'R';
11009             end case;
11010
11011             if Locking_Policy /= ' '
11012               and then Locking_Policy /= LP
11013             then
11014                Error_Msg_Sloc := Locking_Policy_Sloc;
11015                Error_Pragma ("locking policy incompatible with policy#");
11016
11017             --  Set new policy, but always preserve System_Location since we
11018             --  like the error message with the run time name.
11019
11020             else
11021                Locking_Policy := LP;
11022
11023                if Locking_Policy_Sloc /= System_Location then
11024                   Locking_Policy_Sloc := Loc;
11025                end if;
11026             end if;
11027          end;
11028
11029          ----------------
11030          -- Long_Float --
11031          ----------------
11032
11033          --  pragma Long_Float (D_Float | G_Float);
11034
11035          when Pragma_Long_Float => Long_Float : declare
11036          begin
11037             GNAT_Pragma;
11038             Check_Valid_Configuration_Pragma;
11039             Check_Arg_Count (1);
11040             Check_No_Identifier (Arg1);
11041             Check_Arg_Is_One_Of (Arg1, Name_D_Float, Name_G_Float);
11042
11043             if not OpenVMS_On_Target then
11044                Error_Pragma ("?pragma% ignored (applies only to Open'V'M'S)");
11045             end if;
11046
11047             --  D_Float case
11048
11049             if Chars (Get_Pragma_Arg (Arg1)) = Name_D_Float then
11050                if Opt.Float_Format_Long = 'G' then
11051                   Error_Pragma_Arg
11052                     ("G_Float previously specified", Arg1);
11053
11054                elsif Current_Sem_Unit /= Main_Unit
11055                  and then Opt.Float_Format_Long /= 'D'
11056                then
11057                   Error_Pragma_Arg
11058                     ("main unit not compiled with pragma Long_Float (D_Float)",
11059                      "\pragma% must be used consistently for whole partition",
11060                      Arg1);
11061
11062                else
11063                   Opt.Float_Format_Long := 'D';
11064                end if;
11065
11066             --  G_Float case (this is the default, does not need overriding)
11067
11068             else
11069                if Opt.Float_Format_Long = 'D' then
11070                   Error_Pragma ("D_Float previously specified");
11071
11072                elsif Current_Sem_Unit /= Main_Unit
11073                  and then Opt.Float_Format_Long /= 'G'
11074                then
11075                   Error_Pragma_Arg
11076                     ("main unit not compiled with pragma Long_Float (G_Float)",
11077                      "\pragma% must be used consistently for whole partition",
11078                      Arg1);
11079
11080                else
11081                   Opt.Float_Format_Long := 'G';
11082                end if;
11083             end if;
11084
11085             Set_Standard_Fpt_Formats;
11086          end Long_Float;
11087
11088          -----------------------
11089          -- Machine_Attribute --
11090          -----------------------
11091
11092          --  pragma Machine_Attribute (
11093          --       [Entity         =>] LOCAL_NAME,
11094          --       [Attribute_Name =>] static_string_EXPRESSION
11095          --    [, [Info           =>] static_EXPRESSION] );
11096
11097          when Pragma_Machine_Attribute => Machine_Attribute : declare
11098             Def_Id : Entity_Id;
11099
11100          begin
11101             GNAT_Pragma;
11102             Check_Arg_Order ((Name_Entity, Name_Attribute_Name, Name_Info));
11103
11104             if Arg_Count = 3 then
11105                Check_Optional_Identifier (Arg3, Name_Info);
11106                Check_Arg_Is_Static_Expression (Arg3);
11107             else
11108                Check_Arg_Count (2);
11109             end if;
11110
11111             Check_Optional_Identifier (Arg1, Name_Entity);
11112             Check_Optional_Identifier (Arg2, Name_Attribute_Name);
11113             Check_Arg_Is_Local_Name (Arg1);
11114             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
11115             Def_Id := Entity (Get_Pragma_Arg (Arg1));
11116
11117             if Is_Access_Type (Def_Id) then
11118                Def_Id := Designated_Type (Def_Id);
11119             end if;
11120
11121             if Rep_Item_Too_Early (Def_Id, N) then
11122                return;
11123             end if;
11124
11125             Def_Id := Underlying_Type (Def_Id);
11126
11127             --  The only processing required is to link this item on to the
11128             --  list of rep items for the given entity. This is accomplished
11129             --  by the call to Rep_Item_Too_Late (when no error is detected
11130             --  and False is returned).
11131
11132             if Rep_Item_Too_Late (Def_Id, N) then
11133                return;
11134             else
11135                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
11136             end if;
11137          end Machine_Attribute;
11138
11139          ----------
11140          -- Main --
11141          ----------
11142
11143          --  pragma Main
11144          --   (MAIN_OPTION [, MAIN_OPTION]);
11145
11146          --  MAIN_OPTION ::=
11147          --    [STACK_SIZE              =>] static_integer_EXPRESSION
11148          --  | [TASK_STACK_SIZE_DEFAULT =>] static_integer_EXPRESSION
11149          --  | [TIME_SLICING_ENABLED    =>] static_boolean_EXPRESSION
11150
11151          when Pragma_Main => Main : declare
11152             Args  : Args_List (1 .. 3);
11153             Names : constant Name_List (1 .. 3) := (
11154                       Name_Stack_Size,
11155                       Name_Task_Stack_Size_Default,
11156                       Name_Time_Slicing_Enabled);
11157
11158             Nod : Node_Id;
11159
11160          begin
11161             GNAT_Pragma;
11162             Gather_Associations (Names, Args);
11163
11164             for J in 1 .. 2 loop
11165                if Present (Args (J)) then
11166                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
11167                end if;
11168             end loop;
11169
11170             if Present (Args (3)) then
11171                Check_Arg_Is_Static_Expression (Args (3), Standard_Boolean);
11172             end if;
11173
11174             Nod := Next (N);
11175             while Present (Nod) loop
11176                if Nkind (Nod) = N_Pragma
11177                  and then Pragma_Name (Nod) = Name_Main
11178                then
11179                   Error_Msg_Name_1 := Pname;
11180                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
11181                end if;
11182
11183                Next (Nod);
11184             end loop;
11185          end Main;
11186
11187          ------------------
11188          -- Main_Storage --
11189          ------------------
11190
11191          --  pragma Main_Storage
11192          --   (MAIN_STORAGE_OPTION [, MAIN_STORAGE_OPTION]);
11193
11194          --  MAIN_STORAGE_OPTION ::=
11195          --    [WORKING_STORAGE =>] static_SIMPLE_EXPRESSION
11196          --  | [TOP_GUARD =>] static_SIMPLE_EXPRESSION
11197
11198          when Pragma_Main_Storage => Main_Storage : declare
11199             Args  : Args_List (1 .. 2);
11200             Names : constant Name_List (1 .. 2) := (
11201                       Name_Working_Storage,
11202                       Name_Top_Guard);
11203
11204             Nod : Node_Id;
11205
11206          begin
11207             GNAT_Pragma;
11208             Gather_Associations (Names, Args);
11209
11210             for J in 1 .. 2 loop
11211                if Present (Args (J)) then
11212                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
11213                end if;
11214             end loop;
11215
11216             Check_In_Main_Program;
11217
11218             Nod := Next (N);
11219             while Present (Nod) loop
11220                if Nkind (Nod) = N_Pragma
11221                  and then Pragma_Name (Nod) = Name_Main_Storage
11222                then
11223                   Error_Msg_Name_1 := Pname;
11224                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
11225                end if;
11226
11227                Next (Nod);
11228             end loop;
11229          end Main_Storage;
11230
11231          -----------------
11232          -- Memory_Size --
11233          -----------------
11234
11235          --  pragma Memory_Size (NUMERIC_LITERAL)
11236
11237          when Pragma_Memory_Size =>
11238             GNAT_Pragma;
11239
11240             --  Memory size is simply ignored
11241
11242             Check_No_Identifiers;
11243             Check_Arg_Count (1);
11244             Check_Arg_Is_Integer_Literal (Arg1);
11245
11246          -------------
11247          -- No_Body --
11248          -------------
11249
11250          --  pragma No_Body;
11251
11252          --  The only correct use of this pragma is on its own in a file, in
11253          --  which case it is specially processed (see Gnat1drv.Check_Bad_Body
11254          --  and Frontend, which use Sinput.L.Source_File_Is_Pragma_No_Body to
11255          --  check for a file containing nothing but a No_Body pragma). If we
11256          --  attempt to process it during normal semantics processing, it means
11257          --  it was misplaced.
11258
11259          when Pragma_No_Body =>
11260             GNAT_Pragma;
11261             Pragma_Misplaced;
11262
11263          ---------------
11264          -- No_Return --
11265          ---------------
11266
11267          --  pragma No_Return (procedure_LOCAL_NAME {, procedure_Local_Name});
11268
11269          when Pragma_No_Return => No_Return : declare
11270             Id    : Node_Id;
11271             E     : Entity_Id;
11272             Found : Boolean;
11273             Arg   : Node_Id;
11274
11275          begin
11276             Ada_2005_Pragma;
11277             Check_At_Least_N_Arguments (1);
11278
11279             --  Loop through arguments of pragma
11280
11281             Arg := Arg1;
11282             while Present (Arg) loop
11283                Check_Arg_Is_Local_Name (Arg);
11284                Id := Get_Pragma_Arg (Arg);
11285                Analyze (Id);
11286
11287                if not Is_Entity_Name (Id) then
11288                   Error_Pragma_Arg ("entity name required", Arg);
11289                end if;
11290
11291                if Etype (Id) = Any_Type then
11292                   raise Pragma_Exit;
11293                end if;
11294
11295                --  Loop to find matching procedures
11296
11297                E := Entity (Id);
11298                Found := False;
11299                while Present (E)
11300                  and then Scope (E) = Current_Scope
11301                loop
11302                   if Ekind_In (E, E_Procedure, E_Generic_Procedure) then
11303                      Set_No_Return (E);
11304
11305                      --  Set flag on any alias as well
11306
11307                      if Is_Overloadable (E) and then Present (Alias (E)) then
11308                         Set_No_Return (Alias (E));
11309                      end if;
11310
11311                      Found := True;
11312                   end if;
11313
11314                   exit when From_Aspect_Specification (N);
11315                   E := Homonym (E);
11316                end loop;
11317
11318                if not Found then
11319                   Error_Pragma_Arg ("no procedure & found for pragma%", Arg);
11320                end if;
11321
11322                Next (Arg);
11323             end loop;
11324          end No_Return;
11325
11326          -----------------
11327          -- No_Run_Time --
11328          -----------------
11329
11330          --  pragma No_Run_Time;
11331
11332          --  Note: this pragma is retained for backwards compatibility. See
11333          --  body of Rtsfind for full details on its handling.
11334
11335          when Pragma_No_Run_Time =>
11336             GNAT_Pragma;
11337             Check_Valid_Configuration_Pragma;
11338             Check_Arg_Count (0);
11339
11340             No_Run_Time_Mode           := True;
11341             Configurable_Run_Time_Mode := True;
11342
11343             --  Set Duration to 32 bits if word size is 32
11344
11345             if Ttypes.System_Word_Size = 32 then
11346                Duration_32_Bits_On_Target := True;
11347             end if;
11348
11349             --  Set appropriate restrictions
11350
11351             Set_Restriction (No_Finalization, N);
11352             Set_Restriction (No_Exception_Handlers, N);
11353             Set_Restriction (Max_Tasks, N, 0);
11354             Set_Restriction (No_Tasking, N);
11355
11356          ------------------------
11357          -- No_Strict_Aliasing --
11358          ------------------------
11359
11360          --  pragma No_Strict_Aliasing [([Entity =>] type_LOCAL_NAME)];
11361
11362          when Pragma_No_Strict_Aliasing => No_Strict_Aliasing : declare
11363             E_Id : Entity_Id;
11364
11365          begin
11366             GNAT_Pragma;
11367             Check_At_Most_N_Arguments (1);
11368
11369             if Arg_Count = 0 then
11370                Check_Valid_Configuration_Pragma;
11371                Opt.No_Strict_Aliasing := True;
11372
11373             else
11374                Check_Optional_Identifier (Arg2, Name_Entity);
11375                Check_Arg_Is_Local_Name (Arg1);
11376                E_Id := Entity (Get_Pragma_Arg (Arg1));
11377
11378                if E_Id = Any_Type then
11379                   return;
11380                elsif No (E_Id) or else not Is_Access_Type (E_Id) then
11381                   Error_Pragma_Arg ("pragma% requires access type", Arg1);
11382                end if;
11383
11384                Set_No_Strict_Aliasing (Implementation_Base_Type (E_Id));
11385             end if;
11386          end No_Strict_Aliasing;
11387
11388          -----------------------
11389          -- Normalize_Scalars --
11390          -----------------------
11391
11392          --  pragma Normalize_Scalars;
11393
11394          when Pragma_Normalize_Scalars =>
11395             Check_Ada_83_Warning;
11396             Check_Arg_Count (0);
11397             Check_Valid_Configuration_Pragma;
11398
11399             --  Normalize_Scalars creates false positives in CodePeer, and
11400             --  incorrect negative results in Alfa mode, so ignore this pragma
11401             --  in these modes.
11402
11403             if not (CodePeer_Mode or Alfa_Mode) then
11404                Normalize_Scalars := True;
11405                Init_Or_Norm_Scalars := True;
11406             end if;
11407
11408          -----------------
11409          -- Obsolescent --
11410          -----------------
11411
11412          --  pragma Obsolescent;
11413
11414          --  pragma Obsolescent (
11415          --    [Message =>] static_string_EXPRESSION
11416          --  [,[Version =>] Ada_05]]);
11417
11418          --  pragma Obsolescent (
11419          --    [Entity  =>] NAME
11420          --  [,[Message =>] static_string_EXPRESSION
11421          --  [,[Version =>] Ada_05]] );
11422
11423          when Pragma_Obsolescent => Obsolescent : declare
11424             Ename : Node_Id;
11425             Decl  : Node_Id;
11426
11427             procedure Set_Obsolescent (E : Entity_Id);
11428             --  Given an entity Ent, mark it as obsolescent if appropriate
11429
11430             ---------------------
11431             -- Set_Obsolescent --
11432             ---------------------
11433
11434             procedure Set_Obsolescent (E : Entity_Id) is
11435                Active : Boolean;
11436                Ent    : Entity_Id;
11437                S      : String_Id;
11438
11439             begin
11440                Active := True;
11441                Ent    := E;
11442
11443                --  Entity name was given
11444
11445                if Present (Ename) then
11446
11447                   --  If entity name matches, we are fine. Save entity in
11448                   --  pragma argument, for ASIS use.
11449
11450                   if Chars (Ename) = Chars (Ent) then
11451                      Set_Entity (Ename, Ent);
11452                      Generate_Reference (Ent, Ename);
11453
11454                   --  If entity name does not match, only possibility is an
11455                   --  enumeration literal from an enumeration type declaration.
11456
11457                   elsif Ekind (Ent) /= E_Enumeration_Type then
11458                      Error_Pragma
11459                        ("pragma % entity name does not match declaration");
11460
11461                   else
11462                      Ent := First_Literal (E);
11463                      loop
11464                         if No (Ent) then
11465                            Error_Pragma
11466                              ("pragma % entity name does not match any " &
11467                               "enumeration literal");
11468
11469                         elsif Chars (Ent) = Chars (Ename) then
11470                            Set_Entity (Ename, Ent);
11471                            Generate_Reference (Ent, Ename);
11472                            exit;
11473
11474                         else
11475                            Ent := Next_Literal (Ent);
11476                         end if;
11477                      end loop;
11478                   end if;
11479                end if;
11480
11481                --  Ent points to entity to be marked
11482
11483                if Arg_Count >= 1 then
11484
11485                   --  Deal with static string argument
11486
11487                   Check_Arg_Is_Static_Expression (Arg1, Standard_String);
11488                   S := Strval (Get_Pragma_Arg (Arg1));
11489
11490                   for J in 1 .. String_Length (S) loop
11491                      if not In_Character_Range (Get_String_Char (S, J)) then
11492                         Error_Pragma_Arg
11493                           ("pragma% argument does not allow wide characters",
11494                            Arg1);
11495                      end if;
11496                   end loop;
11497
11498                   Obsolescent_Warnings.Append
11499                     ((Ent => Ent, Msg => Strval (Get_Pragma_Arg (Arg1))));
11500
11501                   --  Check for Ada_05 parameter
11502
11503                   if Arg_Count /= 1 then
11504                      Check_Arg_Count (2);
11505
11506                      declare
11507                         Argx : constant Node_Id := Get_Pragma_Arg (Arg2);
11508
11509                      begin
11510                         Check_Arg_Is_Identifier (Argx);
11511
11512                         if Chars (Argx) /= Name_Ada_05 then
11513                            Error_Msg_Name_2 := Name_Ada_05;
11514                            Error_Pragma_Arg
11515                              ("only allowed argument for pragma% is %", Argx);
11516                         end if;
11517
11518                         if Ada_Version_Explicit < Ada_2005
11519                           or else not Warn_On_Ada_2005_Compatibility
11520                         then
11521                            Active := False;
11522                         end if;
11523                      end;
11524                   end if;
11525                end if;
11526
11527                --  Set flag if pragma active
11528
11529                if Active then
11530                   Set_Is_Obsolescent (Ent);
11531                end if;
11532
11533                return;
11534             end Set_Obsolescent;
11535
11536          --  Start of processing for pragma Obsolescent
11537
11538          begin
11539             GNAT_Pragma;
11540
11541             Check_At_Most_N_Arguments (3);
11542
11543             --  See if first argument specifies an entity name
11544
11545             if Arg_Count >= 1
11546               and then
11547                 (Chars (Arg1) = Name_Entity
11548                    or else
11549                      Nkind_In (Get_Pragma_Arg (Arg1), N_Character_Literal,
11550                                                       N_Identifier,
11551                                                       N_Operator_Symbol))
11552             then
11553                Ename := Get_Pragma_Arg (Arg1);
11554
11555                --  Eliminate first argument, so we can share processing
11556
11557                Arg1 := Arg2;
11558                Arg2 := Arg3;
11559                Arg_Count := Arg_Count - 1;
11560
11561             --  No Entity name argument given
11562
11563             else
11564                Ename := Empty;
11565             end if;
11566
11567             if Arg_Count >= 1 then
11568                Check_Optional_Identifier (Arg1, Name_Message);
11569
11570                if Arg_Count = 2 then
11571                   Check_Optional_Identifier (Arg2, Name_Version);
11572                end if;
11573             end if;
11574
11575             --  Get immediately preceding declaration
11576
11577             Decl := Prev (N);
11578             while Present (Decl) and then Nkind (Decl) = N_Pragma loop
11579                Prev (Decl);
11580             end loop;
11581
11582             --  Cases where we do not follow anything other than another pragma
11583
11584             if No (Decl) then
11585
11586                --  First case: library level compilation unit declaration with
11587                --  the pragma immediately following the declaration.
11588
11589                if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
11590                   Set_Obsolescent
11591                     (Defining_Entity (Unit (Parent (Parent (N)))));
11592                   return;
11593
11594                --  Case 2: library unit placement for package
11595
11596                else
11597                   declare
11598                      Ent : constant Entity_Id := Find_Lib_Unit_Name;
11599                   begin
11600                      if Is_Package_Or_Generic_Package (Ent) then
11601                         Set_Obsolescent (Ent);
11602                         return;
11603                      end if;
11604                   end;
11605                end if;
11606
11607             --  Cases where we must follow a declaration
11608
11609             else
11610                if         Nkind (Decl) not in N_Declaration
11611                  and then Nkind (Decl) not in N_Later_Decl_Item
11612                  and then Nkind (Decl) not in N_Generic_Declaration
11613                  and then Nkind (Decl) not in N_Renaming_Declaration
11614                then
11615                   Error_Pragma
11616                     ("pragma% misplaced, "
11617                      & "must immediately follow a declaration");
11618
11619                else
11620                   Set_Obsolescent (Defining_Entity (Decl));
11621                   return;
11622                end if;
11623             end if;
11624          end Obsolescent;
11625
11626          --------------
11627          -- Optimize --
11628          --------------
11629
11630          --  pragma Optimize (Time | Space | Off);
11631
11632          --  The actual check for optimize is done in Gigi. Note that this
11633          --  pragma does not actually change the optimization setting, it
11634          --  simply checks that it is consistent with the pragma.
11635
11636          when Pragma_Optimize =>
11637             Check_No_Identifiers;
11638             Check_Arg_Count (1);
11639             Check_Arg_Is_One_Of (Arg1, Name_Time, Name_Space, Name_Off);
11640
11641          ------------------------
11642          -- Optimize_Alignment --
11643          ------------------------
11644
11645          --  pragma Optimize_Alignment (Time | Space | Off);
11646
11647          when Pragma_Optimize_Alignment => Optimize_Alignment : begin
11648             GNAT_Pragma;
11649             Check_No_Identifiers;
11650             Check_Arg_Count (1);
11651             Check_Valid_Configuration_Pragma;
11652
11653             declare
11654                Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
11655             begin
11656                case Nam is
11657                   when Name_Time =>
11658                      Opt.Optimize_Alignment := 'T';
11659                   when Name_Space =>
11660                      Opt.Optimize_Alignment := 'S';
11661                   when Name_Off =>
11662                      Opt.Optimize_Alignment := 'O';
11663                   when others =>
11664                      Error_Pragma_Arg ("invalid argument for pragma%", Arg1);
11665                end case;
11666             end;
11667
11668             --  Set indication that mode is set locally. If we are in fact in a
11669             --  configuration pragma file, this setting is harmless since the
11670             --  switch will get reset anyway at the start of each unit.
11671
11672             Optimize_Alignment_Local := True;
11673          end Optimize_Alignment;
11674
11675          -------------
11676          -- Ordered --
11677          -------------
11678
11679          --  pragma Ordered (first_enumeration_subtype_LOCAL_NAME);
11680
11681          when Pragma_Ordered => Ordered : declare
11682             Assoc   : constant Node_Id := Arg1;
11683             Type_Id : Node_Id;
11684             Typ     : Entity_Id;
11685
11686          begin
11687             GNAT_Pragma;
11688             Check_No_Identifiers;
11689             Check_Arg_Count (1);
11690             Check_Arg_Is_Local_Name (Arg1);
11691
11692             Type_Id := Get_Pragma_Arg (Assoc);
11693             Find_Type (Type_Id);
11694             Typ := Entity (Type_Id);
11695
11696             if Typ = Any_Type then
11697                return;
11698             else
11699                Typ := Underlying_Type (Typ);
11700             end if;
11701
11702             if not Is_Enumeration_Type (Typ) then
11703                Error_Pragma ("pragma% must specify enumeration type");
11704             end if;
11705
11706             Check_First_Subtype (Arg1);
11707             Set_Has_Pragma_Ordered (Base_Type (Typ));
11708          end Ordered;
11709
11710          ----------
11711          -- Pack --
11712          ----------
11713
11714          --  pragma Pack (first_subtype_LOCAL_NAME);
11715
11716          when Pragma_Pack => Pack : declare
11717             Assoc   : constant Node_Id := Arg1;
11718             Type_Id : Node_Id;
11719             Typ     : Entity_Id;
11720             Ctyp    : Entity_Id;
11721             Ignore  : Boolean := False;
11722
11723          begin
11724             Check_No_Identifiers;
11725             Check_Arg_Count (1);
11726             Check_Arg_Is_Local_Name (Arg1);
11727
11728             Type_Id := Get_Pragma_Arg (Assoc);
11729             Find_Type (Type_Id);
11730             Typ := Entity (Type_Id);
11731
11732             if Typ = Any_Type
11733               or else Rep_Item_Too_Early (Typ, N)
11734             then
11735                return;
11736             else
11737                Typ := Underlying_Type (Typ);
11738             end if;
11739
11740             if not Is_Array_Type (Typ) and then not Is_Record_Type (Typ) then
11741                Error_Pragma ("pragma% must specify array or record type");
11742             end if;
11743
11744             Check_First_Subtype (Arg1);
11745             Check_Duplicate_Pragma (Typ);
11746
11747             --  Array type
11748
11749             if Is_Array_Type (Typ) then
11750                Ctyp := Component_Type (Typ);
11751
11752                --  Ignore pack that does nothing
11753
11754                if Known_Static_Esize (Ctyp)
11755                  and then Known_Static_RM_Size (Ctyp)
11756                  and then Esize (Ctyp) = RM_Size (Ctyp)
11757                  and then Addressable (Esize (Ctyp))
11758                then
11759                   Ignore := True;
11760                end if;
11761
11762                --  Process OK pragma Pack. Note that if there is a separate
11763                --  component clause present, the Pack will be cancelled. This
11764                --  processing is in Freeze.
11765
11766                if not Rep_Item_Too_Late (Typ, N) then
11767
11768                   --  In the context of static code analysis, we do not need
11769                   --  complex front-end expansions related to pragma Pack,
11770                   --  so disable handling of pragma Pack in these cases.
11771
11772                   if CodePeer_Mode or Alfa_Mode then
11773                      null;
11774
11775                   --  Don't attempt any packing for VM targets. We possibly
11776                   --  could deal with some cases of array bit-packing, but we
11777                   --  don't bother, since this is not a typical kind of
11778                   --  representation in the VM context anyway (and would not
11779                   --  for example work nicely with the debugger).
11780
11781                   elsif VM_Target /= No_VM then
11782                      if not GNAT_Mode then
11783                         Error_Pragma
11784                           ("?pragma% ignored in this configuration");
11785                      end if;
11786
11787                   --  Normal case where we do the pack action
11788
11789                   else
11790                      if not Ignore then
11791                         Set_Is_Packed            (Base_Type (Typ));
11792                         Set_Has_Non_Standard_Rep (Base_Type (Typ));
11793                      end if;
11794
11795                      Set_Has_Pragma_Pack (Base_Type (Typ));
11796                   end if;
11797                end if;
11798
11799             --  For record types, the pack is always effective
11800
11801             else pragma Assert (Is_Record_Type (Typ));
11802                if not Rep_Item_Too_Late (Typ, N) then
11803
11804                   --  Ignore pack request with warning in VM mode (skip warning
11805                   --  if we are compiling GNAT run time library).
11806
11807                   if VM_Target /= No_VM then
11808                      if not GNAT_Mode then
11809                         Error_Pragma
11810                           ("?pragma% ignored in this configuration");
11811                      end if;
11812
11813                   --  Normal case of pack request active
11814
11815                   else
11816                      Set_Is_Packed            (Base_Type (Typ));
11817                      Set_Has_Pragma_Pack      (Base_Type (Typ));
11818                      Set_Has_Non_Standard_Rep (Base_Type (Typ));
11819                   end if;
11820                end if;
11821             end if;
11822          end Pack;
11823
11824          ----------
11825          -- Page --
11826          ----------
11827
11828          --  pragma Page;
11829
11830          --  There is nothing to do here, since we did all the processing for
11831          --  this pragma in Par.Prag (so that it works properly even in syntax
11832          --  only mode).
11833
11834          when Pragma_Page =>
11835             null;
11836
11837          -------------
11838          -- Passive --
11839          -------------
11840
11841          --  pragma Passive [(PASSIVE_FORM)];
11842
11843          --  PASSIVE_FORM ::= Semaphore | No
11844
11845          when Pragma_Passive =>
11846             GNAT_Pragma;
11847
11848             if Nkind (Parent (N)) /= N_Task_Definition then
11849                Error_Pragma ("pragma% must be within task definition");
11850             end if;
11851
11852             if Arg_Count /= 0 then
11853                Check_Arg_Count (1);
11854                Check_Arg_Is_One_Of (Arg1, Name_Semaphore, Name_No);
11855             end if;
11856
11857          ----------------------------------
11858          -- Preelaborable_Initialization --
11859          ----------------------------------
11860
11861          --  pragma Preelaborable_Initialization (DIRECT_NAME);
11862
11863          when Pragma_Preelaborable_Initialization => Preelab_Init : declare
11864             Ent : Entity_Id;
11865
11866          begin
11867             Ada_2005_Pragma;
11868             Check_Arg_Count (1);
11869             Check_No_Identifiers;
11870             Check_Arg_Is_Identifier (Arg1);
11871             Check_Arg_Is_Local_Name (Arg1);
11872             Check_First_Subtype (Arg1);
11873             Ent := Entity (Get_Pragma_Arg (Arg1));
11874
11875             if not (Is_Private_Type (Ent)
11876                       or else
11877                     Is_Protected_Type (Ent)
11878                       or else
11879                     (Is_Generic_Type (Ent) and then Is_Derived_Type (Ent)))
11880             then
11881                Error_Pragma_Arg
11882                  ("pragma % can only be applied to private, formal derived or "
11883                   & "protected type",
11884                   Arg1);
11885             end if;
11886
11887             --  Give an error if the pragma is applied to a protected type that
11888             --  does not qualify (due to having entries, or due to components
11889             --  that do not qualify).
11890
11891             if Is_Protected_Type (Ent)
11892               and then not Has_Preelaborable_Initialization (Ent)
11893             then
11894                Error_Msg_N
11895                  ("protected type & does not have preelaborable " &
11896                   "initialization", Ent);
11897
11898             --  Otherwise mark the type as definitely having preelaborable
11899             --  initialization.
11900
11901             else
11902                Set_Known_To_Have_Preelab_Init (Ent);
11903             end if;
11904
11905             if Has_Pragma_Preelab_Init (Ent)
11906               and then Warn_On_Redundant_Constructs
11907             then
11908                Error_Pragma ("?duplicate pragma%!");
11909             else
11910                Set_Has_Pragma_Preelab_Init (Ent);
11911             end if;
11912          end Preelab_Init;
11913
11914          --------------------
11915          -- Persistent_BSS --
11916          --------------------
11917
11918          --  pragma Persistent_BSS [(object_NAME)];
11919
11920          when Pragma_Persistent_BSS => Persistent_BSS :  declare
11921             Decl : Node_Id;
11922             Ent  : Entity_Id;
11923             Prag : Node_Id;
11924
11925          begin
11926             GNAT_Pragma;
11927             Check_At_Most_N_Arguments (1);
11928
11929             --  Case of application to specific object (one argument)
11930
11931             if Arg_Count = 1 then
11932                Check_Arg_Is_Library_Level_Local_Name (Arg1);
11933
11934                if not Is_Entity_Name (Get_Pragma_Arg (Arg1))
11935                  or else not
11936                   Ekind_In (Entity (Get_Pragma_Arg (Arg1)), E_Variable,
11937                                                             E_Constant)
11938                then
11939                   Error_Pragma_Arg ("pragma% only applies to objects", Arg1);
11940                end if;
11941
11942                Ent := Entity (Get_Pragma_Arg (Arg1));
11943                Decl := Parent (Ent);
11944
11945                if Rep_Item_Too_Late (Ent, N) then
11946                   return;
11947                end if;
11948
11949                if Present (Expression (Decl)) then
11950                   Error_Pragma_Arg
11951                     ("object for pragma% cannot have initialization", Arg1);
11952                end if;
11953
11954                if not Is_Potentially_Persistent_Type (Etype (Ent)) then
11955                   Error_Pragma_Arg
11956                     ("object type for pragma% is not potentially persistent",
11957                      Arg1);
11958                end if;
11959
11960                Check_Duplicate_Pragma (Ent);
11961
11962                Prag :=
11963                  Make_Linker_Section_Pragma
11964                    (Ent, Sloc (N), ".persistent.bss");
11965                Insert_After (N, Prag);
11966                Analyze (Prag);
11967
11968             --  Case of use as configuration pragma with no arguments
11969
11970             else
11971                Check_Valid_Configuration_Pragma;
11972                Persistent_BSS_Mode := True;
11973             end if;
11974          end Persistent_BSS;
11975
11976          -------------
11977          -- Polling --
11978          -------------
11979
11980          --  pragma Polling (ON | OFF);
11981
11982          when Pragma_Polling =>
11983             GNAT_Pragma;
11984             Check_Arg_Count (1);
11985             Check_No_Identifiers;
11986             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
11987             Polling_Required := (Chars (Get_Pragma_Arg (Arg1)) = Name_On);
11988
11989          -------------------
11990          -- Postcondition --
11991          -------------------
11992
11993          --  pragma Postcondition ([Check   =>] Boolean_EXPRESSION
11994          --                      [,[Message =>] String_EXPRESSION]);
11995
11996          when Pragma_Postcondition => Postcondition : declare
11997             In_Body : Boolean;
11998             pragma Warnings (Off, In_Body);
11999
12000          begin
12001             GNAT_Pragma;
12002             Check_At_Least_N_Arguments (1);
12003             Check_At_Most_N_Arguments (2);
12004             Check_Optional_Identifier (Arg1, Name_Check);
12005
12006             --  All we need to do here is call the common check procedure,
12007             --  the remainder of the processing is found in Sem_Ch6/Sem_Ch7.
12008
12009             Check_Precondition_Postcondition (In_Body);
12010          end Postcondition;
12011
12012          ------------------
12013          -- Precondition --
12014          ------------------
12015
12016          --  pragma Precondition ([Check   =>] Boolean_EXPRESSION
12017          --                     [,[Message =>] String_EXPRESSION]);
12018
12019          when Pragma_Precondition => Precondition : declare
12020             In_Body : Boolean;
12021
12022          begin
12023             GNAT_Pragma;
12024             Check_At_Least_N_Arguments (1);
12025             Check_At_Most_N_Arguments (2);
12026             Check_Optional_Identifier (Arg1, Name_Check);
12027             Check_Precondition_Postcondition (In_Body);
12028
12029             --  If in spec, nothing more to do. If in body, then we convert the
12030             --  pragma to pragma Check (Precondition, cond [, msg]). Note we do
12031             --  this whether or not precondition checks are enabled. That works
12032             --  fine since pragma Check will do this check, and will also
12033             --  analyze the condition itself in the proper context.
12034
12035             if In_Body then
12036                Rewrite (N,
12037                  Make_Pragma (Loc,
12038                    Chars => Name_Check,
12039                    Pragma_Argument_Associations => New_List (
12040                      Make_Pragma_Argument_Association (Loc,
12041                        Expression => Make_Identifier (Loc, Name_Precondition)),
12042
12043                      Make_Pragma_Argument_Association (Sloc (Arg1),
12044                        Expression => Relocate_Node (Get_Pragma_Arg (Arg1))))));
12045
12046                if Arg_Count = 2 then
12047                   Append_To (Pragma_Argument_Associations (N),
12048                     Make_Pragma_Argument_Association (Sloc (Arg2),
12049                       Expression => Relocate_Node (Get_Pragma_Arg (Arg2))));
12050                end if;
12051
12052                Analyze (N);
12053             end if;
12054          end Precondition;
12055
12056          ---------------
12057          -- Predicate --
12058          ---------------
12059
12060          --  pragma Predicate
12061          --    ([Entity =>] type_LOCAL_NAME,
12062          --     [Check  =>] EXPRESSION);
12063
12064          when Pragma_Predicate => Predicate : declare
12065             Type_Id : Node_Id;
12066             Typ     : Entity_Id;
12067
12068             Discard : Boolean;
12069             pragma Unreferenced (Discard);
12070
12071          begin
12072             GNAT_Pragma;
12073             Check_Arg_Count (2);
12074             Check_Optional_Identifier (Arg1, Name_Entity);
12075             Check_Optional_Identifier (Arg2, Name_Check);
12076
12077             Check_Arg_Is_Local_Name (Arg1);
12078
12079             Type_Id := Get_Pragma_Arg (Arg1);
12080             Find_Type (Type_Id);
12081             Typ := Entity (Type_Id);
12082
12083             if Typ = Any_Type then
12084                return;
12085             end if;
12086
12087             --  The remaining processing is simply to link the pragma on to
12088             --  the rep item chain, for processing when the type is frozen.
12089             --  This is accomplished by a call to Rep_Item_Too_Late. We also
12090             --  mark the type as having predicates.
12091
12092             Set_Has_Predicates (Typ);
12093             Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
12094          end Predicate;
12095
12096          ------------------
12097          -- Preelaborate --
12098          ------------------
12099
12100          --  pragma Preelaborate [(library_unit_NAME)];
12101
12102          --  Set the flag Is_Preelaborated of program unit name entity
12103
12104          when Pragma_Preelaborate => Preelaborate : declare
12105             Pa  : constant Node_Id   := Parent (N);
12106             Pk  : constant Node_Kind := Nkind (Pa);
12107             Ent : Entity_Id;
12108
12109          begin
12110             Check_Ada_83_Warning;
12111             Check_Valid_Library_Unit_Pragma;
12112
12113             if Nkind (N) = N_Null_Statement then
12114                return;
12115             end if;
12116
12117             Ent := Find_Lib_Unit_Name;
12118             Check_Duplicate_Pragma (Ent);
12119
12120             --  This filters out pragmas inside generic parent then
12121             --  show up inside instantiation
12122
12123             if Present (Ent)
12124               and then not (Pk = N_Package_Specification
12125                              and then Present (Generic_Parent (Pa)))
12126             then
12127                if not Debug_Flag_U then
12128                   Set_Is_Preelaborated (Ent);
12129                   Set_Suppress_Elaboration_Warnings (Ent);
12130                end if;
12131             end if;
12132          end Preelaborate;
12133
12134          ---------------------
12135          -- Preelaborate_05 --
12136          ---------------------
12137
12138          --  pragma Preelaborate_05 [(library_unit_NAME)];
12139
12140          --  This pragma is useable only in GNAT_Mode, where it is used like
12141          --  pragma Preelaborate but it is only effective in Ada 2005 mode
12142          --  (otherwise it is ignored). This is used to implement AI-362 which
12143          --  recategorizes some run-time packages in Ada 2005 mode.
12144
12145          when Pragma_Preelaborate_05 => Preelaborate_05 : declare
12146             Ent : Entity_Id;
12147
12148          begin
12149             GNAT_Pragma;
12150             Check_Valid_Library_Unit_Pragma;
12151
12152             if not GNAT_Mode then
12153                Error_Pragma ("pragma% only available in GNAT mode");
12154             end if;
12155
12156             if Nkind (N) = N_Null_Statement then
12157                return;
12158             end if;
12159
12160             --  This is one of the few cases where we need to test the value of
12161             --  Ada_Version_Explicit rather than Ada_Version (which is always
12162             --  set to Ada_2012 in a predefined unit), we need to know the
12163             --  explicit version set to know if this pragma is active.
12164
12165             if Ada_Version_Explicit >= Ada_2005 then
12166                Ent := Find_Lib_Unit_Name;
12167                Set_Is_Preelaborated (Ent);
12168                Set_Suppress_Elaboration_Warnings (Ent);
12169             end if;
12170          end Preelaborate_05;
12171
12172          --------------
12173          -- Priority --
12174          --------------
12175
12176          --  pragma Priority (EXPRESSION);
12177
12178          when Pragma_Priority => Priority : declare
12179             P   : constant Node_Id := Parent (N);
12180             Arg : Node_Id;
12181
12182          begin
12183             Check_No_Identifiers;
12184             Check_Arg_Count (1);
12185
12186             --  Subprogram case
12187
12188             if Nkind (P) = N_Subprogram_Body then
12189                Check_In_Main_Program;
12190
12191                Arg := Get_Pragma_Arg (Arg1);
12192                Analyze_And_Resolve (Arg, Standard_Integer);
12193
12194                --  Must be static
12195
12196                if not Is_Static_Expression (Arg) then
12197                   Flag_Non_Static_Expr
12198                     ("main subprogram priority is not static!", Arg);
12199                   raise Pragma_Exit;
12200
12201                --  If constraint error, then we already signalled an error
12202
12203                elsif Raises_Constraint_Error (Arg) then
12204                   null;
12205
12206                --  Otherwise check in range
12207
12208                else
12209                   declare
12210                      Val : constant Uint := Expr_Value (Arg);
12211
12212                   begin
12213                      if Val < 0
12214                        or else Val > Expr_Value (Expression
12215                                        (Parent (RTE (RE_Max_Priority))))
12216                      then
12217                         Error_Pragma_Arg
12218                           ("main subprogram priority is out of range", Arg1);
12219                      end if;
12220                   end;
12221                end if;
12222
12223                Set_Main_Priority
12224                     (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
12225
12226                --  Load an arbitrary entity from System.Tasking to make sure
12227                --  this package is implicitly with'ed, since we need to have
12228                --  the tasking run-time active for the pragma Priority to have
12229                --  any effect.
12230
12231                declare
12232                   Discard : Entity_Id;
12233                   pragma Warnings (Off, Discard);
12234                begin
12235                   Discard := RTE (RE_Task_List);
12236                end;
12237
12238             --  Task or Protected, must be of type Integer
12239
12240             elsif Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
12241                Arg := Get_Pragma_Arg (Arg1);
12242
12243                --  The expression must be analyzed in the special manner
12244                --  described in "Handling of Default and Per-Object
12245                --  Expressions" in sem.ads.
12246
12247                Preanalyze_Spec_Expression (Arg, Standard_Integer);
12248
12249                if not Is_Static_Expression (Arg) then
12250                   Check_Restriction (Static_Priorities, Arg);
12251                end if;
12252
12253             --  Anything else is incorrect
12254
12255             else
12256                Pragma_Misplaced;
12257             end if;
12258
12259             if Has_Pragma_Priority (P) then
12260                Error_Pragma ("duplicate pragma% not allowed");
12261             else
12262                Set_Has_Pragma_Priority (P, True);
12263
12264                if Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
12265                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
12266                   --  exp_ch9 should use this ???
12267                end if;
12268             end if;
12269          end Priority;
12270
12271          -----------------------------------
12272          -- Priority_Specific_Dispatching --
12273          -----------------------------------
12274
12275          --  pragma Priority_Specific_Dispatching (
12276          --    policy_IDENTIFIER,
12277          --    first_priority_EXPRESSION,
12278          --    last_priority_EXPRESSION);
12279
12280          when Pragma_Priority_Specific_Dispatching =>
12281          Priority_Specific_Dispatching : declare
12282             Prio_Id : constant Entity_Id := RTE (RE_Any_Priority);
12283             --  This is the entity System.Any_Priority;
12284
12285             DP          : Character;
12286             Lower_Bound : Node_Id;
12287             Upper_Bound : Node_Id;
12288             Lower_Val   : Uint;
12289             Upper_Val   : Uint;
12290
12291          begin
12292             Ada_2005_Pragma;
12293             Check_Arg_Count (3);
12294             Check_No_Identifiers;
12295             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
12296             Check_Valid_Configuration_Pragma;
12297             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
12298             DP := Fold_Upper (Name_Buffer (1));
12299
12300             Lower_Bound := Get_Pragma_Arg (Arg2);
12301             Check_Arg_Is_Static_Expression (Lower_Bound, Standard_Integer);
12302             Lower_Val := Expr_Value (Lower_Bound);
12303
12304             Upper_Bound := Get_Pragma_Arg (Arg3);
12305             Check_Arg_Is_Static_Expression (Upper_Bound, Standard_Integer);
12306             Upper_Val := Expr_Value (Upper_Bound);
12307
12308             --  It is not allowed to use Task_Dispatching_Policy and
12309             --  Priority_Specific_Dispatching in the same partition.
12310
12311             if Task_Dispatching_Policy /= ' ' then
12312                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
12313                Error_Pragma
12314                  ("pragma% incompatible with Task_Dispatching_Policy#");
12315
12316             --  Check lower bound in range
12317
12318             elsif Lower_Val < Expr_Value (Type_Low_Bound (Prio_Id))
12319                     or else
12320                   Lower_Val > Expr_Value (Type_High_Bound (Prio_Id))
12321             then
12322                Error_Pragma_Arg
12323                  ("first_priority is out of range", Arg2);
12324
12325             --  Check upper bound in range
12326
12327             elsif Upper_Val < Expr_Value (Type_Low_Bound (Prio_Id))
12328                     or else
12329                   Upper_Val > Expr_Value (Type_High_Bound (Prio_Id))
12330             then
12331                Error_Pragma_Arg
12332                  ("last_priority is out of range", Arg3);
12333
12334             --  Check that the priority range is valid
12335
12336             elsif Lower_Val > Upper_Val then
12337                Error_Pragma
12338                  ("last_priority_expression must be greater than" &
12339                   " or equal to first_priority_expression");
12340
12341             --  Store the new policy, but always preserve System_Location since
12342             --  we like the error message with the run-time name.
12343
12344             else
12345                --  Check overlapping in the priority ranges specified in other
12346                --  Priority_Specific_Dispatching pragmas within the same
12347                --  partition. We can only check those we know about!
12348
12349                for J in
12350                   Specific_Dispatching.First .. Specific_Dispatching.Last
12351                loop
12352                   if Specific_Dispatching.Table (J).First_Priority in
12353                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
12354                   or else Specific_Dispatching.Table (J).Last_Priority in
12355                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
12356                   then
12357                      Error_Msg_Sloc :=
12358                        Specific_Dispatching.Table (J).Pragma_Loc;
12359                         Error_Pragma
12360                           ("priority range overlaps with "
12361                            & "Priority_Specific_Dispatching#");
12362                   end if;
12363                end loop;
12364
12365                --  The use of Priority_Specific_Dispatching is incompatible
12366                --  with Task_Dispatching_Policy.
12367
12368                if Task_Dispatching_Policy /= ' ' then
12369                   Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
12370                      Error_Pragma
12371                        ("Priority_Specific_Dispatching incompatible "
12372                         & "with Task_Dispatching_Policy#");
12373                end if;
12374
12375                --  The use of Priority_Specific_Dispatching forces ceiling
12376                --  locking policy.
12377
12378                if Locking_Policy /= ' ' and then Locking_Policy /= 'C' then
12379                   Error_Msg_Sloc := Locking_Policy_Sloc;
12380                      Error_Pragma
12381                        ("Priority_Specific_Dispatching incompatible "
12382                         & "with Locking_Policy#");
12383
12384                --  Set the Ceiling_Locking policy, but preserve System_Location
12385                --  since we like the error message with the run time name.
12386
12387                else
12388                   Locking_Policy := 'C';
12389
12390                   if Locking_Policy_Sloc /= System_Location then
12391                      Locking_Policy_Sloc := Loc;
12392                   end if;
12393                end if;
12394
12395                --  Add entry in the table
12396
12397                Specific_Dispatching.Append
12398                     ((Dispatching_Policy => DP,
12399                       First_Priority     => UI_To_Int (Lower_Val),
12400                       Last_Priority      => UI_To_Int (Upper_Val),
12401                       Pragma_Loc         => Loc));
12402             end if;
12403          end Priority_Specific_Dispatching;
12404
12405          -------------
12406          -- Profile --
12407          -------------
12408
12409          --  pragma Profile (profile_IDENTIFIER);
12410
12411          --  profile_IDENTIFIER => Restricted | Ravenscar
12412
12413          when Pragma_Profile =>
12414             Ada_2005_Pragma;
12415             Check_Arg_Count (1);
12416             Check_Valid_Configuration_Pragma;
12417             Check_No_Identifiers;
12418
12419             declare
12420                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
12421
12422             begin
12423                if Chars (Argx) = Name_Ravenscar then
12424                   Set_Ravenscar_Profile (N);
12425
12426                elsif Chars (Argx) = Name_Restricted then
12427                   Set_Profile_Restrictions
12428                     (Restricted,
12429                      N, Warn => Treat_Restrictions_As_Warnings);
12430
12431                elsif Chars (Argx) = Name_No_Implementation_Extensions then
12432                   Set_Profile_Restrictions
12433                     (No_Implementation_Extensions,
12434                      N, Warn => Treat_Restrictions_As_Warnings);
12435
12436                else
12437                   Error_Pragma_Arg ("& is not a valid profile", Argx);
12438                end if;
12439             end;
12440
12441          ----------------------
12442          -- Profile_Warnings --
12443          ----------------------
12444
12445          --  pragma Profile_Warnings (profile_IDENTIFIER);
12446
12447          --  profile_IDENTIFIER => Restricted | Ravenscar
12448
12449          when Pragma_Profile_Warnings =>
12450             GNAT_Pragma;
12451             Check_Arg_Count (1);
12452             Check_Valid_Configuration_Pragma;
12453             Check_No_Identifiers;
12454
12455             declare
12456                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
12457
12458             begin
12459                if Chars (Argx) = Name_Ravenscar then
12460                   Set_Profile_Restrictions (Ravenscar, N, Warn => True);
12461
12462                elsif Chars (Argx) = Name_Restricted then
12463                   Set_Profile_Restrictions (Restricted, N, Warn => True);
12464
12465                elsif Chars (Argx) = Name_No_Implementation_Extensions then
12466                   Set_Profile_Restrictions
12467                     (No_Implementation_Extensions, N, Warn => True);
12468
12469                else
12470                   Error_Pragma_Arg ("& is not a valid profile", Argx);
12471                end if;
12472             end;
12473
12474          --------------------------
12475          -- Propagate_Exceptions --
12476          --------------------------
12477
12478          --  pragma Propagate_Exceptions;
12479
12480          --  Note: this pragma is obsolete and has no effect
12481
12482          when Pragma_Propagate_Exceptions =>
12483             GNAT_Pragma;
12484             Check_Arg_Count (0);
12485
12486             if In_Extended_Main_Source_Unit (N) then
12487                Propagate_Exceptions := True;
12488             end if;
12489
12490          ------------------
12491          -- Psect_Object --
12492          ------------------
12493
12494          --  pragma Psect_Object (
12495          --        [Internal =>] LOCAL_NAME,
12496          --     [, [External =>] EXTERNAL_SYMBOL]
12497          --     [, [Size     =>] EXTERNAL_SYMBOL]);
12498
12499          when Pragma_Psect_Object | Pragma_Common_Object =>
12500          Psect_Object : declare
12501             Args  : Args_List (1 .. 3);
12502             Names : constant Name_List (1 .. 3) := (
12503                       Name_Internal,
12504                       Name_External,
12505                       Name_Size);
12506
12507             Internal : Node_Id renames Args (1);
12508             External : Node_Id renames Args (2);
12509             Size     : Node_Id renames Args (3);
12510
12511             Def_Id : Entity_Id;
12512
12513             procedure Check_Too_Long (Arg : Node_Id);
12514             --  Posts message if the argument is an identifier with more
12515             --  than 31 characters, or a string literal with more than
12516             --  31 characters, and we are operating under VMS
12517
12518             --------------------
12519             -- Check_Too_Long --
12520             --------------------
12521
12522             procedure Check_Too_Long (Arg : Node_Id) is
12523                X : constant Node_Id := Original_Node (Arg);
12524
12525             begin
12526                if not Nkind_In (X, N_String_Literal, N_Identifier) then
12527                   Error_Pragma_Arg
12528                     ("inappropriate argument for pragma %", Arg);
12529                end if;
12530
12531                if OpenVMS_On_Target then
12532                   if (Nkind (X) = N_String_Literal
12533                        and then String_Length (Strval (X)) > 31)
12534                     or else
12535                      (Nkind (X) = N_Identifier
12536                        and then Length_Of_Name (Chars (X)) > 31)
12537                   then
12538                      Error_Pragma_Arg
12539                        ("argument for pragma % is longer than 31 characters",
12540                         Arg);
12541                   end if;
12542                end if;
12543             end Check_Too_Long;
12544
12545          --  Start of processing for Common_Object/Psect_Object
12546
12547          begin
12548             GNAT_Pragma;
12549             Gather_Associations (Names, Args);
12550             Process_Extended_Import_Export_Internal_Arg (Internal);
12551
12552             Def_Id := Entity (Internal);
12553
12554             if not Ekind_In (Def_Id, E_Constant, E_Variable) then
12555                Error_Pragma_Arg
12556                  ("pragma% must designate an object", Internal);
12557             end if;
12558
12559             Check_Too_Long (Internal);
12560
12561             if Is_Imported (Def_Id) or else Is_Exported (Def_Id) then
12562                Error_Pragma_Arg
12563                  ("cannot use pragma% for imported/exported object",
12564                   Internal);
12565             end if;
12566
12567             if Is_Concurrent_Type (Etype (Internal)) then
12568                Error_Pragma_Arg
12569                  ("cannot specify pragma % for task/protected object",
12570                   Internal);
12571             end if;
12572
12573             if Has_Rep_Pragma (Def_Id, Name_Common_Object)
12574                  or else
12575                Has_Rep_Pragma (Def_Id, Name_Psect_Object)
12576             then
12577                Error_Msg_N ("?duplicate Common/Psect_Object pragma", N);
12578             end if;
12579
12580             if Ekind (Def_Id) = E_Constant then
12581                Error_Pragma_Arg
12582                  ("cannot specify pragma % for a constant", Internal);
12583             end if;
12584
12585             if Is_Record_Type (Etype (Internal)) then
12586                declare
12587                   Ent  : Entity_Id;
12588                   Decl : Entity_Id;
12589
12590                begin
12591                   Ent := First_Entity (Etype (Internal));
12592                   while Present (Ent) loop
12593                      Decl := Declaration_Node (Ent);
12594
12595                      if Ekind (Ent) = E_Component
12596                        and then Nkind (Decl) = N_Component_Declaration
12597                        and then Present (Expression (Decl))
12598                        and then Warn_On_Export_Import
12599                      then
12600                         Error_Msg_N
12601                           ("?object for pragma % has defaults", Internal);
12602                         exit;
12603
12604                      else
12605                         Next_Entity (Ent);
12606                      end if;
12607                   end loop;
12608                end;
12609             end if;
12610
12611             if Present (Size) then
12612                Check_Too_Long (Size);
12613             end if;
12614
12615             if Present (External) then
12616                Check_Arg_Is_External_Name (External);
12617                Check_Too_Long (External);
12618             end if;
12619
12620             --  If all error tests pass, link pragma on to the rep item chain
12621
12622             Record_Rep_Item (Def_Id, N);
12623          end Psect_Object;
12624
12625          ----------
12626          -- Pure --
12627          ----------
12628
12629          --  pragma Pure [(library_unit_NAME)];
12630
12631          when Pragma_Pure => Pure : declare
12632             Ent : Entity_Id;
12633
12634          begin
12635             Check_Ada_83_Warning;
12636             Check_Valid_Library_Unit_Pragma;
12637
12638             if Nkind (N) = N_Null_Statement then
12639                return;
12640             end if;
12641
12642             Ent := Find_Lib_Unit_Name;
12643             Set_Is_Pure (Ent);
12644             Set_Has_Pragma_Pure (Ent);
12645             Set_Suppress_Elaboration_Warnings (Ent);
12646          end Pure;
12647
12648          -------------
12649          -- Pure_05 --
12650          -------------
12651
12652          --  pragma Pure_05 [(library_unit_NAME)];
12653
12654          --  This pragma is useable only in GNAT_Mode, where it is used like
12655          --  pragma Pure but it is only effective in Ada 2005 mode (otherwise
12656          --  it is ignored). It may be used after a pragma Preelaborate, in
12657          --  which case it overrides the effect of the pragma Preelaborate.
12658          --  This is used to implement AI-362 which recategorizes some run-time
12659          --  packages in Ada 2005 mode.
12660
12661          when Pragma_Pure_05 => Pure_05 : declare
12662             Ent : Entity_Id;
12663
12664          begin
12665             GNAT_Pragma;
12666             Check_Valid_Library_Unit_Pragma;
12667
12668             if not GNAT_Mode then
12669                Error_Pragma ("pragma% only available in GNAT mode");
12670             end if;
12671
12672             if Nkind (N) = N_Null_Statement then
12673                return;
12674             end if;
12675
12676             --  This is one of the few cases where we need to test the value of
12677             --  Ada_Version_Explicit rather than Ada_Version (which is always
12678             --  set to Ada_2012 in a predefined unit), we need to know the
12679             --  explicit version set to know if this pragma is active.
12680
12681             if Ada_Version_Explicit >= Ada_2005 then
12682                Ent := Find_Lib_Unit_Name;
12683                Set_Is_Preelaborated (Ent, False);
12684                Set_Is_Pure (Ent);
12685                Set_Suppress_Elaboration_Warnings (Ent);
12686             end if;
12687          end Pure_05;
12688
12689          -------------
12690          -- Pure_12 --
12691          -------------
12692
12693          --  pragma Pure_12 [(library_unit_NAME)];
12694
12695          --  This pragma is useable only in GNAT_Mode, where it is used like
12696          --  pragma Pure but it is only effective in Ada 2012 mode (otherwise
12697          --  it is ignored). It may be used after a pragma Preelaborate, in
12698          --  which case it overrides the effect of the pragma Preelaborate.
12699          --  This is used to implement AI05-0212 which recategorizes some
12700          --  run-time packages in Ada 2012 mode.
12701
12702          when Pragma_Pure_12 => Pure_12 : declare
12703             Ent : Entity_Id;
12704
12705          begin
12706             GNAT_Pragma;
12707             Check_Valid_Library_Unit_Pragma;
12708
12709             if not GNAT_Mode then
12710                Error_Pragma ("pragma% only available in GNAT mode");
12711             end if;
12712
12713             if Nkind (N) = N_Null_Statement then
12714                return;
12715             end if;
12716
12717             --  This is one of the few cases where we need to test the value of
12718             --  Ada_Version_Explicit rather than Ada_Version (which is always
12719             --  set to Ada_2012 in a predefined unit), we need to know the
12720             --  explicit version set to know if this pragma is active.
12721
12722             if Ada_Version_Explicit >= Ada_2012 then
12723                Ent := Find_Lib_Unit_Name;
12724                Set_Is_Preelaborated (Ent, False);
12725                Set_Is_Pure (Ent);
12726                Set_Suppress_Elaboration_Warnings (Ent);
12727             end if;
12728          end Pure_12;
12729
12730          -------------------
12731          -- Pure_Function --
12732          -------------------
12733
12734          --  pragma Pure_Function ([Entity =>] function_LOCAL_NAME);
12735
12736          when Pragma_Pure_Function => Pure_Function : declare
12737             E_Id      : Node_Id;
12738             E         : Entity_Id;
12739             Def_Id    : Entity_Id;
12740             Effective : Boolean := False;
12741
12742          begin
12743             GNAT_Pragma;
12744             Check_Arg_Count (1);
12745             Check_Optional_Identifier (Arg1, Name_Entity);
12746             Check_Arg_Is_Local_Name (Arg1);
12747             E_Id := Get_Pragma_Arg (Arg1);
12748
12749             if Error_Posted (E_Id) then
12750                return;
12751             end if;
12752
12753             --  Loop through homonyms (overloadings) of referenced entity
12754
12755             E := Entity (E_Id);
12756
12757             if Present (E) then
12758                loop
12759                   Def_Id := Get_Base_Subprogram (E);
12760
12761                   if not Ekind_In (Def_Id, E_Function,
12762                                            E_Generic_Function,
12763                                            E_Operator)
12764                   then
12765                      Error_Pragma_Arg
12766                        ("pragma% requires a function name", Arg1);
12767                   end if;
12768
12769                   Set_Is_Pure (Def_Id);
12770
12771                   if not Has_Pragma_Pure_Function (Def_Id) then
12772                      Set_Has_Pragma_Pure_Function (Def_Id);
12773                      Effective := True;
12774                   end if;
12775
12776                   exit when From_Aspect_Specification (N);
12777                   E := Homonym (E);
12778                   exit when No (E) or else Scope (E) /= Current_Scope;
12779                end loop;
12780
12781                if not Effective
12782                  and then Warn_On_Redundant_Constructs
12783                then
12784                   Error_Msg_NE
12785                     ("pragma Pure_Function on& is redundant?",
12786                      N, Entity (E_Id));
12787                end if;
12788             end if;
12789          end Pure_Function;
12790
12791          --------------------
12792          -- Queuing_Policy --
12793          --------------------
12794
12795          --  pragma Queuing_Policy (policy_IDENTIFIER);
12796
12797          when Pragma_Queuing_Policy => declare
12798             QP : Character;
12799
12800          begin
12801             Check_Ada_83_Warning;
12802             Check_Arg_Count (1);
12803             Check_No_Identifiers;
12804             Check_Arg_Is_Queuing_Policy (Arg1);
12805             Check_Valid_Configuration_Pragma;
12806             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
12807             QP := Fold_Upper (Name_Buffer (1));
12808
12809             if Queuing_Policy /= ' '
12810               and then Queuing_Policy /= QP
12811             then
12812                Error_Msg_Sloc := Queuing_Policy_Sloc;
12813                Error_Pragma ("queuing policy incompatible with policy#");
12814
12815             --  Set new policy, but always preserve System_Location since we
12816             --  like the error message with the run time name.
12817
12818             else
12819                Queuing_Policy := QP;
12820
12821                if Queuing_Policy_Sloc /= System_Location then
12822                   Queuing_Policy_Sloc := Loc;
12823                end if;
12824             end if;
12825          end;
12826
12827          -----------------------
12828          -- Relative_Deadline --
12829          -----------------------
12830
12831          --  pragma Relative_Deadline (time_span_EXPRESSION);
12832
12833          when Pragma_Relative_Deadline => Relative_Deadline : declare
12834             P   : constant Node_Id := Parent (N);
12835             Arg : Node_Id;
12836
12837          begin
12838             Ada_2005_Pragma;
12839             Check_No_Identifiers;
12840             Check_Arg_Count (1);
12841
12842             Arg := Get_Pragma_Arg (Arg1);
12843
12844             --  The expression must be analyzed in the special manner described
12845             --  in "Handling of Default and Per-Object Expressions" in sem.ads.
12846
12847             Preanalyze_Spec_Expression (Arg, RTE (RE_Time_Span));
12848
12849             --  Subprogram case
12850
12851             if Nkind (P) = N_Subprogram_Body then
12852                Check_In_Main_Program;
12853
12854             --  Tasks
12855
12856             elsif Nkind (P) = N_Task_Definition then
12857                null;
12858
12859             --  Anything else is incorrect
12860
12861             else
12862                Pragma_Misplaced;
12863             end if;
12864
12865             if Has_Relative_Deadline_Pragma (P) then
12866                Error_Pragma ("duplicate pragma% not allowed");
12867             else
12868                Set_Has_Relative_Deadline_Pragma (P, True);
12869
12870                if Nkind (P) = N_Task_Definition then
12871                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
12872                end if;
12873             end if;
12874          end Relative_Deadline;
12875
12876          ---------------------------
12877          -- Remote_Call_Interface --
12878          ---------------------------
12879
12880          --  pragma Remote_Call_Interface [(library_unit_NAME)];
12881
12882          when Pragma_Remote_Call_Interface => Remote_Call_Interface : declare
12883             Cunit_Node : Node_Id;
12884             Cunit_Ent  : Entity_Id;
12885             K          : Node_Kind;
12886
12887          begin
12888             Check_Ada_83_Warning;
12889             Check_Valid_Library_Unit_Pragma;
12890
12891             if Nkind (N) = N_Null_Statement then
12892                return;
12893             end if;
12894
12895             Cunit_Node := Cunit (Current_Sem_Unit);
12896             K          := Nkind (Unit (Cunit_Node));
12897             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12898
12899             if K = N_Package_Declaration
12900               or else K = N_Generic_Package_Declaration
12901               or else K = N_Subprogram_Declaration
12902               or else K = N_Generic_Subprogram_Declaration
12903               or else (K = N_Subprogram_Body
12904                          and then Acts_As_Spec (Unit (Cunit_Node)))
12905             then
12906                null;
12907             else
12908                Error_Pragma (
12909                  "pragma% must apply to package or subprogram declaration");
12910             end if;
12911
12912             Set_Is_Remote_Call_Interface (Cunit_Ent);
12913          end Remote_Call_Interface;
12914
12915          ------------------
12916          -- Remote_Types --
12917          ------------------
12918
12919          --  pragma Remote_Types [(library_unit_NAME)];
12920
12921          when Pragma_Remote_Types => Remote_Types : declare
12922             Cunit_Node : Node_Id;
12923             Cunit_Ent  : Entity_Id;
12924
12925          begin
12926             Check_Ada_83_Warning;
12927             Check_Valid_Library_Unit_Pragma;
12928
12929             if Nkind (N) = N_Null_Statement then
12930                return;
12931             end if;
12932
12933             Cunit_Node := Cunit (Current_Sem_Unit);
12934             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12935
12936             if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
12937                                                 N_Generic_Package_Declaration)
12938             then
12939                Error_Pragma
12940                  ("pragma% can only apply to a package declaration");
12941             end if;
12942
12943             Set_Is_Remote_Types (Cunit_Ent);
12944          end Remote_Types;
12945
12946          ---------------
12947          -- Ravenscar --
12948          ---------------
12949
12950          --  pragma Ravenscar;
12951
12952          when Pragma_Ravenscar =>
12953             GNAT_Pragma;
12954             Check_Arg_Count (0);
12955             Check_Valid_Configuration_Pragma;
12956             Set_Ravenscar_Profile (N);
12957
12958             if Warn_On_Obsolescent_Feature then
12959                Error_Msg_N ("pragma Ravenscar is an obsolescent feature?", N);
12960                Error_Msg_N ("|use pragma Profile (Ravenscar) instead", N);
12961             end if;
12962
12963          -------------------------
12964          -- Restricted_Run_Time --
12965          -------------------------
12966
12967          --  pragma Restricted_Run_Time;
12968
12969          when Pragma_Restricted_Run_Time =>
12970             GNAT_Pragma;
12971             Check_Arg_Count (0);
12972             Check_Valid_Configuration_Pragma;
12973             Set_Profile_Restrictions
12974               (Restricted, N, Warn => Treat_Restrictions_As_Warnings);
12975
12976             if Warn_On_Obsolescent_Feature then
12977                Error_Msg_N
12978                  ("pragma Restricted_Run_Time is an obsolescent feature?", N);
12979                Error_Msg_N ("|use pragma Profile (Restricted) instead", N);
12980             end if;
12981
12982          ------------------
12983          -- Restrictions --
12984          ------------------
12985
12986          --  pragma Restrictions (RESTRICTION {, RESTRICTION});
12987
12988          --  RESTRICTION ::=
12989          --    restriction_IDENTIFIER
12990          --  | restriction_parameter_IDENTIFIER => EXPRESSION
12991
12992          when Pragma_Restrictions =>
12993             Process_Restrictions_Or_Restriction_Warnings
12994               (Warn => Treat_Restrictions_As_Warnings);
12995
12996          --------------------------
12997          -- Restriction_Warnings --
12998          --------------------------
12999
13000          --  pragma Restriction_Warnings (RESTRICTION {, RESTRICTION});
13001
13002          --  RESTRICTION ::=
13003          --    restriction_IDENTIFIER
13004          --  | restriction_parameter_IDENTIFIER => EXPRESSION
13005
13006          when Pragma_Restriction_Warnings =>
13007             GNAT_Pragma;
13008             Process_Restrictions_Or_Restriction_Warnings (Warn => True);
13009
13010          ----------------
13011          -- Reviewable --
13012          ----------------
13013
13014          --  pragma Reviewable;
13015
13016          when Pragma_Reviewable =>
13017             Check_Ada_83_Warning;
13018             Check_Arg_Count (0);
13019
13020             --  Call dummy debugging function rv. This is done to assist front
13021             --  end debugging. By placing a Reviewable pragma in the source
13022             --  program, a breakpoint on rv catches this place in the source,
13023             --  allowing convenient stepping to the point of interest.
13024
13025             rv;
13026
13027          --------------------------
13028          -- Short_Circuit_And_Or --
13029          --------------------------
13030
13031          when Pragma_Short_Circuit_And_Or =>
13032             GNAT_Pragma;
13033             Check_Arg_Count (0);
13034             Check_Valid_Configuration_Pragma;
13035             Short_Circuit_And_Or := True;
13036
13037          -------------------
13038          -- Share_Generic --
13039          -------------------
13040
13041          --  pragma Share_Generic (NAME {, NAME});
13042
13043          when Pragma_Share_Generic =>
13044             GNAT_Pragma;
13045             Process_Generic_List;
13046
13047          ------------
13048          -- Shared --
13049          ------------
13050
13051          --  pragma Shared (LOCAL_NAME);
13052
13053          when Pragma_Shared =>
13054             GNAT_Pragma;
13055             Process_Atomic_Shared_Volatile;
13056
13057          --------------------
13058          -- Shared_Passive --
13059          --------------------
13060
13061          --  pragma Shared_Passive [(library_unit_NAME)];
13062
13063          --  Set the flag Is_Shared_Passive of program unit name entity
13064
13065          when Pragma_Shared_Passive => Shared_Passive : declare
13066             Cunit_Node : Node_Id;
13067             Cunit_Ent  : Entity_Id;
13068
13069          begin
13070             Check_Ada_83_Warning;
13071             Check_Valid_Library_Unit_Pragma;
13072
13073             if Nkind (N) = N_Null_Statement then
13074                return;
13075             end if;
13076
13077             Cunit_Node := Cunit (Current_Sem_Unit);
13078             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
13079
13080             if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
13081                                                 N_Generic_Package_Declaration)
13082             then
13083                Error_Pragma
13084                  ("pragma% can only apply to a package declaration");
13085             end if;
13086
13087             Set_Is_Shared_Passive (Cunit_Ent);
13088          end Shared_Passive;
13089
13090          -----------------------
13091          -- Short_Descriptors --
13092          -----------------------
13093
13094          --  pragma Short_Descriptors;
13095
13096          when Pragma_Short_Descriptors =>
13097             GNAT_Pragma;
13098             Check_Arg_Count (0);
13099             Check_Valid_Configuration_Pragma;
13100             Short_Descriptors := True;
13101
13102          ----------------------
13103          -- Source_File_Name --
13104          ----------------------
13105
13106          --  There are five forms for this pragma:
13107
13108          --  pragma Source_File_Name (
13109          --    [UNIT_NAME      =>] unit_NAME,
13110          --     BODY_FILE_NAME =>  STRING_LITERAL
13111          --    [, [INDEX =>] INTEGER_LITERAL]);
13112
13113          --  pragma Source_File_Name (
13114          --    [UNIT_NAME      =>] unit_NAME,
13115          --     SPEC_FILE_NAME =>  STRING_LITERAL
13116          --    [, [INDEX =>] INTEGER_LITERAL]);
13117
13118          --  pragma Source_File_Name (
13119          --     BODY_FILE_NAME  => STRING_LITERAL
13120          --  [, DOT_REPLACEMENT => STRING_LITERAL]
13121          --  [, CASING          => CASING_SPEC]);
13122
13123          --  pragma Source_File_Name (
13124          --     SPEC_FILE_NAME  => STRING_LITERAL
13125          --  [, DOT_REPLACEMENT => STRING_LITERAL]
13126          --  [, CASING          => CASING_SPEC]);
13127
13128          --  pragma Source_File_Name (
13129          --     SUBUNIT_FILE_NAME  => STRING_LITERAL
13130          --  [, DOT_REPLACEMENT    => STRING_LITERAL]
13131          --  [, CASING             => CASING_SPEC]);
13132
13133          --  CASING_SPEC ::= Uppercase | Lowercase | Mixedcase
13134
13135          --  Pragma Source_File_Name_Project (SFNP) is equivalent to pragma
13136          --  Source_File_Name (SFN), however their usage is exclusive: SFN can
13137          --  only be used when no project file is used, while SFNP can only be
13138          --  used when a project file is used.
13139
13140          --  No processing here. Processing was completed during parsing, since
13141          --  we need to have file names set as early as possible. Units are
13142          --  loaded well before semantic processing starts.
13143
13144          --  The only processing we defer to this point is the check for
13145          --  correct placement.
13146
13147          when Pragma_Source_File_Name =>
13148             GNAT_Pragma;
13149             Check_Valid_Configuration_Pragma;
13150
13151          ------------------------------
13152          -- Source_File_Name_Project --
13153          ------------------------------
13154
13155          --  See Source_File_Name for syntax
13156
13157          --  No processing here. Processing was completed during parsing, since
13158          --  we need to have file names set as early as possible. Units are
13159          --  loaded well before semantic processing starts.
13160
13161          --  The only processing we defer to this point is the check for
13162          --  correct placement.
13163
13164          when Pragma_Source_File_Name_Project =>
13165             GNAT_Pragma;
13166             Check_Valid_Configuration_Pragma;
13167
13168             --  Check that a pragma Source_File_Name_Project is used only in a
13169             --  configuration pragmas file.
13170
13171             --  Pragmas Source_File_Name_Project should only be generated by
13172             --  the Project Manager in configuration pragmas files.
13173
13174             --  This is really an ugly test. It seems to depend on some
13175             --  accidental and undocumented property. At the very least it
13176             --  needs to be documented, but it would be better to have a
13177             --  clean way of testing if we are in a configuration file???
13178
13179             if Present (Parent (N)) then
13180                Error_Pragma
13181                  ("pragma% can only appear in a configuration pragmas file");
13182             end if;
13183
13184          ----------------------
13185          -- Source_Reference --
13186          ----------------------
13187
13188          --  pragma Source_Reference (INTEGER_LITERAL [, STRING_LITERAL]);
13189
13190          --  Nothing to do, all processing completed in Par.Prag, since we need
13191          --  the information for possible parser messages that are output.
13192
13193          when Pragma_Source_Reference =>
13194             GNAT_Pragma;
13195
13196          --------------------------------
13197          -- Static_Elaboration_Desired --
13198          --------------------------------
13199
13200          --  pragma Static_Elaboration_Desired (DIRECT_NAME);
13201
13202          when Pragma_Static_Elaboration_Desired =>
13203             GNAT_Pragma;
13204             Check_At_Most_N_Arguments (1);
13205
13206             if Is_Compilation_Unit (Current_Scope)
13207               and then Ekind (Current_Scope) = E_Package
13208             then
13209                Set_Static_Elaboration_Desired (Current_Scope, True);
13210             else
13211                Error_Pragma ("pragma% must apply to a library-level package");
13212             end if;
13213
13214          ------------------
13215          -- Storage_Size --
13216          ------------------
13217
13218          --  pragma Storage_Size (EXPRESSION);
13219
13220          when Pragma_Storage_Size => Storage_Size : declare
13221             P   : constant Node_Id := Parent (N);
13222             Arg : Node_Id;
13223
13224          begin
13225             Check_No_Identifiers;
13226             Check_Arg_Count (1);
13227
13228             --  The expression must be analyzed in the special manner described
13229             --  in "Handling of Default Expressions" in sem.ads.
13230
13231             Arg := Get_Pragma_Arg (Arg1);
13232             Preanalyze_Spec_Expression (Arg, Any_Integer);
13233
13234             if not Is_Static_Expression (Arg) then
13235                Check_Restriction (Static_Storage_Size, Arg);
13236             end if;
13237
13238             if Nkind (P) /= N_Task_Definition then
13239                Pragma_Misplaced;
13240                return;
13241
13242             else
13243                if Has_Storage_Size_Pragma (P) then
13244                   Error_Pragma ("duplicate pragma% not allowed");
13245                else
13246                   Set_Has_Storage_Size_Pragma (P, True);
13247                end if;
13248
13249                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
13250                --  ???  exp_ch9 should use this!
13251             end if;
13252          end Storage_Size;
13253
13254          ------------------
13255          -- Storage_Unit --
13256          ------------------
13257
13258          --  pragma Storage_Unit (NUMERIC_LITERAL);
13259
13260          --  Only permitted argument is System'Storage_Unit value
13261
13262          when Pragma_Storage_Unit =>
13263             Check_No_Identifiers;
13264             Check_Arg_Count (1);
13265             Check_Arg_Is_Integer_Literal (Arg1);
13266
13267             if Intval (Get_Pragma_Arg (Arg1)) /=
13268               UI_From_Int (Ttypes.System_Storage_Unit)
13269             then
13270                Error_Msg_Uint_1 := UI_From_Int (Ttypes.System_Storage_Unit);
13271                Error_Pragma_Arg
13272                  ("the only allowed argument for pragma% is ^", Arg1);
13273             end if;
13274
13275          --------------------
13276          -- Stream_Convert --
13277          --------------------
13278
13279          --  pragma Stream_Convert (
13280          --    [Entity =>] type_LOCAL_NAME,
13281          --    [Read   =>] function_NAME,
13282          --    [Write  =>] function NAME);
13283
13284          when Pragma_Stream_Convert => Stream_Convert : declare
13285
13286             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id);
13287             --  Check that the given argument is the name of a local function
13288             --  of one argument that is not overloaded earlier in the current
13289             --  local scope. A check is also made that the argument is a
13290             --  function with one parameter.
13291
13292             --------------------------------------
13293             -- Check_OK_Stream_Convert_Function --
13294             --------------------------------------
13295
13296             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id) is
13297                Ent : Entity_Id;
13298
13299             begin
13300                Check_Arg_Is_Local_Name (Arg);
13301                Ent := Entity (Get_Pragma_Arg (Arg));
13302
13303                if Has_Homonym (Ent) then
13304                   Error_Pragma_Arg
13305                     ("argument for pragma% may not be overloaded", Arg);
13306                end if;
13307
13308                if Ekind (Ent) /= E_Function
13309                  or else No (First_Formal (Ent))
13310                  or else Present (Next_Formal (First_Formal (Ent)))
13311                then
13312                   Error_Pragma_Arg
13313                     ("argument for pragma% must be" &
13314                      " function of one argument", Arg);
13315                end if;
13316             end Check_OK_Stream_Convert_Function;
13317
13318          --  Start of processing for Stream_Convert
13319
13320          begin
13321             GNAT_Pragma;
13322             Check_Arg_Order ((Name_Entity, Name_Read, Name_Write));
13323             Check_Arg_Count (3);
13324             Check_Optional_Identifier (Arg1, Name_Entity);
13325             Check_Optional_Identifier (Arg2, Name_Read);
13326             Check_Optional_Identifier (Arg3, Name_Write);
13327             Check_Arg_Is_Local_Name (Arg1);
13328             Check_OK_Stream_Convert_Function (Arg2);
13329             Check_OK_Stream_Convert_Function (Arg3);
13330
13331             declare
13332                Typ   : constant Entity_Id :=
13333                          Underlying_Type (Entity (Get_Pragma_Arg (Arg1)));
13334                Read  : constant Entity_Id := Entity (Get_Pragma_Arg (Arg2));
13335                Write : constant Entity_Id := Entity (Get_Pragma_Arg (Arg3));
13336
13337             begin
13338                Check_First_Subtype (Arg1);
13339
13340                --  Check for too early or too late. Note that we don't enforce
13341                --  the rule about primitive operations in this case, since, as
13342                --  is the case for explicit stream attributes themselves, these
13343                --  restrictions are not appropriate. Note that the chaining of
13344                --  the pragma by Rep_Item_Too_Late is actually the critical
13345                --  processing done for this pragma.
13346
13347                if Rep_Item_Too_Early (Typ, N)
13348                     or else
13349                   Rep_Item_Too_Late (Typ, N, FOnly => True)
13350                then
13351                   return;
13352                end if;
13353
13354                --  Return if previous error
13355
13356                if Etype (Typ) = Any_Type
13357                     or else
13358                   Etype (Read) = Any_Type
13359                     or else
13360                   Etype (Write) = Any_Type
13361                then
13362                   return;
13363                end if;
13364
13365                --  Error checks
13366
13367                if Underlying_Type (Etype (Read)) /= Typ then
13368                   Error_Pragma_Arg
13369                     ("incorrect return type for function&", Arg2);
13370                end if;
13371
13372                if Underlying_Type (Etype (First_Formal (Write))) /= Typ then
13373                   Error_Pragma_Arg
13374                     ("incorrect parameter type for function&", Arg3);
13375                end if;
13376
13377                if Underlying_Type (Etype (First_Formal (Read))) /=
13378                   Underlying_Type (Etype (Write))
13379                then
13380                   Error_Pragma_Arg
13381                     ("result type of & does not match Read parameter type",
13382                      Arg3);
13383                end if;
13384             end;
13385          end Stream_Convert;
13386
13387          -------------------------
13388          -- Style_Checks (GNAT) --
13389          -------------------------
13390
13391          --  pragma Style_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
13392
13393          --  This is processed by the parser since some of the style checks
13394          --  take place during source scanning and parsing. This means that
13395          --  we don't need to issue error messages here.
13396
13397          when Pragma_Style_Checks => Style_Checks : declare
13398             A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
13399             S  : String_Id;
13400             C  : Char_Code;
13401
13402          begin
13403             GNAT_Pragma;
13404             Check_No_Identifiers;
13405
13406             --  Two argument form
13407
13408             if Arg_Count = 2 then
13409                Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
13410
13411                declare
13412                   E_Id : Node_Id;
13413                   E    : Entity_Id;
13414
13415                begin
13416                   E_Id := Get_Pragma_Arg (Arg2);
13417                   Analyze (E_Id);
13418
13419                   if not Is_Entity_Name (E_Id) then
13420                      Error_Pragma_Arg
13421                        ("second argument of pragma% must be entity name",
13422                         Arg2);
13423                   end if;
13424
13425                   E := Entity (E_Id);
13426
13427                   if E = Any_Id then
13428                      return;
13429                   else
13430                      loop
13431                         Set_Suppress_Style_Checks (E,
13432                           (Chars (Get_Pragma_Arg (Arg1)) = Name_Off));
13433                         exit when No (Homonym (E));
13434                         E := Homonym (E);
13435                      end loop;
13436                   end if;
13437                end;
13438
13439             --  One argument form
13440
13441             else
13442                Check_Arg_Count (1);
13443
13444                if Nkind (A) = N_String_Literal then
13445                   S   := Strval (A);
13446
13447                   declare
13448                      Slen    : constant Natural := Natural (String_Length (S));
13449                      Options : String (1 .. Slen);
13450                      J       : Natural;
13451
13452                   begin
13453                      J := 1;
13454                      loop
13455                         C := Get_String_Char (S, Int (J));
13456                         exit when not In_Character_Range (C);
13457                         Options (J) := Get_Character (C);
13458
13459                         --  If at end of string, set options. As per discussion
13460                         --  above, no need to check for errors, since we issued
13461                         --  them in the parser.
13462
13463                         if J = Slen then
13464                            Set_Style_Check_Options (Options);
13465                            exit;
13466                         end if;
13467
13468                         J := J + 1;
13469                      end loop;
13470                   end;
13471
13472                elsif Nkind (A) = N_Identifier then
13473                   if Chars (A) = Name_All_Checks then
13474                      if GNAT_Mode then
13475                         Set_GNAT_Style_Check_Options;
13476                      else
13477                         Set_Default_Style_Check_Options;
13478                      end if;
13479
13480                   elsif Chars (A) = Name_On then
13481                      Style_Check := True;
13482
13483                   elsif Chars (A) = Name_Off then
13484                      Style_Check := False;
13485                   end if;
13486                end if;
13487             end if;
13488          end Style_Checks;
13489
13490          --------------
13491          -- Subtitle --
13492          --------------
13493
13494          --  pragma Subtitle ([Subtitle =>] STRING_LITERAL);
13495
13496          when Pragma_Subtitle =>
13497             GNAT_Pragma;
13498             Check_Arg_Count (1);
13499             Check_Optional_Identifier (Arg1, Name_Subtitle);
13500             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
13501             Store_Note (N);
13502
13503          --------------
13504          -- Suppress --
13505          --------------
13506
13507          --  pragma Suppress (IDENTIFIER [, [On =>] NAME]);
13508
13509          when Pragma_Suppress =>
13510             Process_Suppress_Unsuppress (True);
13511
13512          ------------------
13513          -- Suppress_All --
13514          ------------------
13515
13516          --  pragma Suppress_All;
13517
13518          --  The only check made here is that the pragma has no arguments.
13519          --  There are no placement rules, and the processing required (setting
13520          --  the Has_Pragma_Suppress_All flag in the compilation unit node was
13521          --  taken care of by the parser). Process_Compilation_Unit_Pragmas
13522          --  then creates and inserts a pragma Suppress (All_Checks).
13523
13524          when Pragma_Suppress_All =>
13525             GNAT_Pragma;
13526             Check_Arg_Count (0);
13527
13528          -------------------------
13529          -- Suppress_Debug_Info --
13530          -------------------------
13531
13532          --  pragma Suppress_Debug_Info ([Entity =>] LOCAL_NAME);
13533
13534          when Pragma_Suppress_Debug_Info =>
13535             GNAT_Pragma;
13536             Check_Arg_Count (1);
13537             Check_Optional_Identifier (Arg1, Name_Entity);
13538             Check_Arg_Is_Local_Name (Arg1);
13539             Set_Debug_Info_Off (Entity (Get_Pragma_Arg (Arg1)));
13540
13541          ----------------------------------
13542          -- Suppress_Exception_Locations --
13543          ----------------------------------
13544
13545          --  pragma Suppress_Exception_Locations;
13546
13547          when Pragma_Suppress_Exception_Locations =>
13548             GNAT_Pragma;
13549             Check_Arg_Count (0);
13550             Check_Valid_Configuration_Pragma;
13551             Exception_Locations_Suppressed := True;
13552
13553          -----------------------------
13554          -- Suppress_Initialization --
13555          -----------------------------
13556
13557          --  pragma Suppress_Initialization ([Entity =>] type_Name);
13558
13559          when Pragma_Suppress_Initialization => Suppress_Init : declare
13560             E_Id : Node_Id;
13561             E    : Entity_Id;
13562
13563          begin
13564             GNAT_Pragma;
13565             Check_Arg_Count (1);
13566             Check_Optional_Identifier (Arg1, Name_Entity);
13567             Check_Arg_Is_Local_Name (Arg1);
13568
13569             E_Id := Get_Pragma_Arg (Arg1);
13570
13571             if Etype (E_Id) = Any_Type then
13572                return;
13573             end if;
13574
13575             E := Entity (E_Id);
13576
13577             if not Is_Type (E) then
13578                Error_Pragma_Arg ("pragma% requires type or subtype", Arg1);
13579             end if;
13580
13581             if Rep_Item_Too_Early (E, N)
13582                  or else
13583                Rep_Item_Too_Late (E, N, FOnly => True)
13584             then
13585                return;
13586             end if;
13587
13588             --  For incomplete/private type, set flag on full view
13589
13590             if Is_Incomplete_Or_Private_Type (E) then
13591                if No (Full_View (Base_Type (E))) then
13592                   Error_Pragma_Arg
13593                     ("argument of pragma% cannot be an incomplete type", Arg1);
13594                else
13595                   Set_Suppress_Initialization (Full_View (Base_Type (E)));
13596                end if;
13597
13598             --  For first subtype, set flag on base type
13599
13600             elsif Is_First_Subtype (E) then
13601                Set_Suppress_Initialization (Base_Type (E));
13602
13603             --  For other than first subtype, set flag on subtype itself
13604
13605             else
13606                Set_Suppress_Initialization (E);
13607             end if;
13608          end Suppress_Init;
13609
13610          -----------------
13611          -- System_Name --
13612          -----------------
13613
13614          --  pragma System_Name (DIRECT_NAME);
13615
13616          --  Syntax check: one argument, which must be the identifier GNAT or
13617          --  the identifier GCC, no other identifiers are acceptable.
13618
13619          when Pragma_System_Name =>
13620             GNAT_Pragma;
13621             Check_No_Identifiers;
13622             Check_Arg_Count (1);
13623             Check_Arg_Is_One_Of (Arg1, Name_Gcc, Name_Gnat);
13624
13625          -----------------------------
13626          -- Task_Dispatching_Policy --
13627          -----------------------------
13628
13629          --  pragma Task_Dispatching_Policy (policy_IDENTIFIER);
13630
13631          when Pragma_Task_Dispatching_Policy => declare
13632             DP : Character;
13633
13634          begin
13635             Check_Ada_83_Warning;
13636             Check_Arg_Count (1);
13637             Check_No_Identifiers;
13638             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
13639             Check_Valid_Configuration_Pragma;
13640             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
13641             DP := Fold_Upper (Name_Buffer (1));
13642
13643             if Task_Dispatching_Policy /= ' '
13644               and then Task_Dispatching_Policy /= DP
13645             then
13646                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
13647                Error_Pragma
13648                  ("task dispatching policy incompatible with policy#");
13649
13650             --  Set new policy, but always preserve System_Location since we
13651             --  like the error message with the run time name.
13652
13653             else
13654                Task_Dispatching_Policy := DP;
13655
13656                if Task_Dispatching_Policy_Sloc /= System_Location then
13657                   Task_Dispatching_Policy_Sloc := Loc;
13658                end if;
13659             end if;
13660          end;
13661
13662          ---------------
13663          -- Task_Info --
13664          ---------------
13665
13666          --  pragma Task_Info (EXPRESSION);
13667
13668          when Pragma_Task_Info => Task_Info : declare
13669             P : constant Node_Id := Parent (N);
13670
13671          begin
13672             GNAT_Pragma;
13673
13674             if Nkind (P) /= N_Task_Definition then
13675                Error_Pragma ("pragma% must appear in task definition");
13676             end if;
13677
13678             Check_No_Identifiers;
13679             Check_Arg_Count (1);
13680
13681             Analyze_And_Resolve
13682               (Get_Pragma_Arg (Arg1), RTE (RE_Task_Info_Type));
13683
13684             if Etype (Get_Pragma_Arg (Arg1)) = Any_Type then
13685                return;
13686             end if;
13687
13688             if Has_Task_Info_Pragma (P) then
13689                Error_Pragma ("duplicate pragma% not allowed");
13690             else
13691                Set_Has_Task_Info_Pragma (P, True);
13692             end if;
13693          end Task_Info;
13694
13695          ---------------
13696          -- Task_Name --
13697          ---------------
13698
13699          --  pragma Task_Name (string_EXPRESSION);
13700
13701          when Pragma_Task_Name => Task_Name : declare
13702             P   : constant Node_Id := Parent (N);
13703             Arg : Node_Id;
13704
13705          begin
13706             Check_No_Identifiers;
13707             Check_Arg_Count (1);
13708
13709             Arg := Get_Pragma_Arg (Arg1);
13710
13711             --  The expression is used in the call to Create_Task, and must be
13712             --  expanded there, not in the context of the current spec. It must
13713             --  however be analyzed to capture global references, in case it
13714             --  appears in a generic context.
13715
13716             Preanalyze_And_Resolve (Arg, Standard_String);
13717
13718             if Nkind (P) /= N_Task_Definition then
13719                Pragma_Misplaced;
13720             end if;
13721
13722             if Has_Task_Name_Pragma (P) then
13723                Error_Pragma ("duplicate pragma% not allowed");
13724             else
13725                Set_Has_Task_Name_Pragma (P, True);
13726                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
13727             end if;
13728          end Task_Name;
13729
13730          ------------------
13731          -- Task_Storage --
13732          ------------------
13733
13734          --  pragma Task_Storage (
13735          --     [Task_Type =>] LOCAL_NAME,
13736          --     [Top_Guard =>] static_integer_EXPRESSION);
13737
13738          when Pragma_Task_Storage => Task_Storage : declare
13739             Args  : Args_List (1 .. 2);
13740             Names : constant Name_List (1 .. 2) := (
13741                       Name_Task_Type,
13742                       Name_Top_Guard);
13743
13744             Task_Type : Node_Id renames Args (1);
13745             Top_Guard : Node_Id renames Args (2);
13746
13747             Ent : Entity_Id;
13748
13749          begin
13750             GNAT_Pragma;
13751             Gather_Associations (Names, Args);
13752
13753             if No (Task_Type) then
13754                Error_Pragma
13755                  ("missing task_type argument for pragma%");
13756             end if;
13757
13758             Check_Arg_Is_Local_Name (Task_Type);
13759
13760             Ent := Entity (Task_Type);
13761
13762             if not Is_Task_Type (Ent) then
13763                Error_Pragma_Arg
13764                  ("argument for pragma% must be task type", Task_Type);
13765             end if;
13766
13767             if No (Top_Guard) then
13768                Error_Pragma_Arg
13769                  ("pragma% takes two arguments", Task_Type);
13770             else
13771                Check_Arg_Is_Static_Expression (Top_Guard, Any_Integer);
13772             end if;
13773
13774             Check_First_Subtype (Task_Type);
13775
13776             if Rep_Item_Too_Late (Ent, N) then
13777                raise Pragma_Exit;
13778             end if;
13779          end Task_Storage;
13780
13781          ---------------
13782          -- Test_Case --
13783          ---------------
13784
13785          --  pragma Test_Case ([Name     =>] Static_String_EXPRESSION
13786          --                   ,[Mode     =>] MODE_TYPE
13787          --                  [, Requires =>  Boolean_EXPRESSION]
13788          --                  [, Ensures  =>  Boolean_EXPRESSION]);
13789
13790          --  MODE_TYPE ::= Nominal | Robustness
13791
13792          when Pragma_Test_Case => Test_Case : declare
13793          begin
13794             GNAT_Pragma;
13795             Check_At_Least_N_Arguments (2);
13796             Check_At_Most_N_Arguments (4);
13797             Check_Arg_Order
13798                  ((Name_Name, Name_Mode, Name_Requires, Name_Ensures));
13799
13800             Check_Optional_Identifier (Arg1, Name_Name);
13801             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
13802
13803             --  In ASIS mode, for a pragma generated from a source aspect, also
13804             --  analyze the original aspect expression.
13805
13806             if ASIS_Mode
13807               and then Present (Corresponding_Aspect (N))
13808             then
13809                Check_Expr_Is_Static_Expression
13810                  (Original_Node (Get_Pragma_Arg (Arg1)), Standard_String);
13811             end if;
13812
13813             Check_Optional_Identifier (Arg2, Name_Mode);
13814             Check_Arg_Is_One_Of (Arg2, Name_Nominal, Name_Robustness);
13815
13816             if Arg_Count = 4 then
13817                Check_Identifier (Arg3, Name_Requires);
13818                Check_Identifier (Arg4, Name_Ensures);
13819
13820             elsif Arg_Count = 3 then
13821                Check_Identifier_Is_One_Of (Arg3, Name_Requires, Name_Ensures);
13822             end if;
13823
13824             Check_Test_Case;
13825          end Test_Case;
13826
13827          --------------------------
13828          -- Thread_Local_Storage --
13829          --------------------------
13830
13831          --  pragma Thread_Local_Storage ([Entity =>] LOCAL_NAME);
13832
13833          when Pragma_Thread_Local_Storage => Thread_Local_Storage : declare
13834             Id : Node_Id;
13835             E  : Entity_Id;
13836
13837          begin
13838             GNAT_Pragma;
13839             Check_Arg_Count (1);
13840             Check_Optional_Identifier (Arg1, Name_Entity);
13841             Check_Arg_Is_Library_Level_Local_Name (Arg1);
13842
13843             Id := Get_Pragma_Arg (Arg1);
13844             Analyze (Id);
13845
13846             if not Is_Entity_Name (Id)
13847               or else Ekind (Entity (Id)) /= E_Variable
13848             then
13849                Error_Pragma_Arg ("local variable name required", Arg1);
13850             end if;
13851
13852             E := Entity (Id);
13853
13854             if Rep_Item_Too_Early (E, N)
13855               or else Rep_Item_Too_Late (E, N)
13856             then
13857                raise Pragma_Exit;
13858             end if;
13859
13860             Set_Has_Pragma_Thread_Local_Storage (E);
13861             Set_Has_Gigi_Rep_Item (E);
13862          end Thread_Local_Storage;
13863
13864          ----------------
13865          -- Time_Slice --
13866          ----------------
13867
13868          --  pragma Time_Slice (static_duration_EXPRESSION);
13869
13870          when Pragma_Time_Slice => Time_Slice : declare
13871             Val : Ureal;
13872             Nod : Node_Id;
13873
13874          begin
13875             GNAT_Pragma;
13876             Check_Arg_Count (1);
13877             Check_No_Identifiers;
13878             Check_In_Main_Program;
13879             Check_Arg_Is_Static_Expression (Arg1, Standard_Duration);
13880
13881             if not Error_Posted (Arg1) then
13882                Nod := Next (N);
13883                while Present (Nod) loop
13884                   if Nkind (Nod) = N_Pragma
13885                     and then Pragma_Name (Nod) = Name_Time_Slice
13886                   then
13887                      Error_Msg_Name_1 := Pname;
13888                      Error_Msg_N ("duplicate pragma% not permitted", Nod);
13889                   end if;
13890
13891                   Next (Nod);
13892                end loop;
13893             end if;
13894
13895             --  Process only if in main unit
13896
13897             if Get_Source_Unit (Loc) = Main_Unit then
13898                Opt.Time_Slice_Set := True;
13899                Val := Expr_Value_R (Get_Pragma_Arg (Arg1));
13900
13901                if Val <= Ureal_0 then
13902                   Opt.Time_Slice_Value := 0;
13903
13904                elsif Val > UR_From_Uint (UI_From_Int (1000)) then
13905                   Opt.Time_Slice_Value := 1_000_000_000;
13906
13907                else
13908                   Opt.Time_Slice_Value :=
13909                     UI_To_Int (UR_To_Uint (Val * UI_From_Int (1_000_000)));
13910                end if;
13911             end if;
13912          end Time_Slice;
13913
13914          -----------
13915          -- Title --
13916          -----------
13917
13918          --  pragma Title (TITLING_OPTION [, TITLING OPTION]);
13919
13920          --   TITLING_OPTION ::=
13921          --     [Title =>] STRING_LITERAL
13922          --   | [Subtitle =>] STRING_LITERAL
13923
13924          when Pragma_Title => Title : declare
13925             Args  : Args_List (1 .. 2);
13926             Names : constant Name_List (1 .. 2) := (
13927                       Name_Title,
13928                       Name_Subtitle);
13929
13930          begin
13931             GNAT_Pragma;
13932             Gather_Associations (Names, Args);
13933             Store_Note (N);
13934
13935             for J in 1 .. 2 loop
13936                if Present (Args (J)) then
13937                   Check_Arg_Is_Static_Expression (Args (J), Standard_String);
13938                end if;
13939             end loop;
13940          end Title;
13941
13942          ---------------------
13943          -- Unchecked_Union --
13944          ---------------------
13945
13946          --  pragma Unchecked_Union (first_subtype_LOCAL_NAME)
13947
13948          when Pragma_Unchecked_Union => Unchecked_Union : declare
13949             Assoc   : constant Node_Id := Arg1;
13950             Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
13951             Typ     : Entity_Id;
13952             Discr   : Entity_Id;
13953             Tdef    : Node_Id;
13954             Clist   : Node_Id;
13955             Vpart   : Node_Id;
13956             Comp    : Node_Id;
13957             Variant : Node_Id;
13958
13959          begin
13960             Ada_2005_Pragma;
13961             Check_No_Identifiers;
13962             Check_Arg_Count (1);
13963             Check_Arg_Is_Local_Name (Arg1);
13964
13965             Find_Type (Type_Id);
13966             Typ := Entity (Type_Id);
13967
13968             if Typ = Any_Type
13969               or else Rep_Item_Too_Early (Typ, N)
13970             then
13971                return;
13972             else
13973                Typ := Underlying_Type (Typ);
13974             end if;
13975
13976             if Rep_Item_Too_Late (Typ, N) then
13977                return;
13978             end if;
13979
13980             Check_First_Subtype (Arg1);
13981
13982             --  Note remaining cases are references to a type in the current
13983             --  declarative part. If we find an error, we post the error on
13984             --  the relevant type declaration at an appropriate point.
13985
13986             if not Is_Record_Type (Typ) then
13987                Error_Msg_N ("Unchecked_Union must be record type", Typ);
13988                return;
13989
13990             elsif Is_Tagged_Type (Typ) then
13991                Error_Msg_N ("Unchecked_Union must not be tagged", Typ);
13992                return;
13993
13994             elsif not Has_Discriminants (Typ) then
13995                Error_Msg_N
13996                 ("Unchecked_Union must have one discriminant", Typ);
13997                return;
13998
13999             --  Note: in previous versions of GNAT we used to check for limited
14000             --  types and give an error, but in fact the standard does allow
14001             --  Unchecked_Union on limited types, so this check was removed.
14002
14003             --  Proceed with basic error checks completed
14004
14005             else
14006                Discr := First_Discriminant (Typ);
14007                while Present (Discr) loop
14008                   if No (Discriminant_Default_Value (Discr)) then
14009                      Error_Msg_N
14010                        ("Unchecked_Union discriminant must have default value",
14011                         Discr);
14012                   end if;
14013
14014                   Next_Discriminant (Discr);
14015                end loop;
14016
14017                Tdef  := Type_Definition (Declaration_Node (Typ));
14018                Clist := Component_List (Tdef);
14019
14020                Comp := First (Component_Items (Clist));
14021                while Present (Comp) loop
14022                   Check_Component (Comp, Typ);
14023                   Next (Comp);
14024                end loop;
14025
14026                if No (Clist) or else No (Variant_Part (Clist)) then
14027                   Error_Msg_N
14028                     ("Unchecked_Union must have variant part",
14029                      Tdef);
14030                   return;
14031                end if;
14032
14033                Vpart := Variant_Part (Clist);
14034
14035                Variant := First (Variants (Vpart));
14036                while Present (Variant) loop
14037                   Check_Variant (Variant, Typ);
14038                   Next (Variant);
14039                end loop;
14040             end if;
14041
14042             Set_Is_Unchecked_Union  (Typ);
14043             Set_Convention (Typ, Convention_C);
14044             Set_Has_Unchecked_Union (Base_Type (Typ));
14045             Set_Is_Unchecked_Union  (Base_Type (Typ));
14046          end Unchecked_Union;
14047
14048          ------------------------
14049          -- Unimplemented_Unit --
14050          ------------------------
14051
14052          --  pragma Unimplemented_Unit;
14053
14054          --  Note: this only gives an error if we are generating code, or if
14055          --  we are in a generic library unit (where the pragma appears in the
14056          --  body, not in the spec).
14057
14058          when Pragma_Unimplemented_Unit => Unimplemented_Unit : declare
14059             Cunitent : constant Entity_Id :=
14060                          Cunit_Entity (Get_Source_Unit (Loc));
14061             Ent_Kind : constant Entity_Kind :=
14062                          Ekind (Cunitent);
14063
14064          begin
14065             GNAT_Pragma;
14066             Check_Arg_Count (0);
14067
14068             if Operating_Mode = Generate_Code
14069               or else Ent_Kind = E_Generic_Function
14070               or else Ent_Kind = E_Generic_Procedure
14071               or else Ent_Kind = E_Generic_Package
14072             then
14073                Get_Name_String (Chars (Cunitent));
14074                Set_Casing (Mixed_Case);
14075                Write_Str (Name_Buffer (1 .. Name_Len));
14076                Write_Str (" is not supported in this configuration");
14077                Write_Eol;
14078                raise Unrecoverable_Error;
14079             end if;
14080          end Unimplemented_Unit;
14081
14082          ------------------------
14083          -- Universal_Aliasing --
14084          ------------------------
14085
14086          --  pragma Universal_Aliasing [([Entity =>] type_LOCAL_NAME)];
14087
14088          when Pragma_Universal_Aliasing => Universal_Alias : declare
14089             E_Id : Entity_Id;
14090
14091          begin
14092             GNAT_Pragma;
14093             Check_Arg_Count (1);
14094             Check_Optional_Identifier (Arg2, Name_Entity);
14095             Check_Arg_Is_Local_Name (Arg1);
14096             E_Id := Entity (Get_Pragma_Arg (Arg1));
14097
14098             if E_Id = Any_Type then
14099                return;
14100             elsif No (E_Id) or else not Is_Type (E_Id) then
14101                Error_Pragma_Arg ("pragma% requires type", Arg1);
14102             end if;
14103
14104             Set_Universal_Aliasing (Implementation_Base_Type (E_Id));
14105          end Universal_Alias;
14106
14107          --------------------
14108          -- Universal_Data --
14109          --------------------
14110
14111          --  pragma Universal_Data [(library_unit_NAME)];
14112
14113          when Pragma_Universal_Data =>
14114             GNAT_Pragma;
14115
14116             --  If this is a configuration pragma, then set the universal
14117             --  addressing option, otherwise confirm that the pragma satisfies
14118             --  the requirements of library unit pragma placement and leave it
14119             --  to the GNAAMP back end to detect the pragma (avoids transitive
14120             --  setting of the option due to withed units).
14121
14122             if Is_Configuration_Pragma then
14123                Universal_Addressing_On_AAMP := True;
14124             else
14125                Check_Valid_Library_Unit_Pragma;
14126             end if;
14127
14128             if not AAMP_On_Target then
14129                Error_Pragma ("?pragma% ignored (applies only to AAMP)");
14130             end if;
14131
14132          ----------------
14133          -- Unmodified --
14134          ----------------
14135
14136          --  pragma Unmodified (local_Name {, local_Name});
14137
14138          when Pragma_Unmodified => Unmodified : declare
14139             Arg_Node : Node_Id;
14140             Arg_Expr : Node_Id;
14141             Arg_Ent  : Entity_Id;
14142
14143          begin
14144             GNAT_Pragma;
14145             Check_At_Least_N_Arguments (1);
14146
14147             --  Loop through arguments
14148
14149             Arg_Node := Arg1;
14150             while Present (Arg_Node) loop
14151                Check_No_Identifier (Arg_Node);
14152
14153                --  Note: the analyze call done by Check_Arg_Is_Local_Name will
14154                --  in fact generate reference, so that the entity will have a
14155                --  reference, which will inhibit any warnings about it not
14156                --  being referenced, and also properly show up in the ali file
14157                --  as a reference. But this reference is recorded before the
14158                --  Has_Pragma_Unreferenced flag is set, so that no warning is
14159                --  generated for this reference.
14160
14161                Check_Arg_Is_Local_Name (Arg_Node);
14162                Arg_Expr := Get_Pragma_Arg (Arg_Node);
14163
14164                if Is_Entity_Name (Arg_Expr) then
14165                   Arg_Ent := Entity (Arg_Expr);
14166
14167                   if not Is_Assignable (Arg_Ent) then
14168                      Error_Pragma_Arg
14169                        ("pragma% can only be applied to a variable",
14170                         Arg_Expr);
14171                   else
14172                      Set_Has_Pragma_Unmodified (Arg_Ent);
14173                   end if;
14174                end if;
14175
14176                Next (Arg_Node);
14177             end loop;
14178          end Unmodified;
14179
14180          ------------------
14181          -- Unreferenced --
14182          ------------------
14183
14184          --  pragma Unreferenced (local_Name {, local_Name});
14185
14186          --    or when used in a context clause:
14187
14188          --  pragma Unreferenced (library_unit_NAME {, library_unit_NAME}
14189
14190          when Pragma_Unreferenced => Unreferenced : declare
14191             Arg_Node : Node_Id;
14192             Arg_Expr : Node_Id;
14193             Arg_Ent  : Entity_Id;
14194             Citem    : Node_Id;
14195
14196          begin
14197             GNAT_Pragma;
14198             Check_At_Least_N_Arguments (1);
14199
14200             --  Check case of appearing within context clause
14201
14202             if Is_In_Context_Clause then
14203
14204                --  The arguments must all be units mentioned in a with clause
14205                --  in the same context clause. Note we already checked (in
14206                --  Par.Prag) that the arguments are either identifiers or
14207                --  selected components.
14208
14209                Arg_Node := Arg1;
14210                while Present (Arg_Node) loop
14211                   Citem := First (List_Containing (N));
14212                   while Citem /= N loop
14213                      if Nkind (Citem) = N_With_Clause
14214                        and then
14215                          Same_Name (Name (Citem), Get_Pragma_Arg (Arg_Node))
14216                      then
14217                         Set_Has_Pragma_Unreferenced
14218                           (Cunit_Entity
14219                              (Get_Source_Unit
14220                                 (Library_Unit (Citem))));
14221                         Set_Unit_Name
14222                           (Get_Pragma_Arg (Arg_Node), Name (Citem));
14223                         exit;
14224                      end if;
14225
14226                      Next (Citem);
14227                   end loop;
14228
14229                   if Citem = N then
14230                      Error_Pragma_Arg
14231                        ("argument of pragma% is not with'ed unit", Arg_Node);
14232                   end if;
14233
14234                   Next (Arg_Node);
14235                end loop;
14236
14237             --  Case of not in list of context items
14238
14239             else
14240                Arg_Node := Arg1;
14241                while Present (Arg_Node) loop
14242                   Check_No_Identifier (Arg_Node);
14243
14244                   --  Note: the analyze call done by Check_Arg_Is_Local_Name
14245                   --  will in fact generate reference, so that the entity will
14246                   --  have a reference, which will inhibit any warnings about
14247                   --  it not being referenced, and also properly show up in the
14248                   --  ali file as a reference. But this reference is recorded
14249                   --  before the Has_Pragma_Unreferenced flag is set, so that
14250                   --  no warning is generated for this reference.
14251
14252                   Check_Arg_Is_Local_Name (Arg_Node);
14253                   Arg_Expr := Get_Pragma_Arg (Arg_Node);
14254
14255                   if Is_Entity_Name (Arg_Expr) then
14256                      Arg_Ent := Entity (Arg_Expr);
14257
14258                      --  If the entity is overloaded, the pragma applies to the
14259                      --  most recent overloading, as documented. In this case,
14260                      --  name resolution does not generate a reference, so it
14261                      --  must be done here explicitly.
14262
14263                      if Is_Overloaded (Arg_Expr) then
14264                         Generate_Reference (Arg_Ent, N);
14265                      end if;
14266
14267                      Set_Has_Pragma_Unreferenced (Arg_Ent);
14268                   end if;
14269
14270                   Next (Arg_Node);
14271                end loop;
14272             end if;
14273          end Unreferenced;
14274
14275          --------------------------
14276          -- Unreferenced_Objects --
14277          --------------------------
14278
14279          --  pragma Unreferenced_Objects (local_Name {, local_Name});
14280
14281          when Pragma_Unreferenced_Objects => Unreferenced_Objects : declare
14282             Arg_Node : Node_Id;
14283             Arg_Expr : Node_Id;
14284
14285          begin
14286             GNAT_Pragma;
14287             Check_At_Least_N_Arguments (1);
14288
14289             Arg_Node := Arg1;
14290             while Present (Arg_Node) loop
14291                Check_No_Identifier (Arg_Node);
14292                Check_Arg_Is_Local_Name (Arg_Node);
14293                Arg_Expr := Get_Pragma_Arg (Arg_Node);
14294
14295                if not Is_Entity_Name (Arg_Expr)
14296                  or else not Is_Type (Entity (Arg_Expr))
14297                then
14298                   Error_Pragma_Arg
14299                     ("argument for pragma% must be type or subtype", Arg_Node);
14300                end if;
14301
14302                Set_Has_Pragma_Unreferenced_Objects (Entity (Arg_Expr));
14303                Next (Arg_Node);
14304             end loop;
14305          end Unreferenced_Objects;
14306
14307          ------------------------------
14308          -- Unreserve_All_Interrupts --
14309          ------------------------------
14310
14311          --  pragma Unreserve_All_Interrupts;
14312
14313          when Pragma_Unreserve_All_Interrupts =>
14314             GNAT_Pragma;
14315             Check_Arg_Count (0);
14316
14317             if In_Extended_Main_Code_Unit (Main_Unit_Entity) then
14318                Unreserve_All_Interrupts := True;
14319             end if;
14320
14321          ----------------
14322          -- Unsuppress --
14323          ----------------
14324
14325          --  pragma Unsuppress (IDENTIFIER [, [On =>] NAME]);
14326
14327          when Pragma_Unsuppress =>
14328             Ada_2005_Pragma;
14329             Process_Suppress_Unsuppress (False);
14330
14331          -------------------
14332          -- Use_VADS_Size --
14333          -------------------
14334
14335          --  pragma Use_VADS_Size;
14336
14337          when Pragma_Use_VADS_Size =>
14338             GNAT_Pragma;
14339             Check_Arg_Count (0);
14340             Check_Valid_Configuration_Pragma;
14341             Use_VADS_Size := True;
14342
14343          ---------------------
14344          -- Validity_Checks --
14345          ---------------------
14346
14347          --  pragma Validity_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
14348
14349          when Pragma_Validity_Checks => Validity_Checks : declare
14350             A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
14351             S  : String_Id;
14352             C  : Char_Code;
14353
14354          begin
14355             GNAT_Pragma;
14356             Check_Arg_Count (1);
14357             Check_No_Identifiers;
14358
14359             if Nkind (A) = N_String_Literal then
14360                S   := Strval (A);
14361
14362                declare
14363                   Slen    : constant Natural := Natural (String_Length (S));
14364                   Options : String (1 .. Slen);
14365                   J       : Natural;
14366
14367                begin
14368                   J := 1;
14369                   loop
14370                      C := Get_String_Char (S, Int (J));
14371                      exit when not In_Character_Range (C);
14372                      Options (J) := Get_Character (C);
14373
14374                      if J = Slen then
14375                         Set_Validity_Check_Options (Options);
14376                         exit;
14377                      else
14378                         J := J + 1;
14379                      end if;
14380                   end loop;
14381                end;
14382
14383             elsif Nkind (A) = N_Identifier then
14384                if Chars (A) = Name_All_Checks then
14385                   Set_Validity_Check_Options ("a");
14386                elsif Chars (A) = Name_On then
14387                   Validity_Checks_On := True;
14388                elsif Chars (A) = Name_Off then
14389                   Validity_Checks_On := False;
14390                end if;
14391             end if;
14392          end Validity_Checks;
14393
14394          --------------
14395          -- Volatile --
14396          --------------
14397
14398          --  pragma Volatile (LOCAL_NAME);
14399
14400          when Pragma_Volatile =>
14401             Process_Atomic_Shared_Volatile;
14402
14403          -------------------------
14404          -- Volatile_Components --
14405          -------------------------
14406
14407          --  pragma Volatile_Components (array_LOCAL_NAME);
14408
14409          --  Volatile is handled by the same circuit as Atomic_Components
14410
14411          --------------
14412          -- Warnings --
14413          --------------
14414
14415          --  pragma Warnings (On | Off);
14416          --  pragma Warnings (On | Off, LOCAL_NAME);
14417          --  pragma Warnings (static_string_EXPRESSION);
14418          --  pragma Warnings (On | Off, STRING_LITERAL);
14419
14420          when Pragma_Warnings => Warnings : begin
14421             GNAT_Pragma;
14422             Check_At_Least_N_Arguments (1);
14423             Check_No_Identifiers;
14424
14425             --  If debug flag -gnatd.i is set, pragma is ignored
14426
14427             if Debug_Flag_Dot_I then
14428                return;
14429             end if;
14430
14431             --  Process various forms of the pragma
14432
14433             declare
14434                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
14435
14436             begin
14437                --  One argument case
14438
14439                if Arg_Count = 1 then
14440
14441                   --  On/Off one argument case was processed by parser
14442
14443                   if Nkind (Argx) = N_Identifier
14444                     and then
14445                       (Chars (Argx) = Name_On
14446                          or else
14447                        Chars (Argx) = Name_Off)
14448                   then
14449                      null;
14450
14451                   --  One argument case must be ON/OFF or static string expr
14452
14453                   elsif not Is_Static_String_Expression (Arg1) then
14454                      Error_Pragma_Arg
14455                        ("argument of pragma% must be On/Off or " &
14456                         "static string expression", Arg1);
14457
14458                   --  One argument string expression case
14459
14460                   else
14461                      declare
14462                         Lit : constant Node_Id   := Expr_Value_S (Argx);
14463                         Str : constant String_Id := Strval (Lit);
14464                         Len : constant Nat       := String_Length (Str);
14465                         C   : Char_Code;
14466                         J   : Nat;
14467                         OK  : Boolean;
14468                         Chr : Character;
14469
14470                      begin
14471                         J := 1;
14472                         while J <= Len loop
14473                            C := Get_String_Char (Str, J);
14474                            OK := In_Character_Range (C);
14475
14476                            if OK then
14477                               Chr := Get_Character (C);
14478
14479                               --  Dot case
14480
14481                               if J < Len and then Chr = '.' then
14482                                  J := J + 1;
14483                                  C := Get_String_Char (Str, J);
14484                                  Chr := Get_Character (C);
14485
14486                                  if not Set_Dot_Warning_Switch (Chr) then
14487                                     Error_Pragma_Arg
14488                                       ("invalid warning switch character " &
14489                                        '.' & Chr, Arg1);
14490                                  end if;
14491
14492                               --  Non-Dot case
14493
14494                               else
14495                                  OK := Set_Warning_Switch (Chr);
14496                               end if;
14497                            end if;
14498
14499                            if not OK then
14500                               Error_Pragma_Arg
14501                                 ("invalid warning switch character " & Chr,
14502                                  Arg1);
14503                            end if;
14504
14505                            J := J + 1;
14506                         end loop;
14507                      end;
14508                   end if;
14509
14510                --  Two or more arguments (must be two)
14511
14512                else
14513                   Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
14514                   Check_At_Most_N_Arguments (2);
14515
14516                   declare
14517                      E_Id : Node_Id;
14518                      E    : Entity_Id;
14519                      Err  : Boolean;
14520
14521                   begin
14522                      E_Id := Get_Pragma_Arg (Arg2);
14523                      Analyze (E_Id);
14524
14525                      --  In the expansion of an inlined body, a reference to
14526                      --  the formal may be wrapped in a conversion if the
14527                      --  actual is a conversion. Retrieve the real entity name.
14528
14529                      if (In_Instance_Body or else In_Inlined_Body)
14530                        and then Nkind (E_Id) = N_Unchecked_Type_Conversion
14531                      then
14532                         E_Id := Expression (E_Id);
14533                      end if;
14534
14535                      --  Entity name case
14536
14537                      if Is_Entity_Name (E_Id) then
14538                         E := Entity (E_Id);
14539
14540                         if E = Any_Id then
14541                            return;
14542                         else
14543                            loop
14544                               Set_Warnings_Off
14545                                 (E, (Chars (Get_Pragma_Arg (Arg1)) =
14546                                                               Name_Off));
14547
14548                               if Chars (Get_Pragma_Arg (Arg1)) = Name_Off
14549                                 and then Warn_On_Warnings_Off
14550                               then
14551                                  Warnings_Off_Pragmas.Append ((N, E));
14552                               end if;
14553
14554                               if Is_Enumeration_Type (E) then
14555                                  declare
14556                                     Lit : Entity_Id;
14557                                  begin
14558                                     Lit := First_Literal (E);
14559                                     while Present (Lit) loop
14560                                        Set_Warnings_Off (Lit);
14561                                        Next_Literal (Lit);
14562                                     end loop;
14563                                  end;
14564                               end if;
14565
14566                               exit when No (Homonym (E));
14567                               E := Homonym (E);
14568                            end loop;
14569                         end if;
14570
14571                      --  Error if not entity or static string literal case
14572
14573                      elsif not Is_Static_String_Expression (Arg2) then
14574                         Error_Pragma_Arg
14575                           ("second argument of pragma% must be entity " &
14576                            "name or static string expression", Arg2);
14577
14578                      --  String literal case
14579
14580                      else
14581                         String_To_Name_Buffer
14582                           (Strval (Expr_Value_S (Get_Pragma_Arg (Arg2))));
14583
14584                         --  Note on configuration pragma case: If this is a
14585                         --  configuration pragma, then for an OFF pragma, we
14586                         --  just set Config True in the call, which is all
14587                         --  that needs to be done. For the case of ON, this
14588                         --  is normally an error, unless it is canceling the
14589                         --  effect of a previous OFF pragma in the same file.
14590                         --  In any other case, an error will be signalled (ON
14591                         --  with no matching OFF).
14592
14593                         --  Note: We set Used if we are inside a generic to
14594                         --  disable the test that the non-config case actually
14595                         --  cancels a warning. That's because we can't be sure
14596                         --  there isn't an instantiation in some other unit
14597                         --  where a warning is suppressed.
14598
14599                         --  We could do a little better here by checking if the
14600                         --  generic unit we are inside is public, but for now
14601                         --  we don't bother with that refinement.
14602
14603                         if Chars (Argx) = Name_Off then
14604                            Set_Specific_Warning_Off
14605                              (Loc, Name_Buffer (1 .. Name_Len),
14606                               Config => Is_Configuration_Pragma,
14607                               Used   => Inside_A_Generic or else In_Instance);
14608
14609                         elsif Chars (Argx) = Name_On then
14610                            Set_Specific_Warning_On
14611                              (Loc, Name_Buffer (1 .. Name_Len), Err);
14612
14613                            if Err then
14614                               Error_Msg
14615                                 ("?pragma Warnings On with no " &
14616                                  "matching Warnings Off",
14617                                  Loc);
14618                            end if;
14619                         end if;
14620                      end if;
14621                   end;
14622                end if;
14623             end;
14624          end Warnings;
14625
14626          -------------------
14627          -- Weak_External --
14628          -------------------
14629
14630          --  pragma Weak_External ([Entity =>] LOCAL_NAME);
14631
14632          when Pragma_Weak_External => Weak_External : declare
14633             Ent : Entity_Id;
14634
14635          begin
14636             GNAT_Pragma;
14637             Check_Arg_Count (1);
14638             Check_Optional_Identifier (Arg1, Name_Entity);
14639             Check_Arg_Is_Library_Level_Local_Name (Arg1);
14640             Ent := Entity (Get_Pragma_Arg (Arg1));
14641
14642             if Rep_Item_Too_Early (Ent, N) then
14643                return;
14644             else
14645                Ent := Underlying_Type (Ent);
14646             end if;
14647
14648             --  The only processing required is to link this item on to the
14649             --  list of rep items for the given entity. This is accomplished
14650             --  by the call to Rep_Item_Too_Late (when no error is detected
14651             --  and False is returned).
14652
14653             if Rep_Item_Too_Late (Ent, N) then
14654                return;
14655             else
14656                Set_Has_Gigi_Rep_Item (Ent);
14657             end if;
14658          end Weak_External;
14659
14660          -----------------------------
14661          -- Wide_Character_Encoding --
14662          -----------------------------
14663
14664          --  pragma Wide_Character_Encoding (IDENTIFIER);
14665
14666          when Pragma_Wide_Character_Encoding =>
14667             GNAT_Pragma;
14668
14669             --  Nothing to do, handled in parser. Note that we do not enforce
14670             --  configuration pragma placement, this pragma can appear at any
14671             --  place in the source, allowing mixed encodings within a single
14672             --  source program.
14673
14674             null;
14675
14676          --------------------
14677          -- Unknown_Pragma --
14678          --------------------
14679
14680          --  Should be impossible, since the case of an unknown pragma is
14681          --  separately processed before the case statement is entered.
14682
14683          when Unknown_Pragma =>
14684             raise Program_Error;
14685       end case;
14686
14687       --  AI05-0144: detect dangerous order dependence. Disabled for now,
14688       --  until AI is formally approved.
14689
14690       --  Check_Order_Dependence;
14691
14692    exception
14693       when Pragma_Exit => null;
14694    end Analyze_Pragma;
14695
14696    -----------------------------
14697    -- Analyze_TC_In_Decl_Part --
14698    -----------------------------
14699
14700    procedure Analyze_TC_In_Decl_Part (N : Node_Id; S : Entity_Id) is
14701    begin
14702       --  Install formals and push subprogram spec onto scope stack so that we
14703       --  can see the formals from the pragma.
14704
14705       Install_Formals (S);
14706       Push_Scope (S);
14707
14708       --  Preanalyze the boolean expressions, we treat these as spec
14709       --  expressions (i.e. similar to a default expression).
14710
14711       Preanalyze_TC_Args (N,
14712                           Get_Requires_From_Test_Case_Pragma (N),
14713                           Get_Ensures_From_Test_Case_Pragma (N));
14714
14715       --  Remove the subprogram from the scope stack now that the pre-analysis
14716       --  of the expressions in the test-case is done.
14717
14718       End_Scope;
14719    end Analyze_TC_In_Decl_Part;
14720
14721    --------------------
14722    -- Check_Disabled --
14723    --------------------
14724
14725    function Check_Disabled (Nam : Name_Id) return Boolean is
14726       PP : Node_Id;
14727
14728    begin
14729       --  Loop through entries in check policy list
14730
14731       PP := Opt.Check_Policy_List;
14732       loop
14733          --  If there are no specific entries that matched, then nothing is
14734          --  disabled, so return False.
14735
14736          if No (PP) then
14737             return False;
14738
14739          --  Here we have an entry see if it matches
14740
14741          else
14742             declare
14743                PPA : constant List_Id := Pragma_Argument_Associations (PP);
14744             begin
14745                if Nam = Chars (Get_Pragma_Arg (First (PPA))) then
14746                   return Chars (Get_Pragma_Arg (Last (PPA))) = Name_Disable;
14747                else
14748                   PP := Next_Pragma (PP);
14749                end if;
14750             end;
14751          end if;
14752       end loop;
14753    end Check_Disabled;
14754
14755    -------------------
14756    -- Check_Enabled --
14757    -------------------
14758
14759    function Check_Enabled (Nam : Name_Id) return Boolean is
14760       PP : Node_Id;
14761
14762    begin
14763       --  Loop through entries in check policy list
14764
14765       PP := Opt.Check_Policy_List;
14766       loop
14767          --  If there are no specific entries that matched, then we let the
14768          --  setting of assertions govern. Note that this provides the needed
14769          --  compatibility with the RM for the cases of assertion, invariant,
14770          --  precondition, predicate, and postcondition.
14771
14772          if No (PP) then
14773             return Assertions_Enabled;
14774
14775          --  Here we have an entry see if it matches
14776
14777          else
14778             declare
14779                PPA : constant List_Id := Pragma_Argument_Associations (PP);
14780
14781             begin
14782                if Nam = Chars (Get_Pragma_Arg (First (PPA))) then
14783                   case (Chars (Get_Pragma_Arg (Last (PPA)))) is
14784                      when Name_On | Name_Check =>
14785                         return True;
14786                      when Name_Off | Name_Ignore =>
14787                         return False;
14788                      when others =>
14789                         raise Program_Error;
14790                   end case;
14791
14792                else
14793                   PP := Next_Pragma (PP);
14794                end if;
14795             end;
14796          end if;
14797       end loop;
14798    end Check_Enabled;
14799
14800    ---------------------------------
14801    -- Delay_Config_Pragma_Analyze --
14802    ---------------------------------
14803
14804    function Delay_Config_Pragma_Analyze (N : Node_Id) return Boolean is
14805    begin
14806       return Pragma_Name (N) = Name_Interrupt_State
14807                or else
14808              Pragma_Name (N) = Name_Priority_Specific_Dispatching;
14809    end Delay_Config_Pragma_Analyze;
14810
14811    -------------------------
14812    -- Get_Base_Subprogram --
14813    -------------------------
14814
14815    function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id is
14816       Result : Entity_Id;
14817
14818    begin
14819       --  Follow subprogram renaming chain
14820
14821       Result := Def_Id;
14822       while Is_Subprogram (Result)
14823         and then
14824           Nkind (Parent (Declaration_Node (Result))) =
14825                                          N_Subprogram_Renaming_Declaration
14826         and then Present (Alias (Result))
14827       loop
14828          Result := Alias (Result);
14829       end loop;
14830
14831       return Result;
14832    end Get_Base_Subprogram;
14833
14834    ----------------
14835    -- Initialize --
14836    ----------------
14837
14838    procedure Initialize is
14839    begin
14840       Externals.Init;
14841    end Initialize;
14842
14843    -----------------------------
14844    -- Is_Config_Static_String --
14845    -----------------------------
14846
14847    function Is_Config_Static_String (Arg : Node_Id) return Boolean is
14848
14849       function Add_Config_Static_String (Arg : Node_Id) return Boolean;
14850       --  This is an internal recursive function that is just like the outer
14851       --  function except that it adds the string to the name buffer rather
14852       --  than placing the string in the name buffer.
14853
14854       ------------------------------
14855       -- Add_Config_Static_String --
14856       ------------------------------
14857
14858       function Add_Config_Static_String (Arg : Node_Id) return Boolean is
14859          N : Node_Id;
14860          C : Char_Code;
14861
14862       begin
14863          N := Arg;
14864
14865          if Nkind (N) = N_Op_Concat then
14866             if Add_Config_Static_String (Left_Opnd (N)) then
14867                N := Right_Opnd (N);
14868             else
14869                return False;
14870             end if;
14871          end if;
14872
14873          if Nkind (N) /= N_String_Literal then
14874             Error_Msg_N ("string literal expected for pragma argument", N);
14875             return False;
14876
14877          else
14878             for J in 1 .. String_Length (Strval (N)) loop
14879                C := Get_String_Char (Strval (N), J);
14880
14881                if not In_Character_Range (C) then
14882                   Error_Msg
14883                     ("string literal contains invalid wide character",
14884                      Sloc (N) + 1 + Source_Ptr (J));
14885                   return False;
14886                end if;
14887
14888                Add_Char_To_Name_Buffer (Get_Character (C));
14889             end loop;
14890          end if;
14891
14892          return True;
14893       end Add_Config_Static_String;
14894
14895    --  Start of processing for Is_Config_Static_String
14896
14897    begin
14898
14899       Name_Len := 0;
14900       return Add_Config_Static_String (Arg);
14901    end Is_Config_Static_String;
14902
14903    -----------------------------------------
14904    -- Is_Non_Significant_Pragma_Reference --
14905    -----------------------------------------
14906
14907    --  This function makes use of the following static table which indicates
14908    --  whether a given pragma is significant.
14909
14910    --  -1  indicates that references in any argument position are significant
14911    --  0   indicates that appearance in any argument is not significant
14912    --  +n  indicates that appearance as argument n is significant, but all
14913    --      other arguments are not significant
14914    --  99  special processing required (e.g. for pragma Check)
14915
14916    Sig_Flags : constant array (Pragma_Id) of Int :=
14917      (Pragma_AST_Entry                      => -1,
14918       Pragma_Abort_Defer                    => -1,
14919       Pragma_Ada_83                         => -1,
14920       Pragma_Ada_95                         => -1,
14921       Pragma_Ada_05                         => -1,
14922       Pragma_Ada_2005                       => -1,
14923       Pragma_Ada_12                         => -1,
14924       Pragma_Ada_2012                       => -1,
14925       Pragma_All_Calls_Remote               => -1,
14926       Pragma_Annotate                       => -1,
14927       Pragma_Assert                         => -1,
14928       Pragma_Assertion_Policy               =>  0,
14929       Pragma_Assume_No_Invalid_Values       =>  0,
14930       Pragma_Asynchronous                   => -1,
14931       Pragma_Atomic                         =>  0,
14932       Pragma_Atomic_Components              =>  0,
14933       Pragma_Attach_Handler                 => -1,
14934       Pragma_Check                          => 99,
14935       Pragma_Check_Name                     =>  0,
14936       Pragma_Check_Policy                   =>  0,
14937       Pragma_CIL_Constructor                => -1,
14938       Pragma_CPP_Class                      =>  0,
14939       Pragma_CPP_Constructor                =>  0,
14940       Pragma_CPP_Virtual                    =>  0,
14941       Pragma_CPP_Vtable                     =>  0,
14942       Pragma_CPU                            => -1,
14943       Pragma_C_Pass_By_Copy                 =>  0,
14944       Pragma_Comment                        =>  0,
14945       Pragma_Common_Object                  => -1,
14946       Pragma_Compile_Time_Error             => -1,
14947       Pragma_Compile_Time_Warning           => -1,
14948       Pragma_Compiler_Unit                  =>  0,
14949       Pragma_Complete_Representation        =>  0,
14950       Pragma_Complex_Representation         =>  0,
14951       Pragma_Component_Alignment            => -1,
14952       Pragma_Controlled                     =>  0,
14953       Pragma_Convention                     =>  0,
14954       Pragma_Convention_Identifier          =>  0,
14955       Pragma_Debug                          => -1,
14956       Pragma_Debug_Policy                   =>  0,
14957       Pragma_Detect_Blocking                => -1,
14958       Pragma_Default_Storage_Pool           => -1,
14959       Pragma_Dimension                      => -1,
14960       Pragma_Disable_Atomic_Synchronization => -1,
14961       Pragma_Discard_Names                  =>  0,
14962       Pragma_Dispatching_Domain             => -1,
14963       Pragma_Elaborate                      => -1,
14964       Pragma_Elaborate_All                  => -1,
14965       Pragma_Elaborate_Body                 => -1,
14966       Pragma_Elaboration_Checks             => -1,
14967       Pragma_Eliminate                      => -1,
14968       Pragma_Enable_Atomic_Synchronization  => -1,
14969       Pragma_Export                         => -1,
14970       Pragma_Export_Exception               => -1,
14971       Pragma_Export_Function                => -1,
14972       Pragma_Export_Object                  => -1,
14973       Pragma_Export_Procedure               => -1,
14974       Pragma_Export_Value                   => -1,
14975       Pragma_Export_Valued_Procedure        => -1,
14976       Pragma_Extend_System                  => -1,
14977       Pragma_Extensions_Allowed             => -1,
14978       Pragma_External                       => -1,
14979       Pragma_Favor_Top_Level                => -1,
14980       Pragma_External_Name_Casing           => -1,
14981       Pragma_Fast_Math                      => -1,
14982       Pragma_Finalize_Storage_Only          =>  0,
14983       Pragma_Float_Representation           =>  0,
14984       Pragma_Ident                          => -1,
14985       Pragma_Implementation_Defined         => -1,
14986       Pragma_Implemented                    => -1,
14987       Pragma_Implicit_Packing               =>  0,
14988       Pragma_Import                         => +2,
14989       Pragma_Import_Exception               =>  0,
14990       Pragma_Import_Function                =>  0,
14991       Pragma_Import_Object                  =>  0,
14992       Pragma_Import_Procedure               =>  0,
14993       Pragma_Import_Valued_Procedure        =>  0,
14994       Pragma_Independent                    =>  0,
14995       Pragma_Independent_Components         =>  0,
14996       Pragma_Initialize_Scalars             => -1,
14997       Pragma_Inline                         =>  0,
14998       Pragma_Inline_Always                  =>  0,
14999       Pragma_Inline_Generic                 =>  0,
15000       Pragma_Inspection_Point               => -1,
15001       Pragma_Interface                      => +2,
15002       Pragma_Interface_Name                 => +2,
15003       Pragma_Interrupt_Handler              => -1,
15004       Pragma_Interrupt_Priority             => -1,
15005       Pragma_Interrupt_State                => -1,
15006       Pragma_Invariant                      => -1,
15007       Pragma_Java_Constructor               => -1,
15008       Pragma_Java_Interface                 => -1,
15009       Pragma_Keep_Names                     =>  0,
15010       Pragma_License                        => -1,
15011       Pragma_Link_With                      => -1,
15012       Pragma_Linker_Alias                   => -1,
15013       Pragma_Linker_Constructor             => -1,
15014       Pragma_Linker_Destructor              => -1,
15015       Pragma_Linker_Options                 => -1,
15016       Pragma_Linker_Section                 => -1,
15017       Pragma_List                           => -1,
15018       Pragma_Locking_Policy                 => -1,
15019       Pragma_Long_Float                     => -1,
15020       Pragma_Machine_Attribute              => -1,
15021       Pragma_Main                           => -1,
15022       Pragma_Main_Storage                   => -1,
15023       Pragma_Memory_Size                    => -1,
15024       Pragma_No_Return                      =>  0,
15025       Pragma_No_Body                        =>  0,
15026       Pragma_No_Run_Time                    => -1,
15027       Pragma_No_Strict_Aliasing             => -1,
15028       Pragma_Normalize_Scalars              => -1,
15029       Pragma_Obsolescent                    =>  0,
15030       Pragma_Optimize                       => -1,
15031       Pragma_Optimize_Alignment             => -1,
15032       Pragma_Ordered                        =>  0,
15033       Pragma_Pack                           =>  0,
15034       Pragma_Page                           => -1,
15035       Pragma_Passive                        => -1,
15036       Pragma_Preelaborable_Initialization   => -1,
15037       Pragma_Polling                        => -1,
15038       Pragma_Persistent_BSS                 =>  0,
15039       Pragma_Postcondition                  => -1,
15040       Pragma_Precondition                   => -1,
15041       Pragma_Predicate                      => -1,
15042       Pragma_Preelaborate                   => -1,
15043       Pragma_Preelaborate_05                => -1,
15044       Pragma_Priority                       => -1,
15045       Pragma_Priority_Specific_Dispatching  => -1,
15046       Pragma_Profile                        =>  0,
15047       Pragma_Profile_Warnings               =>  0,
15048       Pragma_Propagate_Exceptions           => -1,
15049       Pragma_Psect_Object                   => -1,
15050       Pragma_Pure                           => -1,
15051       Pragma_Pure_05                        => -1,
15052       Pragma_Pure_12                        => -1,
15053       Pragma_Pure_Function                  => -1,
15054       Pragma_Queuing_Policy                 => -1,
15055       Pragma_Ravenscar                      => -1,
15056       Pragma_Relative_Deadline              => -1,
15057       Pragma_Remote_Call_Interface          => -1,
15058       Pragma_Remote_Types                   => -1,
15059       Pragma_Restricted_Run_Time            => -1,
15060       Pragma_Restriction_Warnings           => -1,
15061       Pragma_Restrictions                   => -1,
15062       Pragma_Reviewable                     => -1,
15063       Pragma_Short_Circuit_And_Or           => -1,
15064       Pragma_Share_Generic                  => -1,
15065       Pragma_Shared                         => -1,
15066       Pragma_Shared_Passive                 => -1,
15067       Pragma_Short_Descriptors              =>  0,
15068       Pragma_Source_File_Name               => -1,
15069       Pragma_Source_File_Name_Project       => -1,
15070       Pragma_Source_Reference               => -1,
15071       Pragma_Storage_Size                   => -1,
15072       Pragma_Storage_Unit                   => -1,
15073       Pragma_Static_Elaboration_Desired     => -1,
15074       Pragma_Stream_Convert                 => -1,
15075       Pragma_Style_Checks                   => -1,
15076       Pragma_Subtitle                       => -1,
15077       Pragma_Suppress                       =>  0,
15078       Pragma_Suppress_Exception_Locations   =>  0,
15079       Pragma_Suppress_All                   => -1,
15080       Pragma_Suppress_Debug_Info            =>  0,
15081       Pragma_Suppress_Initialization        =>  0,
15082       Pragma_System_Name                    => -1,
15083       Pragma_Task_Dispatching_Policy        => -1,
15084       Pragma_Task_Info                      => -1,
15085       Pragma_Task_Name                      => -1,
15086       Pragma_Task_Storage                   =>  0,
15087       Pragma_Test_Case                      => -1,
15088       Pragma_Thread_Local_Storage           =>  0,
15089       Pragma_Time_Slice                     => -1,
15090       Pragma_Title                          => -1,
15091       Pragma_Unchecked_Union                =>  0,
15092       Pragma_Unimplemented_Unit             => -1,
15093       Pragma_Universal_Aliasing             => -1,
15094       Pragma_Universal_Data                 => -1,
15095       Pragma_Unmodified                     => -1,
15096       Pragma_Unreferenced                   => -1,
15097       Pragma_Unreferenced_Objects           => -1,
15098       Pragma_Unreserve_All_Interrupts       => -1,
15099       Pragma_Unsuppress                     =>  0,
15100       Pragma_Use_VADS_Size                  => -1,
15101       Pragma_Validity_Checks                => -1,
15102       Pragma_Volatile                       =>  0,
15103       Pragma_Volatile_Components            =>  0,
15104       Pragma_Warnings                       => -1,
15105       Pragma_Weak_External                  => -1,
15106       Pragma_Wide_Character_Encoding        =>  0,
15107       Unknown_Pragma                        =>  0);
15108
15109    function Is_Non_Significant_Pragma_Reference (N : Node_Id) return Boolean is
15110       Id : Pragma_Id;
15111       P  : Node_Id;
15112       C  : Int;
15113       A  : Node_Id;
15114
15115    begin
15116       P := Parent (N);
15117
15118       if Nkind (P) /= N_Pragma_Argument_Association then
15119          return False;
15120
15121       else
15122          Id := Get_Pragma_Id (Parent (P));
15123          C := Sig_Flags (Id);
15124
15125          case C is
15126             when -1 =>
15127                return False;
15128
15129             when 0 =>
15130                return True;
15131
15132             when 99 =>
15133                case Id is
15134
15135                   --  For pragma Check, the first argument is not significant,
15136                   --  the second and the third (if present) arguments are
15137                   --  significant.
15138
15139                   when Pragma_Check =>
15140                      return
15141                        P = First (Pragma_Argument_Associations (Parent (P)));
15142
15143                   when others =>
15144                      raise Program_Error;
15145                end case;
15146
15147             when others =>
15148                A := First (Pragma_Argument_Associations (Parent (P)));
15149                for J in 1 .. C - 1 loop
15150                   if No (A) then
15151                      return False;
15152                   end if;
15153
15154                   Next (A);
15155                end loop;
15156
15157                return A = P; -- is this wrong way round ???
15158          end case;
15159       end if;
15160    end Is_Non_Significant_Pragma_Reference;
15161
15162    ------------------------------
15163    -- Is_Pragma_String_Literal --
15164    ------------------------------
15165
15166    --  This function returns true if the corresponding pragma argument is a
15167    --  static string expression. These are the only cases in which string
15168    --  literals can appear as pragma arguments. We also allow a string literal
15169    --  as the first argument to pragma Assert (although it will of course
15170    --  always generate a type error).
15171
15172    function Is_Pragma_String_Literal (Par : Node_Id) return Boolean is
15173       Pragn : constant Node_Id := Parent (Par);
15174       Assoc : constant List_Id := Pragma_Argument_Associations (Pragn);
15175       Pname : constant Name_Id := Pragma_Name (Pragn);
15176       Argn  : Natural;
15177       N     : Node_Id;
15178
15179    begin
15180       Argn := 1;
15181       N := First (Assoc);
15182       loop
15183          exit when N = Par;
15184          Argn := Argn + 1;
15185          Next (N);
15186       end loop;
15187
15188       if Pname = Name_Assert then
15189          return True;
15190
15191       elsif Pname = Name_Export then
15192          return Argn > 2;
15193
15194       elsif Pname = Name_Ident then
15195          return Argn = 1;
15196
15197       elsif Pname = Name_Import then
15198          return Argn > 2;
15199
15200       elsif Pname = Name_Interface_Name then
15201          return Argn > 1;
15202
15203       elsif Pname = Name_Linker_Alias then
15204          return Argn = 2;
15205
15206       elsif Pname = Name_Linker_Section then
15207          return Argn = 2;
15208
15209       elsif Pname = Name_Machine_Attribute then
15210          return Argn = 2;
15211
15212       elsif Pname = Name_Source_File_Name then
15213          return True;
15214
15215       elsif Pname = Name_Source_Reference then
15216          return Argn = 2;
15217
15218       elsif Pname = Name_Title then
15219          return True;
15220
15221       elsif Pname = Name_Subtitle then
15222          return True;
15223
15224       else
15225          return False;
15226       end if;
15227    end Is_Pragma_String_Literal;
15228
15229    ------------------------
15230    -- Preanalyze_TC_Args --
15231    ------------------------
15232
15233    procedure Preanalyze_TC_Args (N, Arg_Req, Arg_Ens : Node_Id) is
15234    begin
15235       --  Preanalyze the boolean expressions, we treat these as spec
15236       --  expressions (i.e. similar to a default expression).
15237
15238       if Present (Arg_Req) then
15239          Preanalyze_Spec_Expression
15240            (Get_Pragma_Arg (Arg_Req), Standard_Boolean);
15241
15242          --  In ASIS mode, for a pragma generated from a source aspect, also
15243          --  analyze the original aspect expression.
15244
15245          if ASIS_Mode
15246            and then Present (Corresponding_Aspect (N))
15247          then
15248             Preanalyze_Spec_Expression
15249               (Original_Node (Get_Pragma_Arg (Arg_Req)), Standard_Boolean);
15250          end if;
15251       end if;
15252
15253       if Present (Arg_Ens) then
15254          Preanalyze_Spec_Expression
15255            (Get_Pragma_Arg (Arg_Ens), Standard_Boolean);
15256
15257          --  In ASIS mode, for a pragma generated from a source aspect, also
15258          --  analyze the original aspect expression.
15259
15260          if ASIS_Mode
15261            and then Present (Corresponding_Aspect (N))
15262          then
15263             Preanalyze_Spec_Expression
15264               (Original_Node (Get_Pragma_Arg (Arg_Ens)), Standard_Boolean);
15265          end if;
15266       end if;
15267    end Preanalyze_TC_Args;
15268
15269    --------------------------------------
15270    -- Process_Compilation_Unit_Pragmas --
15271    --------------------------------------
15272
15273    procedure Process_Compilation_Unit_Pragmas (N : Node_Id) is
15274    begin
15275       --  A special check for pragma Suppress_All, a very strange DEC pragma,
15276       --  strange because it comes at the end of the unit. Rational has the
15277       --  same name for a pragma, but treats it as a program unit pragma, In
15278       --  GNAT we just decide to allow it anywhere at all. If it appeared then
15279       --  the flag Has_Pragma_Suppress_All was set on the compilation unit
15280       --  node, and we insert a pragma Suppress (All_Checks) at the start of
15281       --  the context clause to ensure the correct processing.
15282
15283       if Has_Pragma_Suppress_All (N) then
15284          Prepend_To (Context_Items (N),
15285            Make_Pragma (Sloc (N),
15286              Chars                        => Name_Suppress,
15287              Pragma_Argument_Associations => New_List (
15288                Make_Pragma_Argument_Association (Sloc (N),
15289                  Expression => Make_Identifier (Sloc (N), Name_All_Checks)))));
15290       end if;
15291
15292       --  Nothing else to do at the current time!
15293
15294    end Process_Compilation_Unit_Pragmas;
15295
15296    --------
15297    -- rv --
15298    --------
15299
15300    procedure rv is
15301    begin
15302       null;
15303    end rv;
15304
15305    --------------------------------
15306    -- Set_Encoded_Interface_Name --
15307    --------------------------------
15308
15309    procedure Set_Encoded_Interface_Name (E : Entity_Id; S : Node_Id) is
15310       Str : constant String_Id := Strval (S);
15311       Len : constant Int       := String_Length (Str);
15312       CC  : Char_Code;
15313       C   : Character;
15314       J   : Int;
15315
15316       Hex : constant array (0 .. 15) of Character := "0123456789abcdef";
15317
15318       procedure Encode;
15319       --  Stores encoded value of character code CC. The encoding we use an
15320       --  underscore followed by four lower case hex digits.
15321
15322       ------------
15323       -- Encode --
15324       ------------
15325
15326       procedure Encode is
15327       begin
15328          Store_String_Char (Get_Char_Code ('_'));
15329          Store_String_Char
15330            (Get_Char_Code (Hex (Integer (CC / 2 ** 12))));
15331          Store_String_Char
15332            (Get_Char_Code (Hex (Integer (CC / 2 ** 8 and 16#0F#))));
15333          Store_String_Char
15334            (Get_Char_Code (Hex (Integer (CC / 2 ** 4 and 16#0F#))));
15335          Store_String_Char
15336            (Get_Char_Code (Hex (Integer (CC and 16#0F#))));
15337       end Encode;
15338
15339    --  Start of processing for Set_Encoded_Interface_Name
15340
15341    begin
15342       --  If first character is asterisk, this is a link name, and we leave it
15343       --  completely unmodified. We also ignore null strings (the latter case
15344       --  happens only in error cases) and no encoding should occur for Java or
15345       --  AAMP interface names.
15346
15347       if Len = 0
15348         or else Get_String_Char (Str, 1) = Get_Char_Code ('*')
15349         or else VM_Target /= No_VM
15350         or else AAMP_On_Target
15351       then
15352          Set_Interface_Name (E, S);
15353
15354       else
15355          J := 1;
15356          loop
15357             CC := Get_String_Char (Str, J);
15358
15359             exit when not In_Character_Range (CC);
15360
15361             C := Get_Character (CC);
15362
15363             exit when C /= '_' and then C /= '$'
15364               and then C not in '0' .. '9'
15365               and then C not in 'a' .. 'z'
15366               and then C not in 'A' .. 'Z';
15367
15368             if J = Len then
15369                Set_Interface_Name (E, S);
15370                return;
15371
15372             else
15373                J := J + 1;
15374             end if;
15375          end loop;
15376
15377          --  Here we need to encode. The encoding we use as follows:
15378          --     three underscores  + four hex digits (lower case)
15379
15380          Start_String;
15381
15382          for J in 1 .. String_Length (Str) loop
15383             CC := Get_String_Char (Str, J);
15384
15385             if not In_Character_Range (CC) then
15386                Encode;
15387             else
15388                C := Get_Character (CC);
15389
15390                if C = '_' or else C = '$'
15391                  or else C in '0' .. '9'
15392                  or else C in 'a' .. 'z'
15393                  or else C in 'A' .. 'Z'
15394                then
15395                   Store_String_Char (CC);
15396                else
15397                   Encode;
15398                end if;
15399             end if;
15400          end loop;
15401
15402          Set_Interface_Name (E,
15403            Make_String_Literal (Sloc (S),
15404              Strval => End_String));
15405       end if;
15406    end Set_Encoded_Interface_Name;
15407
15408    -------------------
15409    -- Set_Unit_Name --
15410    -------------------
15411
15412    procedure Set_Unit_Name (N : Node_Id; With_Item : Node_Id) is
15413       Pref : Node_Id;
15414       Scop : Entity_Id;
15415
15416    begin
15417       if Nkind (N) = N_Identifier
15418         and then Nkind (With_Item) = N_Identifier
15419       then
15420          Set_Entity (N, Entity (With_Item));
15421
15422       elsif Nkind (N) = N_Selected_Component then
15423          Change_Selected_Component_To_Expanded_Name (N);
15424          Set_Entity (N, Entity (With_Item));
15425          Set_Entity (Selector_Name (N), Entity (N));
15426
15427          Pref := Prefix (N);
15428          Scop := Scope (Entity (N));
15429          while Nkind (Pref) = N_Selected_Component loop
15430             Change_Selected_Component_To_Expanded_Name (Pref);
15431             Set_Entity (Selector_Name (Pref), Scop);
15432             Set_Entity (Pref, Scop);
15433             Pref := Prefix (Pref);
15434             Scop := Scope (Scop);
15435          end loop;
15436
15437          Set_Entity (Pref, Scop);
15438       end if;
15439    end Set_Unit_Name;
15440
15441 end Sem_Prag;