OSDN Git Service

2012-02-22 Steve Baird <baird@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_prag.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                             S E M _ P R A G                              --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2012, 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          Class_Wide_Condition : 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          --  Start of processing for Class_Wide_Condition
369
370          begin
371             if not Present (T) then
372                Error_Msg_Name_1 :=
373                  Chars (Identifier (Corresponding_Aspect (N)));
374
375                Error_Msg_Name_2 := Name_Class;
376
377                Error_Msg_N
378                  ("aspect `%''%` can only be specified for a primitive " &
379                   "operation of a tagged type",
380                   Corresponding_Aspect (N));
381             end if;
382
383             Replace_Type (Get_Pragma_Arg (Arg1));
384          end Class_Wide_Condition;
385       end if;
386
387       --  Remove the subprogram from the scope stack now that the pre-analysis
388       --  of the precondition/postcondition is done.
389
390       End_Scope;
391    end Analyze_PPC_In_Decl_Part;
392
393    --------------------
394    -- Analyze_Pragma --
395    --------------------
396
397    procedure Analyze_Pragma (N : Node_Id) is
398       Loc     : constant Source_Ptr := Sloc (N);
399       Prag_Id : Pragma_Id;
400
401       Pname : Name_Id;
402       --  Name of the source pragma, or name of the corresponding aspect for
403       --  pragmas which originate in a source aspect. In the latter case, the
404       --  name may be different from the pragma name.
405
406       Pragma_Exit : exception;
407       --  This exception is used to exit pragma processing completely. It is
408       --  used when an error is detected, and no further processing is
409       --  required. It is also used if an earlier error has left the tree in
410       --  a state where the pragma should not be processed.
411
412       Arg_Count : Nat;
413       --  Number of pragma argument associations
414
415       Arg1 : Node_Id;
416       Arg2 : Node_Id;
417       Arg3 : Node_Id;
418       Arg4 : Node_Id;
419       --  First four pragma arguments (pragma argument association nodes, or
420       --  Empty if the corresponding argument does not exist).
421
422       type Name_List is array (Natural range <>) of Name_Id;
423       type Args_List is array (Natural range <>) of Node_Id;
424       --  Types used for arguments to Check_Arg_Order and Gather_Associations
425
426       procedure Ada_2005_Pragma;
427       --  Called for pragmas defined in Ada 2005, that are not in Ada 95. In
428       --  Ada 95 mode, these are implementation defined pragmas, so should be
429       --  caught by the No_Implementation_Pragmas restriction.
430
431       procedure Ada_2012_Pragma;
432       --  Called for pragmas defined in Ada 2012, that are not in Ada 95 or 05.
433       --  In Ada 95 or 05 mode, these are implementation defined pragmas, so
434       --  should be caught by the No_Implementation_Pragmas restriction.
435
436       procedure Check_Ada_83_Warning;
437       --  Issues a warning message for the current pragma if operating in Ada
438       --  83 mode (used for language pragmas that are not a standard part of
439       --  Ada 83). This procedure does not raise Error_Pragma. Also notes use
440       --  of 95 pragma.
441
442       procedure Check_Arg_Count (Required : Nat);
443       --  Check argument count for pragma is equal to given parameter. If not,
444       --  then issue an error message and raise Pragma_Exit.
445
446       --  Note: all routines whose name is Check_Arg_Is_xxx take an argument
447       --  Arg which can either be a pragma argument association, in which case
448       --  the check is applied to the expression of the association or an
449       --  expression directly.
450
451       procedure Check_Arg_Is_External_Name (Arg : Node_Id);
452       --  Check that an argument has the right form for an EXTERNAL_NAME
453       --  parameter of an extended import/export pragma. The rule is that the
454       --  name must be an identifier or string literal (in Ada 83 mode) or a
455       --  static string expression (in Ada 95 mode).
456
457       procedure Check_Arg_Is_Identifier (Arg : Node_Id);
458       --  Check the specified argument Arg to make sure that it is an
459       --  identifier. If not give error and raise Pragma_Exit.
460
461       procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id);
462       --  Check the specified argument Arg to make sure that it is an integer
463       --  literal. If not give error and raise Pragma_Exit.
464
465       procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id);
466       --  Check the specified argument Arg to make sure that it has the proper
467       --  syntactic form for a local name and meets the semantic requirements
468       --  for a local name. The local name is analyzed as part of the
469       --  processing for this call. In addition, the local name is required
470       --  to represent an entity at the library level.
471
472       procedure Check_Arg_Is_Local_Name (Arg : Node_Id);
473       --  Check the specified argument Arg to make sure that it has the proper
474       --  syntactic form for a local name and meets the semantic requirements
475       --  for a local name. The local name is analyzed as part of the
476       --  processing for this call.
477
478       procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id);
479       --  Check the specified argument Arg to make sure that it is a valid
480       --  locking policy name. If not give error and raise Pragma_Exit.
481
482       procedure Check_Arg_Is_One_Of
483         (Arg                : Node_Id;
484          N1, N2             : Name_Id);
485       procedure Check_Arg_Is_One_Of
486         (Arg                : Node_Id;
487          N1, N2, N3         : Name_Id);
488       procedure Check_Arg_Is_One_Of
489         (Arg                : Node_Id;
490          N1, N2, N3, N4     : Name_Id);
491       procedure Check_Arg_Is_One_Of
492         (Arg                : Node_Id;
493          N1, N2, N3, N4, N5 : Name_Id);
494       --  Check the specified argument Arg to make sure that it is an
495       --  identifier whose name matches either N1 or N2 (or N3, N4, N5 if
496       --  present). If not then give error and raise Pragma_Exit.
497
498       procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id);
499       --  Check the specified argument Arg to make sure that it is a valid
500       --  queuing policy name. If not give error and raise Pragma_Exit.
501
502       procedure Check_Arg_Is_Static_Expression
503         (Arg : Node_Id;
504          Typ : Entity_Id := Empty);
505       --  Check the specified argument Arg to make sure that it is a static
506       --  expression of the given type (i.e. it will be analyzed and resolved
507       --  using this type, which can be any valid argument to Resolve, e.g.
508       --  Any_Integer is OK). If not, given error and raise Pragma_Exit. If
509       --  Typ is left Empty, then any static expression is allowed.
510
511       procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id);
512       --  Check the specified argument Arg to make sure that it is a valid task
513       --  dispatching policy name. If not give error and raise Pragma_Exit.
514
515       procedure Check_Arg_Order (Names : Name_List);
516       --  Checks for an instance of two arguments with identifiers for the
517       --  current pragma which are not in the sequence indicated by Names,
518       --  and if so, generates a fatal message about bad order of arguments.
519
520       procedure Check_At_Least_N_Arguments (N : Nat);
521       --  Check there are at least N arguments present
522
523       procedure Check_At_Most_N_Arguments (N : Nat);
524       --  Check there are no more than N arguments present
525
526       procedure Check_Component
527         (Comp            : Node_Id;
528          UU_Typ          : Entity_Id;
529          In_Variant_Part : Boolean := False);
530       --  Examine an Unchecked_Union component for correct use of per-object
531       --  constrained subtypes, and for restrictions on finalizable components.
532       --  UU_Typ is the related Unchecked_Union type. Flag In_Variant_Part
533       --  should be set when Comp comes from a record variant.
534
535       procedure Check_Duplicate_Pragma (E : Entity_Id);
536       --  Check if a pragma of the same name as the current pragma is already
537       --  chained as a rep pragma to the given entity. If so give a message
538       --  about the duplicate, and then raise Pragma_Exit so does not return.
539       --  Also checks for delayed aspect specification node in the chain.
540
541       procedure Check_Duplicated_Export_Name (Nam : Node_Id);
542       --  Nam is an N_String_Literal node containing the external name set by
543       --  an Import or Export pragma (or extended Import or Export pragma).
544       --  This procedure checks for possible duplications if this is the export
545       --  case, and if found, issues an appropriate error message.
546
547       procedure Check_Expr_Is_Static_Expression
548         (Expr : Node_Id;
549          Typ  : Entity_Id := Empty);
550       --  Check the specified expression Expr to make sure that it is a static
551       --  expression of the given type (i.e. it will be analyzed and resolved
552       --  using this type, which can be any valid argument to Resolve, e.g.
553       --  Any_Integer is OK). If not, given error and raise Pragma_Exit. If
554       --  Typ is left Empty, then any static expression is allowed.
555
556       procedure Check_First_Subtype (Arg : Node_Id);
557       --  Checks that Arg, whose expression is an entity name, references a
558       --  first subtype.
559
560       procedure Check_Identifier (Arg : Node_Id; Id : Name_Id);
561       --  Checks that the given argument has an identifier, and if so, requires
562       --  it to match the given identifier name. If there is no identifier, or
563       --  a non-matching identifier, then an error message is given and
564       --  Pragma_Exit is raised.
565
566       procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id);
567       --  Checks that the given argument has an identifier, and if so, requires
568       --  it to match one of the given identifier names. If there is no
569       --  identifier, or a non-matching identifier, then an error message is
570       --  given and Pragma_Exit is raised.
571
572       procedure Check_In_Main_Program;
573       --  Common checks for pragmas that appear within a main program
574       --  (Priority, Main_Storage, Time_Slice, Relative_Deadline, CPU).
575
576       procedure Check_Interrupt_Or_Attach_Handler;
577       --  Common processing for first argument of pragma Interrupt_Handler or
578       --  pragma Attach_Handler.
579
580       procedure Check_Is_In_Decl_Part_Or_Package_Spec;
581       --  Check that pragma appears in a declarative part, or in a package
582       --  specification, i.e. that it does not occur in a statement sequence
583       --  in a body.
584
585       procedure Check_No_Identifier (Arg : Node_Id);
586       --  Checks that the given argument does not have an identifier. If
587       --  an identifier is present, then an error message is issued, and
588       --  Pragma_Exit is raised.
589
590       procedure Check_No_Identifiers;
591       --  Checks that none of the arguments to the pragma has an identifier.
592       --  If any argument has an identifier, then an error message is issued,
593       --  and Pragma_Exit is raised.
594
595       procedure Check_No_Link_Name;
596       --  Checks that no link name is specified
597
598       procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id);
599       --  Checks if the given argument has an identifier, and if so, requires
600       --  it to match the given identifier name. If there is a non-matching
601       --  identifier, then an error message is given and Pragma_Exit is raised.
602
603       procedure Check_Optional_Identifier (Arg : Node_Id; Id : String);
604       --  Checks if the given argument has an identifier, and if so, requires
605       --  it to match the given identifier name. If there is a non-matching
606       --  identifier, then an error message is given and Pragma_Exit is raised.
607       --  In this version of the procedure, the identifier name is given as
608       --  a string with lower case letters.
609
610       procedure Check_Precondition_Postcondition (In_Body : out Boolean);
611       --  Called to process a precondition or postcondition pragma. There are
612       --  three cases:
613       --
614       --    The pragma appears after a subprogram spec
615       --
616       --      If the corresponding check is not enabled, the pragma is analyzed
617       --      but otherwise ignored and control returns with In_Body set False.
618       --
619       --      If the check is enabled, then the first step is to analyze the
620       --      pragma, but this is skipped if the subprogram spec appears within
621       --      a package specification (because this is the case where we delay
622       --      analysis till the end of the spec). Then (whether or not it was
623       --      analyzed), the pragma is chained to the subprogram in question
624       --      (using Spec_PPC_List and Next_Pragma) and control returns to the
625       --      caller with In_Body set False.
626       --
627       --    The pragma appears at the start of subprogram body declarations
628       --
629       --      In this case an immediate return to the caller is made with
630       --      In_Body set True, and the pragma is NOT analyzed.
631       --
632       --    In all other cases, an error message for bad placement is given
633
634       procedure Check_Static_Constraint (Constr : Node_Id);
635       --  Constr is a constraint from an N_Subtype_Indication node from a
636       --  component constraint in an Unchecked_Union type. This routine checks
637       --  that the constraint is static as required by the restrictions for
638       --  Unchecked_Union.
639
640       procedure Check_Test_Case;
641       --  Called to process a test-case pragma. The treatment is similar to the
642       --  one for pre- and postcondition in Check_Precondition_Postcondition,
643       --  except the placement rules for the test-case pragma are stricter.
644       --  This pragma may only occur after a subprogram spec declared directly
645       --  in a package spec unit. In this case, the pragma is chained to the
646       --  subprogram in question (using Spec_TC_List and Next_Pragma) and
647       --  analysis of the pragma is delayed till the end of the spec. In
648       --  all other cases, an error message for bad placement is given.
649
650       procedure Check_Valid_Configuration_Pragma;
651       --  Legality checks for placement of a configuration pragma
652
653       procedure Check_Valid_Library_Unit_Pragma;
654       --  Legality checks for library unit pragmas. A special case arises for
655       --  pragmas in generic instances that come from copies of the original
656       --  library unit pragmas in the generic templates. In the case of other
657       --  than library level instantiations these can appear in contexts which
658       --  would normally be invalid (they only apply to the original template
659       --  and to library level instantiations), and they are simply ignored,
660       --  which is implemented by rewriting them as null statements.
661
662       procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id);
663       --  Check an Unchecked_Union variant for lack of nested variants and
664       --  presence of at least one component. UU_Typ is the related Unchecked_
665       --  Union type.
666
667       procedure Error_Pragma (Msg : String);
668       pragma No_Return (Error_Pragma);
669       --  Outputs error message for current pragma. The message contains a %
670       --  that will be replaced with the pragma name, and the flag is placed
671       --  on the pragma itself. Pragma_Exit is then raised.
672
673       procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id);
674       pragma No_Return (Error_Pragma_Arg);
675       --  Outputs error message for current pragma. The message may contain
676       --  a % that will be replaced with the pragma name. The parameter Arg
677       --  may either be a pragma argument association, in which case the flag
678       --  is placed on the expression of this association, or an expression,
679       --  in which case the flag is placed directly on the expression. The
680       --  message is placed using Error_Msg_N, so the message may also contain
681       --  an & insertion character which will reference the given Arg value.
682       --  After placing the message, Pragma_Exit is raised.
683
684       procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id);
685       pragma No_Return (Error_Pragma_Arg);
686       --  Similar to above form of Error_Pragma_Arg except that two messages
687       --  are provided, the second is a continuation comment starting with \.
688
689       procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id);
690       pragma No_Return (Error_Pragma_Arg_Ident);
691       --  Outputs error message for current pragma. The message may contain
692       --  a % that will be replaced with the pragma name. The parameter Arg
693       --  must be a pragma argument association with a non-empty identifier
694       --  (i.e. its Chars field must be set), and the error message is placed
695       --  on the identifier. The message is placed using Error_Msg_N so
696       --  the message may also contain an & insertion character which will
697       --  reference the identifier. After placing the message, Pragma_Exit
698       --  is raised.
699
700       procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id);
701       pragma No_Return (Error_Pragma_Ref);
702       --  Outputs error message for current pragma. The message may contain
703       --  a % that will be replaced with the pragma name. The parameter Ref
704       --  must be an entity whose name can be referenced by & and sloc by #.
705       --  After placing the message, Pragma_Exit is raised.
706
707       function Find_Lib_Unit_Name return Entity_Id;
708       --  Used for a library unit pragma to find the entity to which the
709       --  library unit pragma applies, returns the entity found.
710
711       procedure Find_Program_Unit_Name (Id : Node_Id);
712       --  If the pragma is a compilation unit pragma, the id must denote the
713       --  compilation unit in the same compilation, and the pragma must appear
714       --  in the list of preceding or trailing pragmas. If it is a program
715       --  unit pragma that is not a compilation unit pragma, then the
716       --  identifier must be visible.
717
718       function Find_Unique_Parameterless_Procedure
719         (Name : Entity_Id;
720          Arg  : Node_Id) return Entity_Id;
721       --  Used for a procedure pragma to find the unique parameterless
722       --  procedure identified by Name, returns it if it exists, otherwise
723       --  errors out and uses Arg as the pragma argument for the message.
724
725       procedure Fix_Error (Msg : in out String);
726       --  This is called prior to issuing an error message. Msg is a string
727       --  that typically contains the substring "pragma". If the current pragma
728       --  comes from an aspect, each such "pragma" substring is replaced with
729       --  the characters "aspect", and if Error_Msg_Name_1 is Name_Precondition
730       --  (resp Name_Postcondition) it is changed to Name_Pre (resp Name_Post).
731
732       procedure Gather_Associations
733         (Names : Name_List;
734          Args  : out Args_List);
735       --  This procedure is used to gather the arguments for a pragma that
736       --  permits arbitrary ordering of parameters using the normal rules
737       --  for named and positional parameters. The Names argument is a list
738       --  of Name_Id values that corresponds to the allowed pragma argument
739       --  association identifiers in order. The result returned in Args is
740       --  a list of corresponding expressions that are the pragma arguments.
741       --  Note that this is a list of expressions, not of pragma argument
742       --  associations (Gather_Associations has completely checked all the
743       --  optional identifiers when it returns). An entry in Args is Empty
744       --  on return if the corresponding argument is not present.
745
746       procedure GNAT_Pragma;
747       --  Called for all GNAT defined pragmas to check the relevant restriction
748       --  (No_Implementation_Pragmas).
749
750       function Is_Before_First_Decl
751         (Pragma_Node : Node_Id;
752          Decls       : List_Id) return Boolean;
753       --  Return True if Pragma_Node is before the first declarative item in
754       --  Decls where Decls is the list of declarative items.
755
756       function Is_Configuration_Pragma return Boolean;
757       --  Determines if the placement of the current pragma is appropriate
758       --  for a configuration pragma.
759
760       function Is_In_Context_Clause return Boolean;
761       --  Returns True if pragma appears within the context clause of a unit,
762       --  and False for any other placement (does not generate any messages).
763
764       function Is_Static_String_Expression (Arg : Node_Id) return Boolean;
765       --  Analyzes the argument, and determines if it is a static string
766       --  expression, returns True if so, False if non-static or not String.
767
768       procedure Pragma_Misplaced;
769       pragma No_Return (Pragma_Misplaced);
770       --  Issue fatal error message for misplaced pragma
771
772       procedure Process_Atomic_Shared_Volatile;
773       --  Common processing for pragmas Atomic, Shared, Volatile. Note that
774       --  Shared is an obsolete Ada 83 pragma, treated as being identical
775       --  in effect to pragma Atomic.
776
777       procedure Process_Compile_Time_Warning_Or_Error;
778       --  Common processing for Compile_Time_Error and Compile_Time_Warning
779
780       procedure Process_Convention
781         (C   : out Convention_Id;
782          Ent : out Entity_Id);
783       --  Common processing for Convention, Interface, Import and Export.
784       --  Checks first two arguments of pragma, and sets the appropriate
785       --  convention value in the specified entity or entities. On return
786       --  C is the convention, Ent is the referenced entity.
787
788       procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id);
789       --  Common processing for Disable/Enable_Atomic_Synchronization. Nam is
790       --  Name_Suppress for Disable and Name_Unsuppress for Enable.
791
792       procedure Process_Extended_Import_Export_Exception_Pragma
793         (Arg_Internal : Node_Id;
794          Arg_External : Node_Id;
795          Arg_Form     : Node_Id;
796          Arg_Code     : Node_Id);
797       --  Common processing for the pragmas Import/Export_Exception. The three
798       --  arguments correspond to the three named parameters of the pragma. An
799       --  argument is empty if the corresponding parameter is not present in
800       --  the pragma.
801
802       procedure Process_Extended_Import_Export_Object_Pragma
803         (Arg_Internal : Node_Id;
804          Arg_External : Node_Id;
805          Arg_Size     : Node_Id);
806       --  Common processing for the pragmas Import/Export_Object. The three
807       --  arguments correspond to the three named parameters of the pragmas. An
808       --  argument is empty if the corresponding parameter is not present in
809       --  the pragma.
810
811       procedure Process_Extended_Import_Export_Internal_Arg
812         (Arg_Internal : Node_Id := Empty);
813       --  Common processing for all extended Import and Export pragmas. The
814       --  argument is the pragma parameter for the Internal argument. If
815       --  Arg_Internal is empty or inappropriate, an error message is posted.
816       --  Otherwise, on normal return, the Entity_Field of Arg_Internal is
817       --  set to identify the referenced entity.
818
819       procedure Process_Extended_Import_Export_Subprogram_Pragma
820         (Arg_Internal                 : Node_Id;
821          Arg_External                 : Node_Id;
822          Arg_Parameter_Types          : Node_Id;
823          Arg_Result_Type              : Node_Id := Empty;
824          Arg_Mechanism                : Node_Id;
825          Arg_Result_Mechanism         : Node_Id := Empty;
826          Arg_First_Optional_Parameter : Node_Id := Empty);
827       --  Common processing for all extended Import and Export pragmas applying
828       --  to subprograms. The caller omits any arguments that do not apply to
829       --  the pragma in question (for example, Arg_Result_Type can be non-Empty
830       --  only in the Import_Function and Export_Function cases). The argument
831       --  names correspond to the allowed pragma association identifiers.
832
833       procedure Process_Generic_List;
834       --  Common processing for Share_Generic and Inline_Generic
835
836       procedure Process_Import_Or_Interface;
837       --  Common processing for Import of Interface
838
839       procedure Process_Import_Predefined_Type;
840       --  Processing for completing a type with pragma Import. This is used
841       --  to declare types that match predefined C types, especially for cases
842       --  without corresponding Ada predefined type.
843
844       procedure Process_Inline (Active : Boolean);
845       --  Common processing for Inline and Inline_Always. The parameter
846       --  indicates if the inline pragma is active, i.e. if it should actually
847       --  cause inlining to occur.
848
849       procedure Process_Interface_Name
850         (Subprogram_Def : Entity_Id;
851          Ext_Arg        : Node_Id;
852          Link_Arg       : Node_Id);
853       --  Given the last two arguments of pragma Import, pragma Export, or
854       --  pragma Interface_Name, performs validity checks and sets the
855       --  Interface_Name field of the given subprogram entity to the
856       --  appropriate external or link name, depending on the arguments given.
857       --  Ext_Arg is always present, but Link_Arg may be missing. Note that
858       --  Ext_Arg may represent the Link_Name if Link_Arg is missing, and
859       --  appropriate named notation is used for Ext_Arg. If neither Ext_Arg
860       --  nor Link_Arg is present, the interface name is set to the default
861       --  from the subprogram name.
862
863       procedure Process_Interrupt_Or_Attach_Handler;
864       --  Common processing for Interrupt and Attach_Handler pragmas
865
866       procedure Process_Restrictions_Or_Restriction_Warnings (Warn : Boolean);
867       --  Common processing for Restrictions and Restriction_Warnings pragmas.
868       --  Warn is True for Restriction_Warnings, or for Restrictions if the
869       --  flag Treat_Restrictions_As_Warnings is set, and False if this flag
870       --  is not set in the Restrictions case.
871
872       procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean);
873       --  Common processing for Suppress and Unsuppress. The boolean parameter
874       --  Suppress_Case is True for the Suppress case, and False for the
875       --  Unsuppress case.
876
877       procedure Set_Exported (E : Entity_Id; Arg : Node_Id);
878       --  This procedure sets the Is_Exported flag for the given entity,
879       --  checking that the entity was not previously imported. Arg is
880       --  the argument that specified the entity. A check is also made
881       --  for exporting inappropriate entities.
882
883       procedure Set_Extended_Import_Export_External_Name
884         (Internal_Ent : Entity_Id;
885          Arg_External : Node_Id);
886       --  Common processing for all extended import export pragmas. The first
887       --  argument, Internal_Ent, is the internal entity, which has already
888       --  been checked for validity by the caller. Arg_External is from the
889       --  Import or Export pragma, and may be null if no External parameter
890       --  was present. If Arg_External is present and is a non-null string
891       --  (a null string is treated as the default), then the Interface_Name
892       --  field of Internal_Ent is set appropriately.
893
894       procedure Set_Imported (E : Entity_Id);
895       --  This procedure sets the Is_Imported flag for the given entity,
896       --  checking that it is not previously exported or imported.
897
898       procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id);
899       --  Mech is a parameter passing mechanism (see Import_Function syntax
900       --  for MECHANISM_NAME). This routine checks that the mechanism argument
901       --  has the right form, and if not issues an error message. If the
902       --  argument has the right form then the Mechanism field of Ent is
903       --  set appropriately.
904
905       procedure Set_Ravenscar_Profile (N : Node_Id);
906       --  Activate the set of configuration pragmas and restrictions that make
907       --  up the Ravenscar Profile. N is the corresponding pragma node, which
908       --  is used for error messages on any constructs that violate the
909       --  profile.
910
911       ---------------------
912       -- Ada_2005_Pragma --
913       ---------------------
914
915       procedure Ada_2005_Pragma is
916       begin
917          if Ada_Version <= Ada_95 then
918             Check_Restriction (No_Implementation_Pragmas, N);
919          end if;
920       end Ada_2005_Pragma;
921
922       ---------------------
923       -- Ada_2012_Pragma --
924       ---------------------
925
926       procedure Ada_2012_Pragma is
927       begin
928          if Ada_Version <= Ada_2005 then
929             Check_Restriction (No_Implementation_Pragmas, N);
930          end if;
931       end Ada_2012_Pragma;
932
933       --------------------------
934       -- Check_Ada_83_Warning --
935       --------------------------
936
937       procedure Check_Ada_83_Warning is
938       begin
939          if Ada_Version = Ada_83 and then Comes_From_Source (N) then
940             Error_Msg_N ("(Ada 83) pragma& is non-standard?", N);
941          end if;
942       end Check_Ada_83_Warning;
943
944       ---------------------
945       -- Check_Arg_Count --
946       ---------------------
947
948       procedure Check_Arg_Count (Required : Nat) is
949       begin
950          if Arg_Count /= Required then
951             Error_Pragma ("wrong number of arguments for pragma%");
952          end if;
953       end Check_Arg_Count;
954
955       --------------------------------
956       -- Check_Arg_Is_External_Name --
957       --------------------------------
958
959       procedure Check_Arg_Is_External_Name (Arg : Node_Id) is
960          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
961
962       begin
963          if Nkind (Argx) = N_Identifier then
964             return;
965
966          else
967             Analyze_And_Resolve (Argx, Standard_String);
968
969             if Is_OK_Static_Expression (Argx) then
970                return;
971
972             elsif Etype (Argx) = Any_Type then
973                raise Pragma_Exit;
974
975             --  An interesting special case, if we have a string literal and
976             --  we are in Ada 83 mode, then we allow it even though it will
977             --  not be flagged as static. This allows expected Ada 83 mode
978             --  use of external names which are string literals, even though
979             --  technically these are not static in Ada 83.
980
981             elsif Ada_Version = Ada_83
982               and then Nkind (Argx) = N_String_Literal
983             then
984                return;
985
986             --  Static expression that raises Constraint_Error. This has
987             --  already been flagged, so just exit from pragma processing.
988
989             elsif Is_Static_Expression (Argx) then
990                raise Pragma_Exit;
991
992             --  Here we have a real error (non-static expression)
993
994             else
995                Error_Msg_Name_1 := Pname;
996
997                declare
998                   Msg : String :=
999                           "argument for pragma% must be a identifier or "
1000                           & "static string expression!";
1001                begin
1002                   Fix_Error (Msg);
1003                   Flag_Non_Static_Expr (Msg, Argx);
1004                   raise Pragma_Exit;
1005                end;
1006             end if;
1007          end if;
1008       end Check_Arg_Is_External_Name;
1009
1010       -----------------------------
1011       -- Check_Arg_Is_Identifier --
1012       -----------------------------
1013
1014       procedure Check_Arg_Is_Identifier (Arg : Node_Id) is
1015          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1016       begin
1017          if Nkind (Argx) /= N_Identifier then
1018             Error_Pragma_Arg
1019               ("argument for pragma% must be identifier", Argx);
1020          end if;
1021       end Check_Arg_Is_Identifier;
1022
1023       ----------------------------------
1024       -- Check_Arg_Is_Integer_Literal --
1025       ----------------------------------
1026
1027       procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id) is
1028          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1029       begin
1030          if Nkind (Argx) /= N_Integer_Literal then
1031             Error_Pragma_Arg
1032               ("argument for pragma% must be integer literal", Argx);
1033          end if;
1034       end Check_Arg_Is_Integer_Literal;
1035
1036       -------------------------------------------
1037       -- Check_Arg_Is_Library_Level_Local_Name --
1038       -------------------------------------------
1039
1040       --  LOCAL_NAME ::=
1041       --    DIRECT_NAME
1042       --  | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
1043       --  | library_unit_NAME
1044
1045       procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id) is
1046       begin
1047          Check_Arg_Is_Local_Name (Arg);
1048
1049          if not Is_Library_Level_Entity (Entity (Get_Pragma_Arg (Arg)))
1050            and then Comes_From_Source (N)
1051          then
1052             Error_Pragma_Arg
1053               ("argument for pragma% must be library level entity", Arg);
1054          end if;
1055       end Check_Arg_Is_Library_Level_Local_Name;
1056
1057       -----------------------------
1058       -- Check_Arg_Is_Local_Name --
1059       -----------------------------
1060
1061       --  LOCAL_NAME ::=
1062       --    DIRECT_NAME
1063       --  | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
1064       --  | library_unit_NAME
1065
1066       procedure Check_Arg_Is_Local_Name (Arg : Node_Id) is
1067          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1068
1069       begin
1070          Analyze (Argx);
1071
1072          if Nkind (Argx) not in N_Direct_Name
1073            and then (Nkind (Argx) /= N_Attribute_Reference
1074                       or else Present (Expressions (Argx))
1075                       or else Nkind (Prefix (Argx)) /= N_Identifier)
1076            and then (not Is_Entity_Name (Argx)
1077                       or else not Is_Compilation_Unit (Entity (Argx)))
1078          then
1079             Error_Pragma_Arg ("argument for pragma% must be local name", Argx);
1080          end if;
1081
1082          --  No further check required if not an entity name
1083
1084          if not Is_Entity_Name (Argx) then
1085             null;
1086
1087          else
1088             declare
1089                OK   : Boolean;
1090                Ent  : constant Entity_Id := Entity (Argx);
1091                Scop : constant Entity_Id := Scope (Ent);
1092             begin
1093                --  Case of a pragma applied to a compilation unit: pragma must
1094                --  occur immediately after the program unit in the compilation.
1095
1096                if Is_Compilation_Unit (Ent) then
1097                   declare
1098                      Decl : constant Node_Id := Unit_Declaration_Node (Ent);
1099
1100                   begin
1101                      --  Case of pragma placed immediately after spec
1102
1103                      if Parent (N) = Aux_Decls_Node (Parent (Decl)) then
1104                         OK := True;
1105
1106                      --  Case of pragma placed immediately after body
1107
1108                      elsif Nkind (Decl) = N_Subprogram_Declaration
1109                              and then Present (Corresponding_Body (Decl))
1110                      then
1111                         OK := Parent (N) =
1112                                 Aux_Decls_Node
1113                                   (Parent (Unit_Declaration_Node
1114                                              (Corresponding_Body (Decl))));
1115
1116                      --  All other cases are illegal
1117
1118                      else
1119                         OK := False;
1120                      end if;
1121                   end;
1122
1123                --  Special restricted placement rule from 10.2.1(11.8/2)
1124
1125                elsif Is_Generic_Formal (Ent)
1126                        and then Prag_Id = Pragma_Preelaborable_Initialization
1127                then
1128                   OK := List_Containing (N) =
1129                           Generic_Formal_Declarations
1130                             (Unit_Declaration_Node (Scop));
1131
1132                --  Default case, just check that the pragma occurs in the scope
1133                --  of the entity denoted by the name.
1134
1135                else
1136                   OK := Current_Scope = Scop;
1137                end if;
1138
1139                if not OK then
1140                   Error_Pragma_Arg
1141                     ("pragma% argument must be in same declarative part", Arg);
1142                end if;
1143             end;
1144          end if;
1145       end Check_Arg_Is_Local_Name;
1146
1147       ---------------------------------
1148       -- Check_Arg_Is_Locking_Policy --
1149       ---------------------------------
1150
1151       procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id) is
1152          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1153
1154       begin
1155          Check_Arg_Is_Identifier (Argx);
1156
1157          if not Is_Locking_Policy_Name (Chars (Argx)) then
1158             Error_Pragma_Arg ("& is not a valid locking policy name", Argx);
1159          end if;
1160       end Check_Arg_Is_Locking_Policy;
1161
1162       -------------------------
1163       -- Check_Arg_Is_One_Of --
1164       -------------------------
1165
1166       procedure Check_Arg_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
1167          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1168
1169       begin
1170          Check_Arg_Is_Identifier (Argx);
1171
1172          if Chars (Argx) /= N1 and then Chars (Argx) /= N2 then
1173             Error_Msg_Name_2 := N1;
1174             Error_Msg_Name_3 := N2;
1175             Error_Pragma_Arg ("argument for pragma% must be% or%", 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 : 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          then
1192             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1193          end if;
1194       end Check_Arg_Is_One_Of;
1195
1196       procedure Check_Arg_Is_One_Of
1197         (Arg                : Node_Id;
1198          N1, N2, N3, N4     : Name_Id)
1199       is
1200          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1201
1202       begin
1203          Check_Arg_Is_Identifier (Argx);
1204
1205          if Chars (Argx) /= N1
1206            and then Chars (Argx) /= N2
1207            and then Chars (Argx) /= N3
1208            and then Chars (Argx) /= N4
1209          then
1210             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1211          end if;
1212       end Check_Arg_Is_One_Of;
1213
1214       procedure Check_Arg_Is_One_Of
1215         (Arg                : Node_Id;
1216          N1, N2, N3, N4, N5 : Name_Id)
1217       is
1218          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1219
1220       begin
1221          Check_Arg_Is_Identifier (Argx);
1222
1223          if Chars (Argx) /= N1
1224            and then Chars (Argx) /= N2
1225            and then Chars (Argx) /= N3
1226            and then Chars (Argx) /= N4
1227            and then Chars (Argx) /= N5
1228          then
1229             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1230          end if;
1231       end Check_Arg_Is_One_Of;
1232       ---------------------------------
1233       -- Check_Arg_Is_Queuing_Policy --
1234       ---------------------------------
1235
1236       procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id) is
1237          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1238
1239       begin
1240          Check_Arg_Is_Identifier (Argx);
1241
1242          if not Is_Queuing_Policy_Name (Chars (Argx)) then
1243             Error_Pragma_Arg ("& is not a valid queuing policy name", Argx);
1244          end if;
1245       end Check_Arg_Is_Queuing_Policy;
1246
1247       ------------------------------------
1248       -- Check_Arg_Is_Static_Expression --
1249       ------------------------------------
1250
1251       procedure Check_Arg_Is_Static_Expression
1252         (Arg : Node_Id;
1253          Typ : Entity_Id := Empty)
1254       is
1255       begin
1256          Check_Expr_Is_Static_Expression (Get_Pragma_Arg (Arg), Typ);
1257       end Check_Arg_Is_Static_Expression;
1258
1259       ------------------------------------------
1260       -- Check_Arg_Is_Task_Dispatching_Policy --
1261       ------------------------------------------
1262
1263       procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id) is
1264          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1265
1266       begin
1267          Check_Arg_Is_Identifier (Argx);
1268
1269          if not Is_Task_Dispatching_Policy_Name (Chars (Argx)) then
1270             Error_Pragma_Arg
1271               ("& is not a valid task dispatching policy name", Argx);
1272          end if;
1273       end Check_Arg_Is_Task_Dispatching_Policy;
1274
1275       ---------------------
1276       -- Check_Arg_Order --
1277       ---------------------
1278
1279       procedure Check_Arg_Order (Names : Name_List) is
1280          Arg : Node_Id;
1281
1282          Highest_So_Far : Natural := 0;
1283          --  Highest index in Names seen do far
1284
1285       begin
1286          Arg := Arg1;
1287          for J in 1 .. Arg_Count loop
1288             if Chars (Arg) /= No_Name then
1289                for K in Names'Range loop
1290                   if Chars (Arg) = Names (K) then
1291                      if K < Highest_So_Far then
1292                         Error_Msg_Name_1 := Pname;
1293                         Error_Msg_N
1294                           ("parameters out of order for pragma%", Arg);
1295                         Error_Msg_Name_1 := Names (K);
1296                         Error_Msg_Name_2 := Names (Highest_So_Far);
1297                         Error_Msg_N ("\% must appear before %", Arg);
1298                         raise Pragma_Exit;
1299
1300                      else
1301                         Highest_So_Far := K;
1302                      end if;
1303                   end if;
1304                end loop;
1305             end if;
1306
1307             Arg := Next (Arg);
1308          end loop;
1309       end Check_Arg_Order;
1310
1311       --------------------------------
1312       -- Check_At_Least_N_Arguments --
1313       --------------------------------
1314
1315       procedure Check_At_Least_N_Arguments (N : Nat) is
1316       begin
1317          if Arg_Count < N then
1318             Error_Pragma ("too few arguments for pragma%");
1319          end if;
1320       end Check_At_Least_N_Arguments;
1321
1322       -------------------------------
1323       -- Check_At_Most_N_Arguments --
1324       -------------------------------
1325
1326       procedure Check_At_Most_N_Arguments (N : Nat) is
1327          Arg : Node_Id;
1328       begin
1329          if Arg_Count > N then
1330             Arg := Arg1;
1331             for J in 1 .. N loop
1332                Next (Arg);
1333                Error_Pragma_Arg ("too many arguments for pragma%", Arg);
1334             end loop;
1335          end if;
1336       end Check_At_Most_N_Arguments;
1337
1338       ---------------------
1339       -- Check_Component --
1340       ---------------------
1341
1342       procedure Check_Component
1343         (Comp            : Node_Id;
1344          UU_Typ          : Entity_Id;
1345          In_Variant_Part : Boolean := False)
1346       is
1347          Comp_Id : constant Entity_Id := Defining_Identifier (Comp);
1348          Sindic  : constant Node_Id :=
1349                      Subtype_Indication (Component_Definition (Comp));
1350          Typ     : constant Entity_Id := Etype (Comp_Id);
1351
1352       begin
1353          --  Ada 2005 (AI-216): If a component subtype is subject to a per-
1354          --  object constraint, then the component type shall be an Unchecked_
1355          --  Union.
1356
1357          if Nkind (Sindic) = N_Subtype_Indication
1358            and then Has_Per_Object_Constraint (Comp_Id)
1359            and then not Is_Unchecked_Union (Etype (Subtype_Mark (Sindic)))
1360          then
1361             Error_Msg_N
1362               ("component subtype subject to per-object constraint " &
1363                "must be an Unchecked_Union", Comp);
1364
1365          --  Ada 2012 (AI05-0026): For an unchecked union type declared within
1366          --  the body of a generic unit, or within the body of any of its
1367          --  descendant library units, no part of the type of a component
1368          --  declared in a variant_part of the unchecked union type shall be of
1369          --  a formal private type or formal private extension declared within
1370          --  the formal part of the generic unit.
1371
1372          elsif Ada_Version >= Ada_2012
1373            and then In_Generic_Body (UU_Typ)
1374            and then In_Variant_Part
1375            and then Is_Private_Type (Typ)
1376            and then Is_Generic_Type (Typ)
1377          then
1378             Error_Msg_N
1379               ("component of Unchecked_Union cannot be of generic type", Comp);
1380
1381          elsif Needs_Finalization (Typ) then
1382             Error_Msg_N
1383               ("component of Unchecked_Union cannot be controlled", Comp);
1384
1385          elsif Has_Task (Typ) then
1386             Error_Msg_N
1387               ("component of Unchecked_Union cannot have tasks", Comp);
1388          end if;
1389       end Check_Component;
1390
1391       ----------------------------
1392       -- Check_Duplicate_Pragma --
1393       ----------------------------
1394
1395       procedure Check_Duplicate_Pragma (E : Entity_Id) is
1396          P : Node_Id;
1397
1398       begin
1399          --  Nothing to do if this pragma comes from an aspect specification,
1400          --  since we could not be duplicating a pragma, and we dealt with the
1401          --  case of duplicated aspects in Analyze_Aspect_Specifications.
1402
1403          if From_Aspect_Specification (N) then
1404             return;
1405          end if;
1406
1407          --  Otherwise current pragma may duplicate previous pragma or a
1408          --  previously given aspect specification for the same pragma.
1409
1410          P := Get_Rep_Item_For_Entity (E, Pragma_Name (N));
1411
1412          if Present (P) then
1413             Error_Msg_Name_1 := Pragma_Name (N);
1414             Error_Msg_Sloc := Sloc (P);
1415
1416             if Nkind (P) = N_Aspect_Specification
1417               or else From_Aspect_Specification (P)
1418             then
1419                Error_Msg_NE ("aspect% for & previously given#", N, E);
1420             else
1421                Error_Msg_NE ("pragma% for & duplicates pragma#", N, E);
1422             end if;
1423
1424             raise Pragma_Exit;
1425          end if;
1426       end Check_Duplicate_Pragma;
1427
1428       ----------------------------------
1429       -- Check_Duplicated_Export_Name --
1430       ----------------------------------
1431
1432       procedure Check_Duplicated_Export_Name (Nam : Node_Id) is
1433          String_Val : constant String_Id := Strval (Nam);
1434
1435       begin
1436          --  We are only interested in the export case, and in the case of
1437          --  generics, it is the instance, not the template, that is the
1438          --  problem (the template will generate a warning in any case).
1439
1440          if not Inside_A_Generic
1441            and then (Prag_Id = Pragma_Export
1442                        or else
1443                      Prag_Id = Pragma_Export_Procedure
1444                        or else
1445                      Prag_Id = Pragma_Export_Valued_Procedure
1446                        or else
1447                      Prag_Id = Pragma_Export_Function)
1448          then
1449             for J in Externals.First .. Externals.Last loop
1450                if String_Equal (String_Val, Strval (Externals.Table (J))) then
1451                   Error_Msg_Sloc := Sloc (Externals.Table (J));
1452                   Error_Msg_N ("external name duplicates name given#", Nam);
1453                   exit;
1454                end if;
1455             end loop;
1456
1457             Externals.Append (Nam);
1458          end if;
1459       end Check_Duplicated_Export_Name;
1460
1461       -------------------------------------
1462       -- Check_Expr_Is_Static_Expression --
1463       -------------------------------------
1464
1465       procedure Check_Expr_Is_Static_Expression
1466         (Expr : Node_Id;
1467          Typ  : Entity_Id := Empty)
1468       is
1469       begin
1470          if Present (Typ) then
1471             Analyze_And_Resolve (Expr, Typ);
1472          else
1473             Analyze_And_Resolve (Expr);
1474          end if;
1475
1476          if Is_OK_Static_Expression (Expr) then
1477             return;
1478
1479          elsif Etype (Expr) = Any_Type then
1480             raise Pragma_Exit;
1481
1482          --  An interesting special case, if we have a string literal and we
1483          --  are in Ada 83 mode, then we allow it even though it will not be
1484          --  flagged as static. This allows the use of Ada 95 pragmas like
1485          --  Import in Ada 83 mode. They will of course be flagged with
1486          --  warnings as usual, but will not cause errors.
1487
1488          elsif Ada_Version = Ada_83
1489            and then Nkind (Expr) = N_String_Literal
1490          then
1491             return;
1492
1493          --  Static expression that raises Constraint_Error. This has already
1494          --  been flagged, so just exit from pragma processing.
1495
1496          elsif Is_Static_Expression (Expr) then
1497             raise Pragma_Exit;
1498
1499          --  Finally, we have a real error
1500
1501          else
1502             Error_Msg_Name_1 := Pname;
1503
1504             declare
1505                Msg : String :=
1506                        "argument for pragma% must be a static expression!";
1507             begin
1508                Fix_Error (Msg);
1509                Flag_Non_Static_Expr (Msg, Expr);
1510             end;
1511
1512             raise Pragma_Exit;
1513          end if;
1514       end Check_Expr_Is_Static_Expression;
1515
1516       -------------------------
1517       -- Check_First_Subtype --
1518       -------------------------
1519
1520       procedure Check_First_Subtype (Arg : Node_Id) is
1521          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1522          Ent  : constant Entity_Id := Entity (Argx);
1523
1524       begin
1525          if Is_First_Subtype (Ent) then
1526             null;
1527
1528          elsif Is_Type (Ent) then
1529             Error_Pragma_Arg
1530               ("pragma% cannot apply to subtype", Argx);
1531
1532          elsif Is_Object (Ent) then
1533             Error_Pragma_Arg
1534               ("pragma% cannot apply to object, requires a type", Argx);
1535
1536          else
1537             Error_Pragma_Arg
1538               ("pragma% cannot apply to&, requires a type", Argx);
1539          end if;
1540       end Check_First_Subtype;
1541
1542       ----------------------
1543       -- Check_Identifier --
1544       ----------------------
1545
1546       procedure Check_Identifier (Arg : Node_Id; Id : Name_Id) is
1547       begin
1548          if Present (Arg)
1549            and then Nkind (Arg) = N_Pragma_Argument_Association
1550          then
1551             if Chars (Arg) = No_Name or else Chars (Arg) /= Id then
1552                Error_Msg_Name_1 := Pname;
1553                Error_Msg_Name_2 := Id;
1554                Error_Msg_N ("pragma% argument expects identifier%", Arg);
1555                raise Pragma_Exit;
1556             end if;
1557          end if;
1558       end Check_Identifier;
1559
1560       --------------------------------
1561       -- Check_Identifier_Is_One_Of --
1562       --------------------------------
1563
1564       procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
1565       begin
1566          if Present (Arg)
1567            and then Nkind (Arg) = N_Pragma_Argument_Association
1568          then
1569             if Chars (Arg) = No_Name then
1570                Error_Msg_Name_1 := Pname;
1571                Error_Msg_N ("pragma% argument expects an identifier", Arg);
1572                raise Pragma_Exit;
1573
1574             elsif Chars (Arg) /= N1
1575               and then Chars (Arg) /= N2
1576             then
1577                Error_Msg_Name_1 := Pname;
1578                Error_Msg_N ("invalid identifier for pragma% argument", Arg);
1579                raise Pragma_Exit;
1580             end if;
1581          end if;
1582       end Check_Identifier_Is_One_Of;
1583
1584       ---------------------------
1585       -- Check_In_Main_Program --
1586       ---------------------------
1587
1588       procedure Check_In_Main_Program is
1589          P : constant Node_Id := Parent (N);
1590
1591       begin
1592          --  Must be at in subprogram body
1593
1594          if Nkind (P) /= N_Subprogram_Body then
1595             Error_Pragma ("% pragma allowed only in subprogram");
1596
1597          --  Otherwise warn if obviously not main program
1598
1599          elsif Present (Parameter_Specifications (Specification (P)))
1600            or else not Is_Compilation_Unit (Defining_Entity (P))
1601          then
1602             Error_Msg_Name_1 := Pname;
1603             Error_Msg_N
1604               ("?pragma% is only effective in main program", N);
1605          end if;
1606       end Check_In_Main_Program;
1607
1608       ---------------------------------------
1609       -- Check_Interrupt_Or_Attach_Handler --
1610       ---------------------------------------
1611
1612       procedure Check_Interrupt_Or_Attach_Handler is
1613          Arg1_X : constant Node_Id := Get_Pragma_Arg (Arg1);
1614          Handler_Proc, Proc_Scope : Entity_Id;
1615
1616       begin
1617          Analyze (Arg1_X);
1618
1619          if Prag_Id = Pragma_Interrupt_Handler then
1620             Check_Restriction (No_Dynamic_Attachment, N);
1621          end if;
1622
1623          Handler_Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
1624          Proc_Scope := Scope (Handler_Proc);
1625
1626          --  On AAMP only, a pragma Interrupt_Handler is supported for
1627          --  nonprotected parameterless procedures.
1628
1629          if not AAMP_On_Target
1630            or else Prag_Id = Pragma_Attach_Handler
1631          then
1632             if Ekind (Proc_Scope) /= E_Protected_Type then
1633                Error_Pragma_Arg
1634                  ("argument of pragma% must be protected procedure", Arg1);
1635             end if;
1636
1637             if Parent (N) /= Protected_Definition (Parent (Proc_Scope)) then
1638                Error_Pragma ("pragma% must be in protected definition");
1639             end if;
1640          end if;
1641
1642          if not Is_Library_Level_Entity (Proc_Scope)
1643            or else (AAMP_On_Target
1644                      and then not Is_Library_Level_Entity (Handler_Proc))
1645          then
1646             Error_Pragma_Arg
1647               ("argument for pragma% must be library level entity", Arg1);
1648          end if;
1649
1650          --  AI05-0033: A pragma cannot appear within a generic body, because
1651          --  instance can be in a nested scope. The check that protected type
1652          --  is itself a library-level declaration is done elsewhere.
1653
1654          --  Note: we omit this check in Codepeer mode to properly handle code
1655          --  prior to AI-0033 (pragmas don't matter to codepeer in any case).
1656
1657          if Inside_A_Generic then
1658             if Ekind (Scope (Current_Scope)) = E_Generic_Package
1659               and then In_Package_Body (Scope (Current_Scope))
1660               and then not CodePeer_Mode
1661             then
1662                Error_Pragma ("pragma% cannot be used inside a generic");
1663             end if;
1664          end if;
1665       end Check_Interrupt_Or_Attach_Handler;
1666
1667       -------------------------------------------
1668       -- Check_Is_In_Decl_Part_Or_Package_Spec --
1669       -------------------------------------------
1670
1671       procedure Check_Is_In_Decl_Part_Or_Package_Spec is
1672          P : Node_Id;
1673
1674       begin
1675          P := Parent (N);
1676          loop
1677             if No (P) then
1678                exit;
1679
1680             elsif Nkind (P) = N_Handled_Sequence_Of_Statements then
1681                exit;
1682
1683             elsif Nkind_In (P, N_Package_Specification,
1684                                N_Block_Statement)
1685             then
1686                return;
1687
1688             --  Note: the following tests seem a little peculiar, because
1689             --  they test for bodies, but if we were in the statement part
1690             --  of the body, we would already have hit the handled statement
1691             --  sequence, so the only way we get here is by being in the
1692             --  declarative part of the body.
1693
1694             elsif Nkind_In (P, N_Subprogram_Body,
1695                                N_Package_Body,
1696                                N_Task_Body,
1697                                N_Entry_Body)
1698             then
1699                return;
1700             end if;
1701
1702             P := Parent (P);
1703          end loop;
1704
1705          Error_Pragma ("pragma% is not in declarative part or package spec");
1706       end Check_Is_In_Decl_Part_Or_Package_Spec;
1707
1708       -------------------------
1709       -- Check_No_Identifier --
1710       -------------------------
1711
1712       procedure Check_No_Identifier (Arg : Node_Id) is
1713       begin
1714          if Nkind (Arg) = N_Pragma_Argument_Association
1715            and then Chars (Arg) /= No_Name
1716          then
1717             Error_Pragma_Arg_Ident
1718               ("pragma% does not permit identifier& here", Arg);
1719          end if;
1720       end Check_No_Identifier;
1721
1722       --------------------------
1723       -- Check_No_Identifiers --
1724       --------------------------
1725
1726       procedure Check_No_Identifiers is
1727          Arg_Node : Node_Id;
1728       begin
1729          if Arg_Count > 0 then
1730             Arg_Node := Arg1;
1731             while Present (Arg_Node) loop
1732                Check_No_Identifier (Arg_Node);
1733                Next (Arg_Node);
1734             end loop;
1735          end if;
1736       end Check_No_Identifiers;
1737
1738       ------------------------
1739       -- Check_No_Link_Name --
1740       ------------------------
1741
1742       procedure Check_No_Link_Name is
1743       begin
1744          if Present (Arg3)
1745            and then Chars (Arg3) = Name_Link_Name
1746          then
1747             Arg4 := Arg3;
1748          end if;
1749
1750          if Present (Arg4) then
1751             Error_Pragma_Arg
1752               ("Link_Name argument not allowed for Import Intrinsic", Arg4);
1753          end if;
1754       end Check_No_Link_Name;
1755
1756       -------------------------------
1757       -- Check_Optional_Identifier --
1758       -------------------------------
1759
1760       procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id) is
1761       begin
1762          if Present (Arg)
1763            and then Nkind (Arg) = N_Pragma_Argument_Association
1764            and then Chars (Arg) /= No_Name
1765          then
1766             if Chars (Arg) /= Id then
1767                Error_Msg_Name_1 := Pname;
1768                Error_Msg_Name_2 := Id;
1769                Error_Msg_N ("pragma% argument expects identifier%", Arg);
1770                raise Pragma_Exit;
1771             end if;
1772          end if;
1773       end Check_Optional_Identifier;
1774
1775       procedure Check_Optional_Identifier (Arg : Node_Id; Id : String) is
1776       begin
1777          Name_Buffer (1 .. Id'Length) := Id;
1778          Name_Len := Id'Length;
1779          Check_Optional_Identifier (Arg, Name_Find);
1780       end Check_Optional_Identifier;
1781
1782       --------------------------------------
1783       -- Check_Precondition_Postcondition --
1784       --------------------------------------
1785
1786       procedure Check_Precondition_Postcondition (In_Body : out Boolean) is
1787          P  : Node_Id;
1788          PO : Node_Id;
1789
1790          procedure Chain_PPC (PO : Node_Id);
1791          --  If PO is an entry or a [generic] subprogram declaration node, then
1792          --  the precondition/postcondition applies to this subprogram and the
1793          --  processing for the pragma is completed. Otherwise the pragma is
1794          --  misplaced.
1795
1796          ---------------
1797          -- Chain_PPC --
1798          ---------------
1799
1800          procedure Chain_PPC (PO : Node_Id) is
1801             S   : Entity_Id;
1802             P   : Node_Id;
1803
1804          begin
1805             if Nkind (PO) = N_Abstract_Subprogram_Declaration then
1806                if not From_Aspect_Specification (N) then
1807                   Error_Pragma
1808                     ("pragma% cannot be applied to abstract subprogram");
1809
1810                elsif Class_Present (N) then
1811                   null;
1812
1813                else
1814                   Error_Pragma
1815                     ("aspect % requires ''Class for abstract subprogram");
1816                end if;
1817
1818             --  AI05-0230: The same restriction applies to null procedures. For
1819             --  compatibility with earlier uses of the Ada pragma, apply this
1820             --  rule only to aspect specifications.
1821
1822             --  The above discrpency needs documentation. Robert is dubious
1823             --  about whether it is a good idea ???
1824
1825             elsif Nkind (PO) = N_Subprogram_Declaration
1826               and then Nkind (Specification (PO)) = N_Procedure_Specification
1827               and then Null_Present (Specification (PO))
1828               and then From_Aspect_Specification (N)
1829               and then not Class_Present (N)
1830             then
1831                Error_Pragma
1832                  ("aspect % requires ''Class for null procedure");
1833
1834             elsif not Nkind_In (PO, N_Subprogram_Declaration,
1835                                     N_Expression_Function,
1836                                     N_Generic_Subprogram_Declaration,
1837                                     N_Entry_Declaration)
1838             then
1839                Pragma_Misplaced;
1840             end if;
1841
1842             --  Here if we have [generic] subprogram or entry declaration
1843
1844             if Nkind (PO) = N_Entry_Declaration then
1845                S := Defining_Entity (PO);
1846             else
1847                S := Defining_Unit_Name (Specification (PO));
1848             end if;
1849
1850             --  Make sure we do not have the case of a precondition pragma when
1851             --  the Pre'Class aspect is present.
1852
1853             --  We do this by looking at pragmas already chained to the entity
1854             --  since the aspect derived pragma will be put on this list first.
1855
1856             if Pragma_Name (N) = Name_Precondition then
1857                if not From_Aspect_Specification (N) then
1858                   P := Spec_PPC_List (Contract (S));
1859                   while Present (P) loop
1860                      if Pragma_Name (P) = Name_Precondition
1861                        and then From_Aspect_Specification (P)
1862                        and then Class_Present (P)
1863                      then
1864                         Error_Msg_Sloc := Sloc (P);
1865                         Error_Pragma
1866                           ("pragma% not allowed, `Pre''Class` aspect given#");
1867                      end if;
1868
1869                      P := Next_Pragma (P);
1870                   end loop;
1871                end if;
1872             end if;
1873
1874             --  Similarly check for Pre with inherited Pre'Class. Note that
1875             --  we cover the aspect case as well here.
1876
1877             if Pragma_Name (N) = Name_Precondition
1878               and then not Class_Present (N)
1879             then
1880                declare
1881                   Inherited : constant Subprogram_List :=
1882                                 Inherited_Subprograms (S);
1883                   P         : Node_Id;
1884
1885                begin
1886                   for J in Inherited'Range loop
1887                      P := Spec_PPC_List (Contract (Inherited (J)));
1888                      while Present (P) loop
1889                         if Pragma_Name (P) = Name_Precondition
1890                           and then Class_Present (P)
1891                         then
1892                            Error_Msg_Sloc := Sloc (P);
1893                            Error_Pragma
1894                              ("pragma% not allowed, `Pre''Class` "
1895                               & "aspect inherited from#");
1896                         end if;
1897
1898                         P := Next_Pragma (P);
1899                      end loop;
1900                   end loop;
1901                end;
1902             end if;
1903
1904             --  Note: we do not analyze the pragma at this point. Instead we
1905             --  delay this analysis until the end of the declarative part in
1906             --  which the pragma appears. This implements the required delay
1907             --  in this analysis, allowing forward references. The analysis
1908             --  happens at the end of Analyze_Declarations.
1909
1910             --  Chain spec PPC pragma to list for subprogram
1911
1912             Set_Next_Pragma (N, Spec_PPC_List (Contract (S)));
1913             Set_Spec_PPC_List (Contract (S), N);
1914
1915             --  Return indicating spec case
1916
1917             In_Body := False;
1918             return;
1919          end Chain_PPC;
1920
1921       --  Start of processing for Check_Precondition_Postcondition
1922
1923       begin
1924          if not Is_List_Member (N) then
1925             Pragma_Misplaced;
1926          end if;
1927
1928          --  Preanalyze message argument if present. Visibility in this
1929          --  argument is established at the point of pragma occurrence.
1930
1931          if Arg_Count = 2 then
1932             Check_Optional_Identifier (Arg2, Name_Message);
1933             Preanalyze_Spec_Expression
1934               (Get_Pragma_Arg (Arg2), Standard_String);
1935          end if;
1936
1937          --  Record if pragma is disabled
1938
1939          if Check_Enabled (Pname) then
1940             Set_SCO_Pragma_Enabled (Loc);
1941          end if;
1942
1943          --  If we are within an inlined body, the legality of the pragma
1944          --  has been checked already.
1945
1946          if In_Inlined_Body then
1947             In_Body := True;
1948             return;
1949          end if;
1950
1951          --  Search prior declarations
1952
1953          P := N;
1954          while Present (Prev (P)) loop
1955             P := Prev (P);
1956
1957             --  If the previous node is a generic subprogram, do not go to to
1958             --  the original node, which is the unanalyzed tree: we need to
1959             --  attach the pre/postconditions to the analyzed version at this
1960             --  point. They get propagated to the original tree when analyzing
1961             --  the corresponding body.
1962
1963             if Nkind (P) not in N_Generic_Declaration then
1964                PO := Original_Node (P);
1965             else
1966                PO := P;
1967             end if;
1968
1969             --  Skip past prior pragma
1970
1971             if Nkind (PO) = N_Pragma then
1972                null;
1973
1974             --  Skip stuff not coming from source
1975
1976             elsif not Comes_From_Source (PO) then
1977
1978                --  The condition may apply to a subprogram instantiation
1979
1980                if Nkind (PO) = N_Subprogram_Declaration
1981                  and then Present (Generic_Parent (Specification (PO)))
1982                then
1983                   Chain_PPC (PO);
1984                   return;
1985
1986                elsif Nkind (PO) = N_Subprogram_Declaration
1987                  and then In_Instance
1988                then
1989                   Chain_PPC (PO);
1990                   return;
1991
1992                --  For all other cases of non source code, do nothing
1993
1994                else
1995                   null;
1996                end if;
1997
1998             --  Only remaining possibility is subprogram declaration
1999
2000             else
2001                Chain_PPC (PO);
2002                return;
2003             end if;
2004          end loop;
2005
2006          --  If we fall through loop, pragma is at start of list, so see if it
2007          --  is at the start of declarations of a subprogram body.
2008
2009          if Nkind (Parent (N)) = N_Subprogram_Body
2010            and then List_Containing (N) = Declarations (Parent (N))
2011          then
2012             if Operating_Mode /= Generate_Code
2013               or else Inside_A_Generic
2014             then
2015                --  Analyze pragma expression for correctness and for ASIS use
2016
2017                Preanalyze_Spec_Expression
2018                  (Get_Pragma_Arg (Arg1), Standard_Boolean);
2019
2020                --  In ASIS mode, for a pragma generated from a source aspect,
2021                --  also analyze the original aspect expression.
2022
2023                if ASIS_Mode
2024                  and then Present (Corresponding_Aspect (N))
2025                then
2026                   Preanalyze_Spec_Expression
2027                     (Expression (Corresponding_Aspect (N)), Standard_Boolean);
2028                end if;
2029             end if;
2030
2031             In_Body := True;
2032             return;
2033
2034          --  See if it is in the pragmas after a library level subprogram
2035
2036          elsif Nkind (Parent (N)) = N_Compilation_Unit_Aux then
2037
2038             --  In formal verification mode, analyze pragma expression for
2039             --  correctness, as it is not expanded later.
2040
2041             if Alfa_Mode then
2042                Analyze_PPC_In_Decl_Part
2043                  (N, Defining_Entity (Unit (Parent (Parent (N)))));
2044             end if;
2045
2046             Chain_PPC (Unit (Parent (Parent (N))));
2047             return;
2048          end if;
2049
2050          --  If we fall through, pragma was misplaced
2051
2052          Pragma_Misplaced;
2053       end Check_Precondition_Postcondition;
2054
2055       -----------------------------
2056       -- Check_Static_Constraint --
2057       -----------------------------
2058
2059       --  Note: for convenience in writing this procedure, in addition to
2060       --  the officially (i.e. by spec) allowed argument which is always a
2061       --  constraint, it also allows ranges and discriminant associations.
2062       --  Above is not clear ???
2063
2064       procedure Check_Static_Constraint (Constr : Node_Id) is
2065
2066          procedure Require_Static (E : Node_Id);
2067          --  Require given expression to be static expression
2068
2069          --------------------
2070          -- Require_Static --
2071          --------------------
2072
2073          procedure Require_Static (E : Node_Id) is
2074          begin
2075             if not Is_OK_Static_Expression (E) then
2076                Flag_Non_Static_Expr
2077                  ("non-static constraint not allowed in Unchecked_Union!", E);
2078                raise Pragma_Exit;
2079             end if;
2080          end Require_Static;
2081
2082       --  Start of processing for Check_Static_Constraint
2083
2084       begin
2085          case Nkind (Constr) is
2086             when N_Discriminant_Association =>
2087                Require_Static (Expression (Constr));
2088
2089             when N_Range =>
2090                Require_Static (Low_Bound (Constr));
2091                Require_Static (High_Bound (Constr));
2092
2093             when N_Attribute_Reference =>
2094                Require_Static (Type_Low_Bound  (Etype (Prefix (Constr))));
2095                Require_Static (Type_High_Bound (Etype (Prefix (Constr))));
2096
2097             when N_Range_Constraint =>
2098                Check_Static_Constraint (Range_Expression (Constr));
2099
2100             when N_Index_Or_Discriminant_Constraint =>
2101                declare
2102                   IDC : Entity_Id;
2103                begin
2104                   IDC := First (Constraints (Constr));
2105                   while Present (IDC) loop
2106                      Check_Static_Constraint (IDC);
2107                      Next (IDC);
2108                   end loop;
2109                end;
2110
2111             when others =>
2112                null;
2113          end case;
2114       end Check_Static_Constraint;
2115
2116       ---------------------
2117       -- Check_Test_Case --
2118       ---------------------
2119
2120       procedure Check_Test_Case is
2121          P  : Node_Id;
2122          PO : Node_Id;
2123
2124          procedure Chain_TC (PO : Node_Id);
2125          --  If PO is a [generic] subprogram declaration node, then the
2126          --  test-case applies to this subprogram and the processing for the
2127          --  pragma is completed. Otherwise the pragma is misplaced.
2128
2129          --------------
2130          -- Chain_TC --
2131          --------------
2132
2133          procedure Chain_TC (PO : Node_Id) is
2134             S   : Entity_Id;
2135
2136          begin
2137             if Nkind (PO) = N_Abstract_Subprogram_Declaration then
2138                if From_Aspect_Specification (N) then
2139                   Error_Pragma
2140                     ("aspect% cannot be applied to abstract subprogram");
2141                else
2142                   Error_Pragma
2143                     ("pragma% cannot be applied to abstract subprogram");
2144                end if;
2145
2146             elsif Nkind (PO) = N_Entry_Declaration then
2147                if From_Aspect_Specification (N) then
2148                   Error_Pragma ("aspect% cannot be applied to entry");
2149                else
2150                   Error_Pragma ("pragma% cannot be applied to entry");
2151                end if;
2152
2153             elsif not Nkind_In (PO, N_Subprogram_Declaration,
2154                                     N_Generic_Subprogram_Declaration)
2155             then
2156                Pragma_Misplaced;
2157             end if;
2158
2159             --  Here if we have [generic] subprogram declaration
2160
2161             S := Defining_Unit_Name (Specification (PO));
2162
2163             --  Note: we do not analyze the pragma at this point. Instead we
2164             --  delay this analysis until the end of the declarative part in
2165             --  which the pragma appears. This implements the required delay
2166             --  in this analysis, allowing forward references. The analysis
2167             --  happens at the end of Analyze_Declarations.
2168
2169             --  There should not be another test case with the same name
2170             --  associated to this subprogram.
2171
2172             declare
2173                Name : constant String_Id := Get_Name_From_Test_Case_Pragma (N);
2174                TC   : Node_Id;
2175
2176             begin
2177                TC := Spec_TC_List (Contract (S));
2178                while Present (TC) loop
2179
2180                   if String_Equal
2181                     (Name, Get_Name_From_Test_Case_Pragma (TC))
2182                   then
2183                      Error_Msg_Sloc := Sloc (TC);
2184
2185                      if From_Aspect_Specification (N) then
2186                         Error_Pragma ("name for aspect% is already used#");
2187                      else
2188                         Error_Pragma ("name for pragma% is already used#");
2189                      end if;
2190                   end if;
2191
2192                   TC := Next_Pragma (TC);
2193                end loop;
2194             end;
2195
2196             --  Chain spec TC pragma to list for subprogram
2197
2198             Set_Next_Pragma (N, Spec_TC_List (Contract (S)));
2199             Set_Spec_TC_List (Contract (S), N);
2200          end Chain_TC;
2201
2202       --  Start of processing for Check_Test_Case
2203
2204       begin
2205          if not Is_List_Member (N) then
2206             Pragma_Misplaced;
2207          end if;
2208
2209          --  Test cases should only appear in package spec unit
2210
2211          if Get_Source_Unit (N) = No_Unit
2212            or else not Nkind_In (Sinfo.Unit (Cunit (Get_Source_Unit (N))),
2213                                  N_Package_Declaration,
2214                                  N_Generic_Package_Declaration)
2215          then
2216             Pragma_Misplaced;
2217          end if;
2218
2219          --  Search prior declarations
2220
2221          P := N;
2222          while Present (Prev (P)) loop
2223             P := Prev (P);
2224
2225             --  If the previous node is a generic subprogram, do not go to to
2226             --  the original node, which is the unanalyzed tree: we need to
2227             --  attach the test-case to the analyzed version at this point.
2228             --  They get propagated to the original tree when analyzing the
2229             --  corresponding body.
2230
2231             if Nkind (P) not in N_Generic_Declaration then
2232                PO := Original_Node (P);
2233             else
2234                PO := P;
2235             end if;
2236
2237             --  Skip past prior pragma
2238
2239             if Nkind (PO) = N_Pragma then
2240                null;
2241
2242             --  Skip stuff not coming from source
2243
2244             elsif not Comes_From_Source (PO) then
2245                null;
2246
2247             --  Only remaining possibility is subprogram declaration. First
2248             --  check that it is declared directly in a package declaration.
2249             --  This may be either the package declaration for the current unit
2250             --  being defined or a local package declaration.
2251
2252             elsif not Present (Parent (Parent (PO)))
2253               or else not Present (Parent (Parent (Parent (PO))))
2254               or else not Nkind_In (Parent (Parent (PO)),
2255                                     N_Package_Declaration,
2256                                     N_Generic_Package_Declaration)
2257             then
2258                Pragma_Misplaced;
2259
2260             else
2261                Chain_TC (PO);
2262                return;
2263             end if;
2264          end loop;
2265
2266          --  If we fall through, pragma was misplaced
2267
2268          Pragma_Misplaced;
2269       end Check_Test_Case;
2270
2271       --------------------------------------
2272       -- Check_Valid_Configuration_Pragma --
2273       --------------------------------------
2274
2275       --  A configuration pragma must appear in the context clause of a
2276       --  compilation unit, and only other pragmas may precede it. Note that
2277       --  the test also allows use in a configuration pragma file.
2278
2279       procedure Check_Valid_Configuration_Pragma is
2280       begin
2281          if not Is_Configuration_Pragma then
2282             Error_Pragma ("incorrect placement for configuration pragma%");
2283          end if;
2284       end Check_Valid_Configuration_Pragma;
2285
2286       -------------------------------------
2287       -- Check_Valid_Library_Unit_Pragma --
2288       -------------------------------------
2289
2290       procedure Check_Valid_Library_Unit_Pragma is
2291          Plist       : List_Id;
2292          Parent_Node : Node_Id;
2293          Unit_Name   : Entity_Id;
2294          Unit_Kind   : Node_Kind;
2295          Unit_Node   : Node_Id;
2296          Sindex      : Source_File_Index;
2297
2298       begin
2299          if not Is_List_Member (N) then
2300             Pragma_Misplaced;
2301
2302          else
2303             Plist := List_Containing (N);
2304             Parent_Node := Parent (Plist);
2305
2306             if Parent_Node = Empty then
2307                Pragma_Misplaced;
2308
2309             --  Case of pragma appearing after a compilation unit. In this case
2310             --  it must have an argument with the corresponding name and must
2311             --  be part of the following pragmas of its parent.
2312
2313             elsif Nkind (Parent_Node) = N_Compilation_Unit_Aux then
2314                if Plist /= Pragmas_After (Parent_Node) then
2315                   Pragma_Misplaced;
2316
2317                elsif Arg_Count = 0 then
2318                   Error_Pragma
2319                     ("argument required if outside compilation unit");
2320
2321                else
2322                   Check_No_Identifiers;
2323                   Check_Arg_Count (1);
2324                   Unit_Node := Unit (Parent (Parent_Node));
2325                   Unit_Kind := Nkind (Unit_Node);
2326
2327                   Analyze (Get_Pragma_Arg (Arg1));
2328
2329                   if Unit_Kind = N_Generic_Subprogram_Declaration
2330                     or else Unit_Kind = N_Subprogram_Declaration
2331                   then
2332                      Unit_Name := Defining_Entity (Unit_Node);
2333
2334                   elsif Unit_Kind in N_Generic_Instantiation then
2335                      Unit_Name := Defining_Entity (Unit_Node);
2336
2337                   else
2338                      Unit_Name := Cunit_Entity (Current_Sem_Unit);
2339                   end if;
2340
2341                   if Chars (Unit_Name) /=
2342                      Chars (Entity (Get_Pragma_Arg (Arg1)))
2343                   then
2344                      Error_Pragma_Arg
2345                        ("pragma% argument is not current unit name", Arg1);
2346                   end if;
2347
2348                   if Ekind (Unit_Name) = E_Package
2349                     and then Present (Renamed_Entity (Unit_Name))
2350                   then
2351                      Error_Pragma ("pragma% not allowed for renamed package");
2352                   end if;
2353                end if;
2354
2355             --  Pragma appears other than after a compilation unit
2356
2357             else
2358                --  Here we check for the generic instantiation case and also
2359                --  for the case of processing a generic formal package. We
2360                --  detect these cases by noting that the Sloc on the node
2361                --  does not belong to the current compilation unit.
2362
2363                Sindex := Source_Index (Current_Sem_Unit);
2364
2365                if Loc not in Source_First (Sindex) .. Source_Last (Sindex) then
2366                   Rewrite (N, Make_Null_Statement (Loc));
2367                   return;
2368
2369                --  If before first declaration, the pragma applies to the
2370                --  enclosing unit, and the name if present must be this name.
2371
2372                elsif Is_Before_First_Decl (N, Plist) then
2373                   Unit_Node := Unit_Declaration_Node (Current_Scope);
2374                   Unit_Kind := Nkind (Unit_Node);
2375
2376                   if Nkind (Parent (Unit_Node)) /= N_Compilation_Unit then
2377                      Pragma_Misplaced;
2378
2379                   elsif Unit_Kind = N_Subprogram_Body
2380                     and then not Acts_As_Spec (Unit_Node)
2381                   then
2382                      Pragma_Misplaced;
2383
2384                   elsif Nkind (Parent_Node) = N_Package_Body then
2385                      Pragma_Misplaced;
2386
2387                   elsif Nkind (Parent_Node) = N_Package_Specification
2388                     and then Plist = Private_Declarations (Parent_Node)
2389                   then
2390                      Pragma_Misplaced;
2391
2392                   elsif (Nkind (Parent_Node) = N_Generic_Package_Declaration
2393                            or else Nkind (Parent_Node) =
2394                                              N_Generic_Subprogram_Declaration)
2395                     and then Plist = Generic_Formal_Declarations (Parent_Node)
2396                   then
2397                      Pragma_Misplaced;
2398
2399                   elsif Arg_Count > 0 then
2400                      Analyze (Get_Pragma_Arg (Arg1));
2401
2402                      if Entity (Get_Pragma_Arg (Arg1)) /= Current_Scope then
2403                         Error_Pragma_Arg
2404                           ("name in pragma% must be enclosing unit", Arg1);
2405                      end if;
2406
2407                   --  It is legal to have no argument in this context
2408
2409                   else
2410                      return;
2411                   end if;
2412
2413                --  Error if not before first declaration. This is because a
2414                --  library unit pragma argument must be the name of a library
2415                --  unit (RM 10.1.5(7)), but the only names permitted in this
2416                --  context are (RM 10.1.5(6)) names of subprogram declarations,
2417                --  generic subprogram declarations or generic instantiations.
2418
2419                else
2420                   Error_Pragma
2421                     ("pragma% misplaced, must be before first declaration");
2422                end if;
2423             end if;
2424          end if;
2425       end Check_Valid_Library_Unit_Pragma;
2426
2427       -------------------
2428       -- Check_Variant --
2429       -------------------
2430
2431       procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id) is
2432          Clist : constant Node_Id := Component_List (Variant);
2433          Comp  : Node_Id;
2434
2435       begin
2436          if not Is_Non_Empty_List (Component_Items (Clist)) then
2437             Error_Msg_N
2438               ("Unchecked_Union may not have empty component list",
2439                Variant);
2440             return;
2441          end if;
2442
2443          Comp := First (Component_Items (Clist));
2444          while Present (Comp) loop
2445             Check_Component (Comp, UU_Typ, In_Variant_Part => True);
2446             Next (Comp);
2447          end loop;
2448       end Check_Variant;
2449
2450       ------------------
2451       -- Error_Pragma --
2452       ------------------
2453
2454       procedure Error_Pragma (Msg : String) is
2455          MsgF : String := Msg;
2456       begin
2457          Error_Msg_Name_1 := Pname;
2458          Fix_Error (MsgF);
2459          Error_Msg_N (MsgF, N);
2460          raise Pragma_Exit;
2461       end Error_Pragma;
2462
2463       ----------------------
2464       -- Error_Pragma_Arg --
2465       ----------------------
2466
2467       procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id) is
2468          MsgF : String := Msg;
2469       begin
2470          Error_Msg_Name_1 := Pname;
2471          Fix_Error (MsgF);
2472          Error_Msg_N (MsgF, Get_Pragma_Arg (Arg));
2473          raise Pragma_Exit;
2474       end Error_Pragma_Arg;
2475
2476       procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id) is
2477          MsgF : String := Msg1;
2478       begin
2479          Error_Msg_Name_1 := Pname;
2480          Fix_Error (MsgF);
2481          Error_Msg_N (MsgF, Get_Pragma_Arg (Arg));
2482          Error_Pragma_Arg (Msg2, Arg);
2483       end Error_Pragma_Arg;
2484
2485       ----------------------------
2486       -- Error_Pragma_Arg_Ident --
2487       ----------------------------
2488
2489       procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id) is
2490          MsgF : String := Msg;
2491       begin
2492          Error_Msg_Name_1 := Pname;
2493          Fix_Error (MsgF);
2494          Error_Msg_N (MsgF, Arg);
2495          raise Pragma_Exit;
2496       end Error_Pragma_Arg_Ident;
2497
2498       ----------------------
2499       -- Error_Pragma_Ref --
2500       ----------------------
2501
2502       procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id) is
2503          MsgF : String := Msg;
2504       begin
2505          Error_Msg_Name_1 := Pname;
2506          Fix_Error (MsgF);
2507          Error_Msg_Sloc   := Sloc (Ref);
2508          Error_Msg_NE (MsgF, N, Ref);
2509          raise Pragma_Exit;
2510       end Error_Pragma_Ref;
2511
2512       ------------------------
2513       -- Find_Lib_Unit_Name --
2514       ------------------------
2515
2516       function Find_Lib_Unit_Name return Entity_Id is
2517       begin
2518          --  Return inner compilation unit entity, for case of nested
2519          --  categorization pragmas. This happens in generic unit.
2520
2521          if Nkind (Parent (N)) = N_Package_Specification
2522            and then Defining_Entity (Parent (N)) /= Current_Scope
2523          then
2524             return Defining_Entity (Parent (N));
2525          else
2526             return Current_Scope;
2527          end if;
2528       end Find_Lib_Unit_Name;
2529
2530       ----------------------------
2531       -- Find_Program_Unit_Name --
2532       ----------------------------
2533
2534       procedure Find_Program_Unit_Name (Id : Node_Id) is
2535          Unit_Name : Entity_Id;
2536          Unit_Kind : Node_Kind;
2537          P         : constant Node_Id := Parent (N);
2538
2539       begin
2540          if Nkind (P) = N_Compilation_Unit then
2541             Unit_Kind := Nkind (Unit (P));
2542
2543             if Unit_Kind = N_Subprogram_Declaration
2544               or else Unit_Kind = N_Package_Declaration
2545               or else Unit_Kind in N_Generic_Declaration
2546             then
2547                Unit_Name := Defining_Entity (Unit (P));
2548
2549                if Chars (Id) = Chars (Unit_Name) then
2550                   Set_Entity (Id, Unit_Name);
2551                   Set_Etype (Id, Etype (Unit_Name));
2552                else
2553                   Set_Etype (Id, Any_Type);
2554                   Error_Pragma
2555                     ("cannot find program unit referenced by pragma%");
2556                end if;
2557
2558             else
2559                Set_Etype (Id, Any_Type);
2560                Error_Pragma ("pragma% inapplicable to this unit");
2561             end if;
2562
2563          else
2564             Analyze (Id);
2565          end if;
2566       end Find_Program_Unit_Name;
2567
2568       -----------------------------------------
2569       -- Find_Unique_Parameterless_Procedure --
2570       -----------------------------------------
2571
2572       function Find_Unique_Parameterless_Procedure
2573         (Name : Entity_Id;
2574          Arg  : Node_Id) return Entity_Id
2575       is
2576          Proc : Entity_Id := Empty;
2577
2578       begin
2579          --  The body of this procedure needs some comments ???
2580
2581          if not Is_Entity_Name (Name) then
2582             Error_Pragma_Arg
2583               ("argument of pragma% must be entity name", Arg);
2584
2585          elsif not Is_Overloaded (Name) then
2586             Proc := Entity (Name);
2587
2588             if Ekind (Proc) /= E_Procedure
2589               or else Present (First_Formal (Proc))
2590             then
2591                Error_Pragma_Arg
2592                  ("argument of pragma% must be parameterless procedure", Arg);
2593             end if;
2594
2595          else
2596             declare
2597                Found : Boolean := False;
2598                It    : Interp;
2599                Index : Interp_Index;
2600
2601             begin
2602                Get_First_Interp (Name, Index, It);
2603                while Present (It.Nam) loop
2604                   Proc := It.Nam;
2605
2606                   if Ekind (Proc) = E_Procedure
2607                     and then No (First_Formal (Proc))
2608                   then
2609                      if not Found then
2610                         Found := True;
2611                         Set_Entity (Name, Proc);
2612                         Set_Is_Overloaded (Name, False);
2613                      else
2614                         Error_Pragma_Arg
2615                           ("ambiguous handler name for pragma% ", Arg);
2616                      end if;
2617                   end if;
2618
2619                   Get_Next_Interp (Index, It);
2620                end loop;
2621
2622                if not Found then
2623                   Error_Pragma_Arg
2624                     ("argument of pragma% must be parameterless procedure",
2625                      Arg);
2626                else
2627                   Proc := Entity (Name);
2628                end if;
2629             end;
2630          end if;
2631
2632          return Proc;
2633       end Find_Unique_Parameterless_Procedure;
2634
2635       ---------------
2636       -- Fix_Error --
2637       ---------------
2638
2639       procedure Fix_Error (Msg : in out String) is
2640       begin
2641          if From_Aspect_Specification (N) then
2642             for J in Msg'First .. Msg'Last - 5 loop
2643                if Msg (J .. J + 5) = "pragma" then
2644                   Msg (J .. J + 5) := "aspect";
2645                end if;
2646             end loop;
2647
2648             if Error_Msg_Name_1 = Name_Precondition then
2649                Error_Msg_Name_1 := Name_Pre;
2650             elsif Error_Msg_Name_1 = Name_Postcondition then
2651                Error_Msg_Name_1 := Name_Post;
2652             end if;
2653          end if;
2654       end Fix_Error;
2655
2656       -------------------------
2657       -- Gather_Associations --
2658       -------------------------
2659
2660       procedure Gather_Associations
2661         (Names : Name_List;
2662          Args  : out Args_List)
2663       is
2664          Arg : Node_Id;
2665
2666       begin
2667          --  Initialize all parameters to Empty
2668
2669          for J in Args'Range loop
2670             Args (J) := Empty;
2671          end loop;
2672
2673          --  That's all we have to do if there are no argument associations
2674
2675          if No (Pragma_Argument_Associations (N)) then
2676             return;
2677          end if;
2678
2679          --  Otherwise first deal with any positional parameters present
2680
2681          Arg := First (Pragma_Argument_Associations (N));
2682          for Index in Args'Range loop
2683             exit when No (Arg) or else Chars (Arg) /= No_Name;
2684             Args (Index) := Get_Pragma_Arg (Arg);
2685             Next (Arg);
2686          end loop;
2687
2688          --  Positional parameters all processed, if any left, then we
2689          --  have too many positional parameters.
2690
2691          if Present (Arg) and then Chars (Arg) = No_Name then
2692             Error_Pragma_Arg
2693               ("too many positional associations for pragma%", Arg);
2694          end if;
2695
2696          --  Process named parameters if any are present
2697
2698          while Present (Arg) loop
2699             if Chars (Arg) = No_Name then
2700                Error_Pragma_Arg
2701                  ("positional association cannot follow named association",
2702                   Arg);
2703
2704             else
2705                for Index in Names'Range loop
2706                   if Names (Index) = Chars (Arg) then
2707                      if Present (Args (Index)) then
2708                         Error_Pragma_Arg
2709                           ("duplicate argument association for pragma%", Arg);
2710                      else
2711                         Args (Index) := Get_Pragma_Arg (Arg);
2712                         exit;
2713                      end if;
2714                   end if;
2715
2716                   if Index = Names'Last then
2717                      Error_Msg_Name_1 := Pname;
2718                      Error_Msg_N ("pragma% does not allow & argument", Arg);
2719
2720                      --  Check for possible misspelling
2721
2722                      for Index1 in Names'Range loop
2723                         if Is_Bad_Spelling_Of
2724                              (Chars (Arg), Names (Index1))
2725                         then
2726                            Error_Msg_Name_1 := Names (Index1);
2727                            Error_Msg_N -- CODEFIX
2728                              ("\possible misspelling of%", Arg);
2729                            exit;
2730                         end if;
2731                      end loop;
2732
2733                      raise Pragma_Exit;
2734                   end if;
2735                end loop;
2736             end if;
2737
2738             Next (Arg);
2739          end loop;
2740       end Gather_Associations;
2741
2742       -----------------
2743       -- GNAT_Pragma --
2744       -----------------
2745
2746       procedure GNAT_Pragma is
2747       begin
2748          --  We need to check the No_Implementation_Pragmas restriction for
2749          --  the case of a pragma from source. Note that the case of aspects
2750          --  generating corresponding pragmas marks these pragmas as not being
2751          --  from source, so this test also catches that case.
2752
2753          if Comes_From_Source (N) then
2754             Check_Restriction (No_Implementation_Pragmas, N);
2755          end if;
2756       end GNAT_Pragma;
2757
2758       --------------------------
2759       -- Is_Before_First_Decl --
2760       --------------------------
2761
2762       function Is_Before_First_Decl
2763         (Pragma_Node : Node_Id;
2764          Decls       : List_Id) return Boolean
2765       is
2766          Item : Node_Id := First (Decls);
2767
2768       begin
2769          --  Only other pragmas can come before this pragma
2770
2771          loop
2772             if No (Item) or else Nkind (Item) /= N_Pragma then
2773                return False;
2774
2775             elsif Item = Pragma_Node then
2776                return True;
2777             end if;
2778
2779             Next (Item);
2780          end loop;
2781       end Is_Before_First_Decl;
2782
2783       -----------------------------
2784       -- Is_Configuration_Pragma --
2785       -----------------------------
2786
2787       --  A configuration pragma must appear in the context clause of a
2788       --  compilation unit, and only other pragmas may precede it. Note that
2789       --  the test below also permits use in a configuration pragma file.
2790
2791       function Is_Configuration_Pragma return Boolean is
2792          Lis : constant List_Id := List_Containing (N);
2793          Par : constant Node_Id := Parent (N);
2794          Prg : Node_Id;
2795
2796       begin
2797          --  If no parent, then we are in the configuration pragma file,
2798          --  so the placement is definitely appropriate.
2799
2800          if No (Par) then
2801             return True;
2802
2803          --  Otherwise we must be in the context clause of a compilation unit
2804          --  and the only thing allowed before us in the context list is more
2805          --  configuration pragmas.
2806
2807          elsif Nkind (Par) = N_Compilation_Unit
2808            and then Context_Items (Par) = Lis
2809          then
2810             Prg := First (Lis);
2811
2812             loop
2813                if Prg = N then
2814                   return True;
2815                elsif Nkind (Prg) /= N_Pragma then
2816                   return False;
2817                end if;
2818
2819                Next (Prg);
2820             end loop;
2821
2822          else
2823             return False;
2824          end if;
2825       end Is_Configuration_Pragma;
2826
2827       --------------------------
2828       -- Is_In_Context_Clause --
2829       --------------------------
2830
2831       function Is_In_Context_Clause return Boolean is
2832          Plist       : List_Id;
2833          Parent_Node : Node_Id;
2834
2835       begin
2836          if not Is_List_Member (N) then
2837             return False;
2838
2839          else
2840             Plist := List_Containing (N);
2841             Parent_Node := Parent (Plist);
2842
2843             if Parent_Node = Empty
2844               or else Nkind (Parent_Node) /= N_Compilation_Unit
2845               or else Context_Items (Parent_Node) /= Plist
2846             then
2847                return False;
2848             end if;
2849          end if;
2850
2851          return True;
2852       end Is_In_Context_Clause;
2853
2854       ---------------------------------
2855       -- Is_Static_String_Expression --
2856       ---------------------------------
2857
2858       function Is_Static_String_Expression (Arg : Node_Id) return Boolean is
2859          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
2860
2861       begin
2862          Analyze_And_Resolve (Argx);
2863          return Is_OK_Static_Expression (Argx)
2864            and then Nkind (Argx) = N_String_Literal;
2865       end Is_Static_String_Expression;
2866
2867       ----------------------
2868       -- Pragma_Misplaced --
2869       ----------------------
2870
2871       procedure Pragma_Misplaced is
2872       begin
2873          Error_Pragma ("incorrect placement of pragma%");
2874       end Pragma_Misplaced;
2875
2876       ------------------------------------
2877       -- Process Atomic_Shared_Volatile --
2878       ------------------------------------
2879
2880       procedure Process_Atomic_Shared_Volatile is
2881          E_Id : Node_Id;
2882          E    : Entity_Id;
2883          D    : Node_Id;
2884          K    : Node_Kind;
2885          Utyp : Entity_Id;
2886
2887          procedure Set_Atomic (E : Entity_Id);
2888          --  Set given type as atomic, and if no explicit alignment was given,
2889          --  set alignment to unknown, since back end knows what the alignment
2890          --  requirements are for atomic arrays. Note: this step is necessary
2891          --  for derived types.
2892
2893          ----------------
2894          -- Set_Atomic --
2895          ----------------
2896
2897          procedure Set_Atomic (E : Entity_Id) is
2898          begin
2899             Set_Is_Atomic (E);
2900
2901             if not Has_Alignment_Clause (E) then
2902                Set_Alignment (E, Uint_0);
2903             end if;
2904          end Set_Atomic;
2905
2906       --  Start of processing for Process_Atomic_Shared_Volatile
2907
2908       begin
2909          Check_Ada_83_Warning;
2910          Check_No_Identifiers;
2911          Check_Arg_Count (1);
2912          Check_Arg_Is_Local_Name (Arg1);
2913          E_Id := Get_Pragma_Arg (Arg1);
2914
2915          if Etype (E_Id) = Any_Type then
2916             return;
2917          end if;
2918
2919          E := Entity (E_Id);
2920          D := Declaration_Node (E);
2921          K := Nkind (D);
2922
2923          --  Check duplicate before we chain ourselves!
2924
2925          Check_Duplicate_Pragma (E);
2926
2927          --  Now check appropriateness of the entity
2928
2929          if Is_Type (E) then
2930             if Rep_Item_Too_Early (E, N)
2931                  or else
2932                Rep_Item_Too_Late (E, N)
2933             then
2934                return;
2935             else
2936                Check_First_Subtype (Arg1);
2937             end if;
2938
2939             if Prag_Id /= Pragma_Volatile then
2940                Set_Atomic (E);
2941                Set_Atomic (Underlying_Type (E));
2942                Set_Atomic (Base_Type (E));
2943             end if;
2944
2945             --  Attribute belongs on the base type. If the view of the type is
2946             --  currently private, it also belongs on the underlying type.
2947
2948             Set_Is_Volatile (Base_Type (E));
2949             Set_Is_Volatile (Underlying_Type (E));
2950
2951             Set_Treat_As_Volatile (E);
2952             Set_Treat_As_Volatile (Underlying_Type (E));
2953
2954          elsif K = N_Object_Declaration
2955            or else (K = N_Component_Declaration
2956                      and then Original_Record_Component (E) = E)
2957          then
2958             if Rep_Item_Too_Late (E, N) then
2959                return;
2960             end if;
2961
2962             if Prag_Id /= Pragma_Volatile then
2963                Set_Is_Atomic (E);
2964
2965                --  If the object declaration has an explicit initialization, a
2966                --  temporary may have to be created to hold the expression, to
2967                --  ensure that access to the object remain atomic.
2968
2969                if Nkind (Parent (E)) = N_Object_Declaration
2970                  and then Present (Expression (Parent (E)))
2971                then
2972                   Set_Has_Delayed_Freeze (E);
2973                end if;
2974
2975                --  An interesting improvement here. If an object of type X is
2976                --  declared atomic, and the type X is not atomic, that's a
2977                --  pity, since it may not have appropriate alignment etc. We
2978                --  can rescue this in the special case where the object and
2979                --  type are in the same unit by just setting the type as
2980                --  atomic, so that the back end will process it as atomic.
2981
2982                Utyp := Underlying_Type (Etype (E));
2983
2984                if Present (Utyp)
2985                  and then Sloc (E) > No_Location
2986                  and then Sloc (Utyp) > No_Location
2987                  and then
2988                    Get_Source_File_Index (Sloc (E)) =
2989                    Get_Source_File_Index (Sloc (Underlying_Type (Etype (E))))
2990                then
2991                   Set_Is_Atomic (Underlying_Type (Etype (E)));
2992                end if;
2993             end if;
2994
2995             Set_Is_Volatile (E);
2996             Set_Treat_As_Volatile (E);
2997
2998          else
2999             Error_Pragma_Arg
3000               ("inappropriate entity for pragma%", Arg1);
3001          end if;
3002       end Process_Atomic_Shared_Volatile;
3003
3004       -------------------------------------------
3005       -- Process_Compile_Time_Warning_Or_Error --
3006       -------------------------------------------
3007
3008       procedure Process_Compile_Time_Warning_Or_Error is
3009          Arg1x : constant Node_Id := Get_Pragma_Arg (Arg1);
3010
3011       begin
3012          Check_Arg_Count (2);
3013          Check_No_Identifiers;
3014          Check_Arg_Is_Static_Expression (Arg2, Standard_String);
3015          Analyze_And_Resolve (Arg1x, Standard_Boolean);
3016
3017          if Compile_Time_Known_Value (Arg1x) then
3018             if Is_True (Expr_Value (Get_Pragma_Arg (Arg1))) then
3019                declare
3020                   Str   : constant String_Id :=
3021                             Strval (Get_Pragma_Arg (Arg2));
3022                   Len   : constant Int := String_Length (Str);
3023                   Cont  : Boolean;
3024                   Ptr   : Nat;
3025                   CC    : Char_Code;
3026                   C     : Character;
3027                   Cent  : constant Entity_Id :=
3028                             Cunit_Entity (Current_Sem_Unit);
3029
3030                   Force : constant Boolean :=
3031                             Prag_Id = Pragma_Compile_Time_Warning
3032                               and then
3033                                 Is_Spec_Name (Unit_Name (Current_Sem_Unit))
3034                               and then (Ekind (Cent) /= E_Package
3035                                           or else not In_Private_Part (Cent));
3036                   --  Set True if this is the warning case, and we are in the
3037                   --  visible part of a package spec, or in a subprogram spec,
3038                   --  in which case we want to force the client to see the
3039                   --  warning, even though it is not in the main unit.
3040
3041                begin
3042                   --  Loop through segments of message separated by line feeds.
3043                   --  We output these segments as separate messages with
3044                   --  continuation marks for all but the first.
3045
3046                   Cont := False;
3047                   Ptr := 1;
3048                   loop
3049                      Error_Msg_Strlen := 0;
3050
3051                      --  Loop to copy characters from argument to error message
3052                      --  string buffer.
3053
3054                      loop
3055                         exit when Ptr > Len;
3056                         CC := Get_String_Char (Str, Ptr);
3057                         Ptr := Ptr + 1;
3058
3059                         --  Ignore wide chars ??? else store character
3060
3061                         if In_Character_Range (CC) then
3062                            C := Get_Character (CC);
3063                            exit when C = ASCII.LF;
3064                            Error_Msg_Strlen := Error_Msg_Strlen + 1;
3065                            Error_Msg_String (Error_Msg_Strlen) := C;
3066                         end if;
3067                      end loop;
3068
3069                      --  Here with one line ready to go
3070
3071                      Error_Msg_Warn := Prag_Id = Pragma_Compile_Time_Warning;
3072
3073                      --  If this is a warning in a spec, then we want clients
3074                      --  to see the warning, so mark the message with the
3075                      --  special sequence !! to force the warning. In the case
3076                      --  of a package spec, we do not force this if we are in
3077                      --  the private part of the spec.
3078
3079                      if Force then
3080                         if Cont = False then
3081                            Error_Msg_N ("<~!!", Arg1);
3082                            Cont := True;
3083                         else
3084                            Error_Msg_N ("\<~!!", Arg1);
3085                         end if;
3086
3087                      --  Error, rather than warning, or in a body, so we do not
3088                      --  need to force visibility for client (error will be
3089                      --  output in any case, and this is the situation in which
3090                      --  we do not want a client to get a warning, since the
3091                      --  warning is in the body or the spec private part).
3092
3093                      else
3094                         if Cont = False then
3095                            Error_Msg_N ("<~", Arg1);
3096                            Cont := True;
3097                         else
3098                            Error_Msg_N ("\<~", Arg1);
3099                         end if;
3100                      end if;
3101
3102                      exit when Ptr > Len;
3103                   end loop;
3104                end;
3105             end if;
3106          end if;
3107       end Process_Compile_Time_Warning_Or_Error;
3108
3109       ------------------------
3110       -- Process_Convention --
3111       ------------------------
3112
3113       procedure Process_Convention
3114         (C   : out Convention_Id;
3115          Ent : out Entity_Id)
3116       is
3117          Id        : Node_Id;
3118          E         : Entity_Id;
3119          E1        : Entity_Id;
3120          Cname     : Name_Id;
3121          Comp_Unit : Unit_Number_Type;
3122
3123          procedure Diagnose_Multiple_Pragmas (S : Entity_Id);
3124          --  Called if we have more than one Export/Import/Convention pragma.
3125          --  This is generally illegal, but we have a special case of allowing
3126          --  Import and Interface to coexist if they specify the convention in
3127          --  a consistent manner. We are allowed to do this, since Interface is
3128          --  an implementation defined pragma, and we choose to do it since we
3129          --  know Rational allows this combination. S is the entity id of the
3130          --  subprogram in question. This procedure also sets the special flag
3131          --  Import_Interface_Present in both pragmas in the case where we do
3132          --  have matching Import and Interface pragmas.
3133
3134          procedure Set_Convention_From_Pragma (E : Entity_Id);
3135          --  Set convention in entity E, and also flag that the entity has a
3136          --  convention pragma. If entity is for a private or incomplete type,
3137          --  also set convention and flag on underlying type. This procedure
3138          --  also deals with the special case of C_Pass_By_Copy convention.
3139
3140          -------------------------------
3141          -- Diagnose_Multiple_Pragmas --
3142          -------------------------------
3143
3144          procedure Diagnose_Multiple_Pragmas (S : Entity_Id) is
3145             Pdec : constant Node_Id := Declaration_Node (S);
3146             Decl : Node_Id;
3147             Err  : Boolean;
3148
3149             function Same_Convention (Decl : Node_Id) return Boolean;
3150             --  Decl is a pragma node. This function returns True if this
3151             --  pragma has a first argument that is an identifier with a
3152             --  Chars field corresponding to the Convention_Id C.
3153
3154             function Same_Name (Decl : Node_Id) return Boolean;
3155             --  Decl is a pragma node. This function returns True if this
3156             --  pragma has a second argument that is an identifier with a
3157             --  Chars field that matches the Chars of the current subprogram.
3158
3159             ---------------------
3160             -- Same_Convention --
3161             ---------------------
3162
3163             function Same_Convention (Decl : Node_Id) return Boolean is
3164                Arg1 : constant Node_Id :=
3165                         First (Pragma_Argument_Associations (Decl));
3166
3167             begin
3168                if Present (Arg1) then
3169                   declare
3170                      Arg : constant Node_Id := Get_Pragma_Arg (Arg1);
3171                   begin
3172                      if Nkind (Arg) = N_Identifier
3173                        and then Is_Convention_Name (Chars (Arg))
3174                        and then Get_Convention_Id (Chars (Arg)) = C
3175                      then
3176                         return True;
3177                      end if;
3178                   end;
3179                end if;
3180
3181                return False;
3182             end Same_Convention;
3183
3184             ---------------
3185             -- Same_Name --
3186             ---------------
3187
3188             function Same_Name (Decl : Node_Id) return Boolean is
3189                Arg1 : constant Node_Id :=
3190                         First (Pragma_Argument_Associations (Decl));
3191                Arg2 : Node_Id;
3192
3193             begin
3194                if No (Arg1) then
3195                   return False;
3196                end if;
3197
3198                Arg2 := Next (Arg1);
3199
3200                if No (Arg2) then
3201                   return False;
3202                end if;
3203
3204                declare
3205                   Arg : constant Node_Id := Get_Pragma_Arg (Arg2);
3206                begin
3207                   if Nkind (Arg) = N_Identifier
3208                     and then Chars (Arg) = Chars (S)
3209                   then
3210                      return True;
3211                   end if;
3212                end;
3213
3214                return False;
3215             end Same_Name;
3216
3217          --  Start of processing for Diagnose_Multiple_Pragmas
3218
3219          begin
3220             Err := True;
3221
3222             --  Definitely give message if we have Convention/Export here
3223
3224             if Prag_Id = Pragma_Convention or else Prag_Id = Pragma_Export then
3225                null;
3226
3227                --  If we have an Import or Export, scan back from pragma to
3228                --  find any previous pragma applying to the same procedure.
3229                --  The scan will be terminated by the start of the list, or
3230                --  hitting the subprogram declaration. This won't allow one
3231                --  pragma to appear in the public part and one in the private
3232                --  part, but that seems very unlikely in practice.
3233
3234             else
3235                Decl := Prev (N);
3236                while Present (Decl) and then Decl /= Pdec loop
3237
3238                   --  Look for pragma with same name as us
3239
3240                   if Nkind (Decl) = N_Pragma
3241                     and then Same_Name (Decl)
3242                   then
3243                      --  Give error if same as our pragma or Export/Convention
3244
3245                      if Pragma_Name (Decl) = Name_Export
3246                           or else
3247                         Pragma_Name (Decl) = Name_Convention
3248                           or else
3249                         Pragma_Name (Decl) = Pragma_Name (N)
3250                      then
3251                         exit;
3252
3253                      --  Case of Import/Interface or the other way round
3254
3255                      elsif Pragma_Name (Decl) = Name_Interface
3256                              or else
3257                            Pragma_Name (Decl) = Name_Import
3258                      then
3259                         --  Here we know that we have Import and Interface. It
3260                         --  doesn't matter which way round they are. See if
3261                         --  they specify the same convention. If so, all OK,
3262                         --  and set special flags to stop other messages
3263
3264                         if Same_Convention (Decl) then
3265                            Set_Import_Interface_Present (N);
3266                            Set_Import_Interface_Present (Decl);
3267                            Err := False;
3268
3269                         --  If different conventions, special message
3270
3271                         else
3272                            Error_Msg_Sloc := Sloc (Decl);
3273                            Error_Pragma_Arg
3274                              ("convention differs from that given#", Arg1);
3275                            return;
3276                         end if;
3277                      end if;
3278                   end if;
3279
3280                   Next (Decl);
3281                end loop;
3282             end if;
3283
3284             --  Give message if needed if we fall through those tests
3285
3286             if Err then
3287                Error_Pragma_Arg
3288                  ("at most one Convention/Export/Import pragma is allowed",
3289                   Arg2);
3290             end if;
3291          end Diagnose_Multiple_Pragmas;
3292
3293          --------------------------------
3294          -- Set_Convention_From_Pragma --
3295          --------------------------------
3296
3297          procedure Set_Convention_From_Pragma (E : Entity_Id) is
3298          begin
3299             --  Ada 2005 (AI-430): Check invalid attempt to change convention
3300             --  for an overridden dispatching operation. Technically this is
3301             --  an amendment and should only be done in Ada 2005 mode. However,
3302             --  this is clearly a mistake, since the problem that is addressed
3303             --  by this AI is that there is a clear gap in the RM!
3304
3305             if Is_Dispatching_Operation (E)
3306               and then Present (Overridden_Operation (E))
3307               and then C /= Convention (Overridden_Operation (E))
3308             then
3309                Error_Pragma_Arg
3310                  ("cannot change convention for " &
3311                   "overridden dispatching operation",
3312                   Arg1);
3313             end if;
3314
3315             --  Set the convention
3316
3317             Set_Convention (E, C);
3318             Set_Has_Convention_Pragma (E);
3319
3320             if Is_Incomplete_Or_Private_Type (E)
3321               and then Present (Underlying_Type (E))
3322             then
3323                Set_Convention            (Underlying_Type (E), C);
3324                Set_Has_Convention_Pragma (Underlying_Type (E), True);
3325             end if;
3326
3327             --  A class-wide type should inherit the convention of the specific
3328             --  root type (although this isn't specified clearly by the RM).
3329
3330             if Is_Type (E) and then Present (Class_Wide_Type (E)) then
3331                Set_Convention (Class_Wide_Type (E), C);
3332             end if;
3333
3334             --  If the entity is a record type, then check for special case of
3335             --  C_Pass_By_Copy, which is treated the same as C except that the
3336             --  special record flag is set. This convention is only permitted
3337             --  on record types (see AI95-00131).
3338
3339             if Cname = Name_C_Pass_By_Copy then
3340                if Is_Record_Type (E) then
3341                   Set_C_Pass_By_Copy (Base_Type (E));
3342                elsif Is_Incomplete_Or_Private_Type (E)
3343                  and then Is_Record_Type (Underlying_Type (E))
3344                then
3345                   Set_C_Pass_By_Copy (Base_Type (Underlying_Type (E)));
3346                else
3347                   Error_Pragma_Arg
3348                     ("C_Pass_By_Copy convention allowed only for record type",
3349                      Arg2);
3350                end if;
3351             end if;
3352
3353             --  If the entity is a derived boolean type, check for the special
3354             --  case of convention C, C++, or Fortran, where we consider any
3355             --  nonzero value to represent true.
3356
3357             if Is_Discrete_Type (E)
3358               and then Root_Type (Etype (E)) = Standard_Boolean
3359               and then
3360                 (C = Convention_C
3361                    or else
3362                  C = Convention_CPP
3363                    or else
3364                  C = Convention_Fortran)
3365             then
3366                Set_Nonzero_Is_True (Base_Type (E));
3367             end if;
3368          end Set_Convention_From_Pragma;
3369
3370       --  Start of processing for Process_Convention
3371
3372       begin
3373          Check_At_Least_N_Arguments (2);
3374          Check_Optional_Identifier (Arg1, Name_Convention);
3375          Check_Arg_Is_Identifier (Arg1);
3376          Cname := Chars (Get_Pragma_Arg (Arg1));
3377
3378          --  C_Pass_By_Copy is treated as a synonym for convention C (this is
3379          --  tested again below to set the critical flag).
3380
3381          if Cname = Name_C_Pass_By_Copy then
3382             C := Convention_C;
3383
3384          --  Otherwise we must have something in the standard convention list
3385
3386          elsif Is_Convention_Name (Cname) then
3387             C := Get_Convention_Id (Chars (Get_Pragma_Arg (Arg1)));
3388
3389          --  In DEC VMS, it seems that there is an undocumented feature that
3390          --  any unrecognized convention is treated as the default, which for
3391          --  us is convention C. It does not seem so terrible to do this
3392          --  unconditionally, silently in the VMS case, and with a warning
3393          --  in the non-VMS case.
3394
3395          else
3396             if Warn_On_Export_Import and not OpenVMS_On_Target then
3397                Error_Msg_N
3398                  ("?unrecognized convention name, C assumed",
3399                   Get_Pragma_Arg (Arg1));
3400             end if;
3401
3402             C := Convention_C;
3403          end if;
3404
3405          Check_Optional_Identifier (Arg2, Name_Entity);
3406          Check_Arg_Is_Local_Name (Arg2);
3407
3408          Id := Get_Pragma_Arg (Arg2);
3409          Analyze (Id);
3410
3411          if not Is_Entity_Name (Id) then
3412             Error_Pragma_Arg ("entity name required", Arg2);
3413          end if;
3414
3415          E := Entity (Id);
3416
3417          --  Set entity to return
3418
3419          Ent := E;
3420
3421          --  Ada_Pass_By_Copy special checking
3422
3423          if C = Convention_Ada_Pass_By_Copy then
3424             if not Is_First_Subtype (E) then
3425                Error_Pragma_Arg
3426                  ("convention `Ada_Pass_By_Copy` only "
3427                   & "allowed for types", Arg2);
3428             end if;
3429
3430             if Is_By_Reference_Type (E) then
3431                Error_Pragma_Arg
3432                  ("convention `Ada_Pass_By_Copy` not allowed for "
3433                   & "by-reference type", Arg1);
3434             end if;
3435          end if;
3436
3437          --  Ada_Pass_By_Reference special checking
3438
3439          if C = Convention_Ada_Pass_By_Reference then
3440             if not Is_First_Subtype (E) then
3441                Error_Pragma_Arg
3442                  ("convention `Ada_Pass_By_Reference` only "
3443                   & "allowed for types", Arg2);
3444             end if;
3445
3446             if Is_By_Copy_Type (E) then
3447                Error_Pragma_Arg
3448                  ("convention `Ada_Pass_By_Reference` not allowed for "
3449                   & "by-copy type", Arg1);
3450             end if;
3451          end if;
3452
3453          --  Go to renamed subprogram if present, since convention applies to
3454          --  the actual renamed entity, not to the renaming entity. If the
3455          --  subprogram is inherited, go to parent subprogram.
3456
3457          if Is_Subprogram (E)
3458            and then Present (Alias (E))
3459          then
3460             if Nkind (Parent (Declaration_Node (E))) =
3461                                        N_Subprogram_Renaming_Declaration
3462             then
3463                if Scope (E) /= Scope (Alias (E)) then
3464                   Error_Pragma_Ref
3465                     ("cannot apply pragma% to non-local entity&#", E);
3466                end if;
3467
3468                E := Alias (E);
3469
3470             elsif Nkind_In (Parent (E), N_Full_Type_Declaration,
3471                                         N_Private_Extension_Declaration)
3472               and then Scope (E) = Scope (Alias (E))
3473             then
3474                E := Alias (E);
3475
3476                --  Return the parent subprogram the entity was inherited from
3477
3478                Ent := E;
3479             end if;
3480          end if;
3481
3482          --  Check that we are not applying this to a specless body
3483
3484          if Is_Subprogram (E)
3485            and then Nkind (Parent (Declaration_Node (E))) = N_Subprogram_Body
3486          then
3487             Error_Pragma
3488               ("pragma% requires separate spec and must come before body");
3489          end if;
3490
3491          --  Check that we are not applying this to a named constant
3492
3493          if Ekind_In (E, E_Named_Integer, E_Named_Real) then
3494             Error_Msg_Name_1 := Pname;
3495             Error_Msg_N
3496               ("cannot apply pragma% to named constant!",
3497                Get_Pragma_Arg (Arg2));
3498             Error_Pragma_Arg
3499               ("\supply appropriate type for&!", Arg2);
3500          end if;
3501
3502          if Ekind (E) = E_Enumeration_Literal then
3503             Error_Pragma ("enumeration literal not allowed for pragma%");
3504          end if;
3505
3506          --  Check for rep item appearing too early or too late
3507
3508          if Etype (E) = Any_Type
3509            or else Rep_Item_Too_Early (E, N)
3510          then
3511             raise Pragma_Exit;
3512
3513          elsif Present (Underlying_Type (E)) then
3514             E := Underlying_Type (E);
3515          end if;
3516
3517          if Rep_Item_Too_Late (E, N) then
3518             raise Pragma_Exit;
3519          end if;
3520
3521          if Has_Convention_Pragma (E) then
3522             Diagnose_Multiple_Pragmas (E);
3523
3524          elsif Convention (E) = Convention_Protected
3525            or else Ekind (Scope (E)) = E_Protected_Type
3526          then
3527             Error_Pragma_Arg
3528               ("a protected operation cannot be given a different convention",
3529                 Arg2);
3530          end if;
3531
3532          --  For Intrinsic, a subprogram is required
3533
3534          if C = Convention_Intrinsic
3535            and then not Is_Subprogram (E)
3536            and then not Is_Generic_Subprogram (E)
3537          then
3538             Error_Pragma_Arg
3539               ("second argument of pragma% must be a subprogram", Arg2);
3540          end if;
3541
3542          --  Stdcall case
3543
3544          if C = Convention_Stdcall then
3545
3546             --  A dispatching call is not allowed. A dispatching subprogram
3547             --  cannot be used to interface to the Win32 API, so in fact this
3548             --  check does not impose any effective restriction.
3549
3550             if Is_Dispatching_Operation (E) then
3551
3552                Error_Pragma
3553                  ("dispatching subprograms cannot use Stdcall convention");
3554
3555             --  Subprogram is allowed, but not a generic subprogram, and not a
3556             --  dispatching operation.
3557
3558             elsif not Is_Subprogram (E)
3559               and then not Is_Generic_Subprogram (E)
3560
3561               --  A variable is OK
3562
3563               and then Ekind (E) /= E_Variable
3564
3565               --  An access to subprogram is also allowed
3566
3567               and then not
3568                 (Is_Access_Type (E)
3569                   and then Ekind (Designated_Type (E)) = E_Subprogram_Type)
3570             then
3571                Error_Pragma_Arg
3572                  ("second argument of pragma% must be subprogram (type)",
3573                   Arg2);
3574             end if;
3575          end if;
3576
3577          if not Is_Subprogram (E)
3578            and then not Is_Generic_Subprogram (E)
3579          then
3580             Set_Convention_From_Pragma (E);
3581
3582             if Is_Type (E) then
3583                Check_First_Subtype (Arg2);
3584                Set_Convention_From_Pragma (Base_Type (E));
3585
3586                --  For subprograms, we must set the convention on the
3587                --  internally generated directly designated type as well.
3588
3589                if Ekind (E) = E_Access_Subprogram_Type then
3590                   Set_Convention_From_Pragma (Directly_Designated_Type (E));
3591                end if;
3592             end if;
3593
3594          --  For the subprogram case, set proper convention for all homonyms
3595          --  in same scope and the same declarative part, i.e. the same
3596          --  compilation unit.
3597
3598          else
3599             Comp_Unit := Get_Source_Unit (E);
3600             Set_Convention_From_Pragma (E);
3601
3602             --  Treat a pragma Import as an implicit body, for GPS use
3603
3604             if Prag_Id = Pragma_Import then
3605                Generate_Reference (E, Id, 'b');
3606             end if;
3607
3608             --  Loop through the homonyms of the pragma argument's entity
3609
3610             E1 := Ent;
3611             loop
3612                E1 := Homonym (E1);
3613                exit when No (E1) or else Scope (E1) /= Current_Scope;
3614
3615                --  Do not set the pragma on inherited operations or on formal
3616                --  subprograms.
3617
3618                if Comes_From_Source (E1)
3619                  and then Comp_Unit = Get_Source_Unit (E1)
3620                  and then not Is_Formal_Subprogram (E1)
3621                  and then Nkind (Original_Node (Parent (E1))) /=
3622                                                     N_Full_Type_Declaration
3623                then
3624                   if Present (Alias (E1))
3625                     and then Scope (E1) /= Scope (Alias (E1))
3626                   then
3627                      Error_Pragma_Ref
3628                        ("cannot apply pragma% to non-local entity& declared#",
3629                         E1);
3630                   end if;
3631
3632                   Set_Convention_From_Pragma (E1);
3633
3634                   if Prag_Id = Pragma_Import then
3635                      Generate_Reference (E1, Id, 'b');
3636                   end if;
3637                end if;
3638
3639                --  For aspect case, do NOT apply to homonyms
3640
3641                exit when From_Aspect_Specification (N);
3642             end loop;
3643          end if;
3644       end Process_Convention;
3645
3646       ----------------------------------------
3647       -- Process_Disable_Enable_Atomic_Sync --
3648       ----------------------------------------
3649
3650       procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id) is
3651       begin
3652          GNAT_Pragma;
3653          Check_No_Identifiers;
3654          Check_At_Most_N_Arguments (1);
3655
3656          --  Modeled internally as
3657          --    pragma Unsuppress (Atomic_Synchronization [,Entity])
3658
3659          Rewrite (N,
3660            Make_Pragma (Loc,
3661              Pragma_Identifier            =>
3662                Make_Identifier (Loc, Nam),
3663              Pragma_Argument_Associations => New_List (
3664                Make_Pragma_Argument_Association (Loc,
3665                  Expression =>
3666                    Make_Identifier (Loc, Name_Atomic_Synchronization)))));
3667
3668          if Present (Arg1) then
3669             Append_To (Pragma_Argument_Associations (N), New_Copy (Arg1));
3670          end if;
3671
3672          Analyze (N);
3673       end Process_Disable_Enable_Atomic_Sync;
3674
3675       -----------------------------------------------------
3676       -- Process_Extended_Import_Export_Exception_Pragma --
3677       -----------------------------------------------------
3678
3679       procedure Process_Extended_Import_Export_Exception_Pragma
3680         (Arg_Internal : Node_Id;
3681          Arg_External : Node_Id;
3682          Arg_Form     : Node_Id;
3683          Arg_Code     : Node_Id)
3684       is
3685          Def_Id   : Entity_Id;
3686          Code_Val : Uint;
3687
3688       begin
3689          if not OpenVMS_On_Target then
3690             Error_Pragma
3691               ("?pragma% ignored (applies only to Open'V'M'S)");
3692          end if;
3693
3694          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3695          Def_Id := Entity (Arg_Internal);
3696
3697          if Ekind (Def_Id) /= E_Exception then
3698             Error_Pragma_Arg
3699               ("pragma% must refer to declared exception", Arg_Internal);
3700          end if;
3701
3702          Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
3703
3704          if Present (Arg_Form) then
3705             Check_Arg_Is_One_Of (Arg_Form, Name_Ada, Name_VMS);
3706          end if;
3707
3708          if Present (Arg_Form)
3709            and then Chars (Arg_Form) = Name_Ada
3710          then
3711             null;
3712          else
3713             Set_Is_VMS_Exception (Def_Id);
3714             Set_Exception_Code (Def_Id, No_Uint);
3715          end if;
3716
3717          if Present (Arg_Code) then
3718             if not Is_VMS_Exception (Def_Id) then
3719                Error_Pragma_Arg
3720                  ("Code option for pragma% not allowed for Ada case",
3721                   Arg_Code);
3722             end if;
3723
3724             Check_Arg_Is_Static_Expression (Arg_Code, Any_Integer);
3725             Code_Val := Expr_Value (Arg_Code);
3726
3727             if not UI_Is_In_Int_Range (Code_Val) then
3728                Error_Pragma_Arg
3729                  ("Code option for pragma% must be in 32-bit range",
3730                   Arg_Code);
3731
3732             else
3733                Set_Exception_Code (Def_Id, Code_Val);
3734             end if;
3735          end if;
3736       end Process_Extended_Import_Export_Exception_Pragma;
3737
3738       -------------------------------------------------
3739       -- Process_Extended_Import_Export_Internal_Arg --
3740       -------------------------------------------------
3741
3742       procedure Process_Extended_Import_Export_Internal_Arg
3743         (Arg_Internal : Node_Id := Empty)
3744       is
3745       begin
3746          if No (Arg_Internal) then
3747             Error_Pragma ("Internal parameter required for pragma%");
3748          end if;
3749
3750          if Nkind (Arg_Internal) = N_Identifier then
3751             null;
3752
3753          elsif Nkind (Arg_Internal) = N_Operator_Symbol
3754            and then (Prag_Id = Pragma_Import_Function
3755                        or else
3756                      Prag_Id = Pragma_Export_Function)
3757          then
3758             null;
3759
3760          else
3761             Error_Pragma_Arg
3762               ("wrong form for Internal parameter for pragma%", Arg_Internal);
3763          end if;
3764
3765          Check_Arg_Is_Local_Name (Arg_Internal);
3766       end Process_Extended_Import_Export_Internal_Arg;
3767
3768       --------------------------------------------------
3769       -- Process_Extended_Import_Export_Object_Pragma --
3770       --------------------------------------------------
3771
3772       procedure Process_Extended_Import_Export_Object_Pragma
3773         (Arg_Internal : Node_Id;
3774          Arg_External : Node_Id;
3775          Arg_Size     : Node_Id)
3776       is
3777          Def_Id : Entity_Id;
3778
3779       begin
3780          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3781          Def_Id := Entity (Arg_Internal);
3782
3783          if not Ekind_In (Def_Id, E_Constant, E_Variable) then
3784             Error_Pragma_Arg
3785               ("pragma% must designate an object", Arg_Internal);
3786          end if;
3787
3788          if Has_Rep_Pragma (Def_Id, Name_Common_Object)
3789               or else
3790             Has_Rep_Pragma (Def_Id, Name_Psect_Object)
3791          then
3792             Error_Pragma_Arg
3793               ("previous Common/Psect_Object applies, pragma % not permitted",
3794                Arg_Internal);
3795          end if;
3796
3797          if Rep_Item_Too_Late (Def_Id, N) then
3798             raise Pragma_Exit;
3799          end if;
3800
3801          Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
3802
3803          if Present (Arg_Size) then
3804             Check_Arg_Is_External_Name (Arg_Size);
3805          end if;
3806
3807          --  Export_Object case
3808
3809          if Prag_Id = Pragma_Export_Object then
3810             if not Is_Library_Level_Entity (Def_Id) then
3811                Error_Pragma_Arg
3812                  ("argument for pragma% must be library level entity",
3813                   Arg_Internal);
3814             end if;
3815
3816             if Ekind (Current_Scope) = E_Generic_Package then
3817                Error_Pragma ("pragma& cannot appear in a generic unit");
3818             end if;
3819
3820             if not Size_Known_At_Compile_Time (Etype (Def_Id)) then
3821                Error_Pragma_Arg
3822                  ("exported object must have compile time known size",
3823                   Arg_Internal);
3824             end if;
3825
3826             if Warn_On_Export_Import and then Is_Exported (Def_Id) then
3827                Error_Msg_N ("?duplicate Export_Object pragma", N);
3828             else
3829                Set_Exported (Def_Id, Arg_Internal);
3830             end if;
3831
3832          --  Import_Object case
3833
3834          else
3835             if Is_Concurrent_Type (Etype (Def_Id)) then
3836                Error_Pragma_Arg
3837                  ("cannot use pragma% for task/protected object",
3838                   Arg_Internal);
3839             end if;
3840
3841             if Ekind (Def_Id) = E_Constant then
3842                Error_Pragma_Arg
3843                  ("cannot import a constant", Arg_Internal);
3844             end if;
3845
3846             if Warn_On_Export_Import
3847               and then Has_Discriminants (Etype (Def_Id))
3848             then
3849                Error_Msg_N
3850                  ("imported value must be initialized?", Arg_Internal);
3851             end if;
3852
3853             if Warn_On_Export_Import
3854               and then Is_Access_Type (Etype (Def_Id))
3855             then
3856                Error_Pragma_Arg
3857                  ("cannot import object of an access type?", Arg_Internal);
3858             end if;
3859
3860             if Warn_On_Export_Import
3861               and then Is_Imported (Def_Id)
3862             then
3863                Error_Msg_N
3864                  ("?duplicate Import_Object pragma", N);
3865
3866             --  Check for explicit initialization present. Note that an
3867             --  initialization generated by the code generator, e.g. for an
3868             --  access type, does not count here.
3869
3870             elsif Present (Expression (Parent (Def_Id)))
3871                and then
3872                  Comes_From_Source
3873                    (Original_Node (Expression (Parent (Def_Id))))
3874             then
3875                Error_Msg_Sloc := Sloc (Def_Id);
3876                Error_Pragma_Arg
3877                  ("imported entities cannot be initialized (RM B.1(24))",
3878                   "\no initialization allowed for & declared#", Arg1);
3879             else
3880                Set_Imported (Def_Id);
3881                Note_Possible_Modification (Arg_Internal, Sure => False);
3882             end if;
3883          end if;
3884       end Process_Extended_Import_Export_Object_Pragma;
3885
3886       ------------------------------------------------------
3887       -- Process_Extended_Import_Export_Subprogram_Pragma --
3888       ------------------------------------------------------
3889
3890       procedure Process_Extended_Import_Export_Subprogram_Pragma
3891         (Arg_Internal                 : Node_Id;
3892          Arg_External                 : Node_Id;
3893          Arg_Parameter_Types          : Node_Id;
3894          Arg_Result_Type              : Node_Id := Empty;
3895          Arg_Mechanism                : Node_Id;
3896          Arg_Result_Mechanism         : Node_Id := Empty;
3897          Arg_First_Optional_Parameter : Node_Id := Empty)
3898       is
3899          Ent       : Entity_Id;
3900          Def_Id    : Entity_Id;
3901          Hom_Id    : Entity_Id;
3902          Formal    : Entity_Id;
3903          Ambiguous : Boolean;
3904          Match     : Boolean;
3905          Dval      : Node_Id;
3906
3907          function Same_Base_Type
3908           (Ptype  : Node_Id;
3909            Formal : Entity_Id) return Boolean;
3910          --  Determines if Ptype references the type of Formal. Note that only
3911          --  the base types need to match according to the spec. Ptype here is
3912          --  the argument from the pragma, which is either a type name, or an
3913          --  access attribute.
3914
3915          --------------------
3916          -- Same_Base_Type --
3917          --------------------
3918
3919          function Same_Base_Type
3920            (Ptype  : Node_Id;
3921             Formal : Entity_Id) return Boolean
3922          is
3923             Ftyp : constant Entity_Id := Base_Type (Etype (Formal));
3924             Pref : Node_Id;
3925
3926          begin
3927             --  Case where pragma argument is typ'Access
3928
3929             if Nkind (Ptype) = N_Attribute_Reference
3930               and then Attribute_Name (Ptype) = Name_Access
3931             then
3932                Pref := Prefix (Ptype);
3933                Find_Type (Pref);
3934
3935                if not Is_Entity_Name (Pref)
3936                  or else Entity (Pref) = Any_Type
3937                then
3938                   raise Pragma_Exit;
3939                end if;
3940
3941                --  We have a match if the corresponding argument is of an
3942                --  anonymous access type, and its designated type matches the
3943                --  type of the prefix of the access attribute
3944
3945                return Ekind (Ftyp) = E_Anonymous_Access_Type
3946                  and then Base_Type (Entity (Pref)) =
3947                             Base_Type (Etype (Designated_Type (Ftyp)));
3948
3949             --  Case where pragma argument is a type name
3950
3951             else
3952                Find_Type (Ptype);
3953
3954                if not Is_Entity_Name (Ptype)
3955                  or else Entity (Ptype) = Any_Type
3956                then
3957                   raise Pragma_Exit;
3958                end if;
3959
3960                --  We have a match if the corresponding argument is of the type
3961                --  given in the pragma (comparing base types)
3962
3963                return Base_Type (Entity (Ptype)) = Ftyp;
3964             end if;
3965          end Same_Base_Type;
3966
3967       --  Start of processing for
3968       --  Process_Extended_Import_Export_Subprogram_Pragma
3969
3970       begin
3971          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3972          Ent := Empty;
3973          Ambiguous := False;
3974
3975          --  Loop through homonyms (overloadings) of the entity
3976
3977          Hom_Id := Entity (Arg_Internal);
3978          while Present (Hom_Id) loop
3979             Def_Id := Get_Base_Subprogram (Hom_Id);
3980
3981             --  We need a subprogram in the current scope
3982
3983             if not Is_Subprogram (Def_Id)
3984               or else Scope (Def_Id) /= Current_Scope
3985             then
3986                null;
3987
3988             else
3989                Match := True;
3990
3991                --  Pragma cannot apply to subprogram body
3992
3993                if Is_Subprogram (Def_Id)
3994                  and then Nkind (Parent (Declaration_Node (Def_Id))) =
3995                                                              N_Subprogram_Body
3996                then
3997                   Error_Pragma
3998                     ("pragma% requires separate spec"
3999                       & " and must come before body");
4000                end if;
4001
4002                --  Test result type if given, note that the result type
4003                --  parameter can only be present for the function cases.
4004
4005                if Present (Arg_Result_Type)
4006                  and then not Same_Base_Type (Arg_Result_Type, Def_Id)
4007                then
4008                   Match := False;
4009
4010                elsif Etype (Def_Id) /= Standard_Void_Type
4011                  and then
4012                    (Pname = Name_Export_Procedure
4013                       or else
4014                     Pname = Name_Import_Procedure)
4015                then
4016                   Match := False;
4017
4018                --  Test parameter types if given. Note that this parameter
4019                --  has not been analyzed (and must not be, since it is
4020                --  semantic nonsense), so we get it as the parser left it.
4021
4022                elsif Present (Arg_Parameter_Types) then
4023                   Check_Matching_Types : declare
4024                      Formal : Entity_Id;
4025                      Ptype  : Node_Id;
4026
4027                   begin
4028                      Formal := First_Formal (Def_Id);
4029
4030                      if Nkind (Arg_Parameter_Types) = N_Null then
4031                         if Present (Formal) then
4032                            Match := False;
4033                         end if;
4034
4035                      --  A list of one type, e.g. (List) is parsed as
4036                      --  a parenthesized expression.
4037
4038                      elsif Nkind (Arg_Parameter_Types) /= N_Aggregate
4039                        and then Paren_Count (Arg_Parameter_Types) = 1
4040                      then
4041                         if No (Formal)
4042                           or else Present (Next_Formal (Formal))
4043                         then
4044                            Match := False;
4045                         else
4046                            Match :=
4047                              Same_Base_Type (Arg_Parameter_Types, Formal);
4048                         end if;
4049
4050                      --  A list of more than one type is parsed as a aggregate
4051
4052                      elsif Nkind (Arg_Parameter_Types) = N_Aggregate
4053                        and then Paren_Count (Arg_Parameter_Types) = 0
4054                      then
4055                         Ptype := First (Expressions (Arg_Parameter_Types));
4056                         while Present (Ptype) or else Present (Formal) loop
4057                            if No (Ptype)
4058                              or else No (Formal)
4059                              or else not Same_Base_Type (Ptype, Formal)
4060                            then
4061                               Match := False;
4062                               exit;
4063                            else
4064                               Next_Formal (Formal);
4065                               Next (Ptype);
4066                            end if;
4067                         end loop;
4068
4069                      --  Anything else is of the wrong form
4070
4071                      else
4072                         Error_Pragma_Arg
4073                           ("wrong form for Parameter_Types parameter",
4074                            Arg_Parameter_Types);
4075                      end if;
4076                   end Check_Matching_Types;
4077                end if;
4078
4079                --  Match is now False if the entry we found did not match
4080                --  either a supplied Parameter_Types or Result_Types argument
4081
4082                if Match then
4083                   if No (Ent) then
4084                      Ent := Def_Id;
4085
4086                   --  Ambiguous case, the flag Ambiguous shows if we already
4087                   --  detected this and output the initial messages.
4088
4089                   else
4090                      if not Ambiguous then
4091                         Ambiguous := True;
4092                         Error_Msg_Name_1 := Pname;
4093                         Error_Msg_N
4094                           ("pragma% does not uniquely identify subprogram!",
4095                            N);
4096                         Error_Msg_Sloc := Sloc (Ent);
4097                         Error_Msg_N ("matching subprogram #!", N);
4098                         Ent := Empty;
4099                      end if;
4100
4101                      Error_Msg_Sloc := Sloc (Def_Id);
4102                      Error_Msg_N ("matching subprogram #!", N);
4103                   end if;
4104                end if;
4105             end if;
4106
4107             Hom_Id := Homonym (Hom_Id);
4108          end loop;
4109
4110          --  See if we found an entry
4111
4112          if No (Ent) then
4113             if not Ambiguous then
4114                if Is_Generic_Subprogram (Entity (Arg_Internal)) then
4115                   Error_Pragma
4116                     ("pragma% cannot be given for generic subprogram");
4117                else
4118                   Error_Pragma
4119                     ("pragma% does not identify local subprogram");
4120                end if;
4121             end if;
4122
4123             return;
4124          end if;
4125
4126          --  Import pragmas must be for imported entities
4127
4128          if Prag_Id = Pragma_Import_Function
4129               or else
4130             Prag_Id = Pragma_Import_Procedure
4131               or else
4132             Prag_Id = Pragma_Import_Valued_Procedure
4133          then
4134             if not Is_Imported (Ent) then
4135                Error_Pragma
4136                  ("pragma Import or Interface must precede pragma%");
4137             end if;
4138
4139          --  Here we have the Export case which can set the entity as exported
4140
4141          --  But does not do so if the specified external name is null, since
4142          --  that is taken as a signal in DEC Ada 83 (with which we want to be
4143          --  compatible) to request no external name.
4144
4145          elsif Nkind (Arg_External) = N_String_Literal
4146            and then String_Length (Strval (Arg_External)) = 0
4147          then
4148             null;
4149
4150          --  In all other cases, set entity as exported
4151
4152          else
4153             Set_Exported (Ent, Arg_Internal);
4154          end if;
4155
4156          --  Special processing for Valued_Procedure cases
4157
4158          if Prag_Id = Pragma_Import_Valued_Procedure
4159            or else
4160             Prag_Id = Pragma_Export_Valued_Procedure
4161          then
4162             Formal := First_Formal (Ent);
4163
4164             if No (Formal) then
4165                Error_Pragma ("at least one parameter required for pragma%");
4166
4167             elsif Ekind (Formal) /= E_Out_Parameter then
4168                Error_Pragma ("first parameter must have mode out for pragma%");
4169
4170             else
4171                Set_Is_Valued_Procedure (Ent);
4172             end if;
4173          end if;
4174
4175          Set_Extended_Import_Export_External_Name (Ent, Arg_External);
4176
4177          --  Process Result_Mechanism argument if present. We have already
4178          --  checked that this is only allowed for the function case.
4179
4180          if Present (Arg_Result_Mechanism) then
4181             Set_Mechanism_Value (Ent, Arg_Result_Mechanism);
4182          end if;
4183
4184          --  Process Mechanism parameter if present. Note that this parameter
4185          --  is not analyzed, and must not be analyzed since it is semantic
4186          --  nonsense, so we get it in exactly as the parser left it.
4187
4188          if Present (Arg_Mechanism) then
4189             declare
4190                Formal : Entity_Id;
4191                Massoc : Node_Id;
4192                Mname  : Node_Id;
4193                Choice : Node_Id;
4194
4195             begin
4196                --  A single mechanism association without a formal parameter
4197                --  name is parsed as a parenthesized expression. All other
4198                --  cases are parsed as aggregates, so we rewrite the single
4199                --  parameter case as an aggregate for consistency.
4200
4201                if Nkind (Arg_Mechanism) /= N_Aggregate
4202                  and then Paren_Count (Arg_Mechanism) = 1
4203                then
4204                   Rewrite (Arg_Mechanism,
4205                     Make_Aggregate (Sloc (Arg_Mechanism),
4206                       Expressions => New_List (
4207                         Relocate_Node (Arg_Mechanism))));
4208                end if;
4209
4210                --  Case of only mechanism name given, applies to all formals
4211
4212                if Nkind (Arg_Mechanism) /= N_Aggregate then
4213                   Formal := First_Formal (Ent);
4214                   while Present (Formal) loop
4215                      Set_Mechanism_Value (Formal, Arg_Mechanism);
4216                      Next_Formal (Formal);
4217                   end loop;
4218
4219                --  Case of list of mechanism associations given
4220
4221                else
4222                   if Null_Record_Present (Arg_Mechanism) then
4223                      Error_Pragma_Arg
4224                        ("inappropriate form for Mechanism parameter",
4225                         Arg_Mechanism);
4226                   end if;
4227
4228                   --  Deal with positional ones first
4229
4230                   Formal := First_Formal (Ent);
4231
4232                   if Present (Expressions (Arg_Mechanism)) then
4233                      Mname := First (Expressions (Arg_Mechanism));
4234                      while Present (Mname) loop
4235                         if No (Formal) then
4236                            Error_Pragma_Arg
4237                              ("too many mechanism associations", Mname);
4238                         end if;
4239
4240                         Set_Mechanism_Value (Formal, Mname);
4241                         Next_Formal (Formal);
4242                         Next (Mname);
4243                      end loop;
4244                   end if;
4245
4246                   --  Deal with named entries
4247
4248                   if Present (Component_Associations (Arg_Mechanism)) then
4249                      Massoc := First (Component_Associations (Arg_Mechanism));
4250                      while Present (Massoc) loop
4251                         Choice := First (Choices (Massoc));
4252
4253                         if Nkind (Choice) /= N_Identifier
4254                           or else Present (Next (Choice))
4255                         then
4256                            Error_Pragma_Arg
4257                              ("incorrect form for mechanism association",
4258                               Massoc);
4259                         end if;
4260
4261                         Formal := First_Formal (Ent);
4262                         loop
4263                            if No (Formal) then
4264                               Error_Pragma_Arg
4265                                 ("parameter name & not present", Choice);
4266                            end if;
4267
4268                            if Chars (Choice) = Chars (Formal) then
4269                               Set_Mechanism_Value
4270                                 (Formal, Expression (Massoc));
4271
4272                               --  Set entity on identifier (needed by ASIS)
4273
4274                               Set_Entity (Choice, Formal);
4275
4276                               exit;
4277                            end if;
4278
4279                            Next_Formal (Formal);
4280                         end loop;
4281
4282                         Next (Massoc);
4283                      end loop;
4284                   end if;
4285                end if;
4286             end;
4287          end if;
4288
4289          --  Process First_Optional_Parameter argument if present. We have
4290          --  already checked that this is only allowed for the Import case.
4291
4292          if Present (Arg_First_Optional_Parameter) then
4293             if Nkind (Arg_First_Optional_Parameter) /= N_Identifier then
4294                Error_Pragma_Arg
4295                  ("first optional parameter must be formal parameter name",
4296                   Arg_First_Optional_Parameter);
4297             end if;
4298
4299             Formal := First_Formal (Ent);
4300             loop
4301                if No (Formal) then
4302                   Error_Pragma_Arg
4303                     ("specified formal parameter& not found",
4304                      Arg_First_Optional_Parameter);
4305                end if;
4306
4307                exit when Chars (Formal) =
4308                          Chars (Arg_First_Optional_Parameter);
4309
4310                Next_Formal (Formal);
4311             end loop;
4312
4313             Set_First_Optional_Parameter (Ent, Formal);
4314
4315             --  Check specified and all remaining formals have right form
4316
4317             while Present (Formal) loop
4318                if Ekind (Formal) /= E_In_Parameter then
4319                   Error_Msg_NE
4320                     ("optional formal& is not of mode in!",
4321                      Arg_First_Optional_Parameter, Formal);
4322
4323                else
4324                   Dval := Default_Value (Formal);
4325
4326                   if No (Dval) then
4327                      Error_Msg_NE
4328                        ("optional formal& does not have default value!",
4329                         Arg_First_Optional_Parameter, Formal);
4330
4331                   elsif Compile_Time_Known_Value_Or_Aggr (Dval) then
4332                      null;
4333
4334                   else
4335                      Error_Msg_FE
4336                        ("default value for optional formal& is non-static!",
4337                         Arg_First_Optional_Parameter, Formal);
4338                   end if;
4339                end if;
4340
4341                Set_Is_Optional_Parameter (Formal);
4342                Next_Formal (Formal);
4343             end loop;
4344          end if;
4345       end Process_Extended_Import_Export_Subprogram_Pragma;
4346
4347       --------------------------
4348       -- Process_Generic_List --
4349       --------------------------
4350
4351       procedure Process_Generic_List is
4352          Arg : Node_Id;
4353          Exp : Node_Id;
4354
4355       begin
4356          Check_No_Identifiers;
4357          Check_At_Least_N_Arguments (1);
4358
4359          Arg := Arg1;
4360          while Present (Arg) loop
4361             Exp := Get_Pragma_Arg (Arg);
4362             Analyze (Exp);
4363
4364             if not Is_Entity_Name (Exp)
4365               or else
4366                 (not Is_Generic_Instance (Entity (Exp))
4367                   and then
4368                  not Is_Generic_Unit (Entity (Exp)))
4369             then
4370                Error_Pragma_Arg
4371                  ("pragma% argument must be name of generic unit/instance",
4372                   Arg);
4373             end if;
4374
4375             Next (Arg);
4376          end loop;
4377       end Process_Generic_List;
4378
4379       ------------------------------------
4380       -- Process_Import_Predefined_Type --
4381       ------------------------------------
4382
4383       procedure Process_Import_Predefined_Type is
4384          Loc  : constant Source_Ptr := Sloc (N);
4385          Elmt : Elmt_Id;
4386          Ftyp : Node_Id := Empty;
4387          Decl : Node_Id;
4388          Def  : Node_Id;
4389          Nam  : Name_Id;
4390
4391       begin
4392          String_To_Name_Buffer (Strval (Expression (Arg3)));
4393          Nam := Name_Find;
4394
4395          Elmt := First_Elmt (Predefined_Float_Types);
4396          while Present (Elmt) and then Chars (Node (Elmt)) /= Nam loop
4397             Next_Elmt (Elmt);
4398          end loop;
4399
4400          Ftyp := Node (Elmt);
4401
4402          if Present (Ftyp) then
4403
4404             --  Don't build a derived type declaration, because predefined C
4405             --  types have no declaration anywhere, so cannot really be named.
4406             --  Instead build a full type declaration, starting with an
4407             --  appropriate type definition is built
4408
4409             if Is_Floating_Point_Type (Ftyp) then
4410                Def := Make_Floating_Point_Definition (Loc,
4411                  Make_Integer_Literal (Loc, Digits_Value (Ftyp)),
4412                  Make_Real_Range_Specification (Loc,
4413                    Make_Real_Literal (Loc, Realval (Type_Low_Bound (Ftyp))),
4414                    Make_Real_Literal (Loc, Realval (Type_High_Bound (Ftyp)))));
4415
4416             --  Should never have a predefined type we cannot handle
4417
4418             else
4419                raise Program_Error;
4420             end if;
4421
4422             --  Build and insert a Full_Type_Declaration, which will be
4423             --  analyzed as soon as this list entry has been analyzed.
4424
4425             Decl := Make_Full_Type_Declaration (Loc,
4426               Make_Defining_Identifier (Loc, Chars (Expression (Arg2))),
4427               Type_Definition => Def);
4428
4429             Insert_After (N, Decl);
4430             Mark_Rewrite_Insertion (Decl);
4431
4432          else
4433             Error_Pragma_Arg ("no matching type found for pragma%",
4434             Arg2);
4435          end if;
4436       end Process_Import_Predefined_Type;
4437
4438       ---------------------------------
4439       -- Process_Import_Or_Interface --
4440       ---------------------------------
4441
4442       procedure Process_Import_Or_Interface is
4443          C      : Convention_Id;
4444          Def_Id : Entity_Id;
4445          Hom_Id : Entity_Id;
4446
4447       begin
4448          Process_Convention (C, Def_Id);
4449          Kill_Size_Check_Code (Def_Id);
4450          Note_Possible_Modification (Get_Pragma_Arg (Arg2), Sure => False);
4451
4452          if Ekind_In (Def_Id, E_Variable, E_Constant) then
4453
4454             --  We do not permit Import to apply to a renaming declaration
4455
4456             if Present (Renamed_Object (Def_Id)) then
4457                Error_Pragma_Arg
4458                  ("pragma% not allowed for object renaming", Arg2);
4459
4460             --  User initialization is not allowed for imported object, but
4461             --  the object declaration may contain a default initialization,
4462             --  that will be discarded. Note that an explicit initialization
4463             --  only counts if it comes from source, otherwise it is simply
4464             --  the code generator making an implicit initialization explicit.
4465
4466             elsif Present (Expression (Parent (Def_Id)))
4467               and then Comes_From_Source (Expression (Parent (Def_Id)))
4468             then
4469                Error_Msg_Sloc := Sloc (Def_Id);
4470                Error_Pragma_Arg
4471                  ("no initialization allowed for declaration of& #",
4472                   "\imported entities cannot be initialized (RM B.1(24))",
4473                   Arg2);
4474
4475             else
4476                Set_Imported (Def_Id);
4477                Process_Interface_Name (Def_Id, Arg3, Arg4);
4478
4479                --  Note that we do not set Is_Public here. That's because we
4480                --  only want to set it if there is no address clause, and we
4481                --  don't know that yet, so we delay that processing till
4482                --  freeze time.
4483
4484                --  pragma Import completes deferred constants
4485
4486                if Ekind (Def_Id) = E_Constant then
4487                   Set_Has_Completion (Def_Id);
4488                end if;
4489
4490                --  It is not possible to import a constant of an unconstrained
4491                --  array type (e.g. string) because there is no simple way to
4492                --  write a meaningful subtype for it.
4493
4494                if Is_Array_Type (Etype (Def_Id))
4495                  and then not Is_Constrained (Etype (Def_Id))
4496                then
4497                   Error_Msg_NE
4498                     ("imported constant& must have a constrained subtype",
4499                       N, Def_Id);
4500                end if;
4501             end if;
4502
4503          elsif Is_Subprogram (Def_Id)
4504            or else Is_Generic_Subprogram (Def_Id)
4505          then
4506             --  If the name is overloaded, pragma applies to all of the denoted
4507             --  entities in the same declarative part.
4508
4509             Hom_Id := Def_Id;
4510             while Present (Hom_Id) loop
4511                Def_Id := Get_Base_Subprogram (Hom_Id);
4512
4513                --  Ignore inherited subprograms because the pragma will apply
4514                --  to the parent operation, which is the one called.
4515
4516                if Is_Overloadable (Def_Id)
4517                  and then Present (Alias (Def_Id))
4518                then
4519                   null;
4520
4521                --  If it is not a subprogram, it must be in an outer scope and
4522                --  pragma does not apply.
4523
4524                elsif not Is_Subprogram (Def_Id)
4525                  and then not Is_Generic_Subprogram (Def_Id)
4526                then
4527                   null;
4528
4529                --  The pragma does not apply to primitives of interfaces
4530
4531                elsif Is_Dispatching_Operation (Def_Id)
4532                  and then Present (Find_Dispatching_Type (Def_Id))
4533                  and then Is_Interface (Find_Dispatching_Type (Def_Id))
4534                then
4535                   null;
4536
4537                --  Verify that the homonym is in the same declarative part (not
4538                --  just the same scope).
4539
4540                elsif Parent (Unit_Declaration_Node (Def_Id)) /= Parent (N)
4541                  and then Nkind (Parent (N)) /= N_Compilation_Unit_Aux
4542                then
4543                   exit;
4544
4545                else
4546                   Set_Imported (Def_Id);
4547
4548                   --  Reject an Import applied to an abstract subprogram
4549
4550                   if Is_Subprogram (Def_Id)
4551                     and then Is_Abstract_Subprogram (Def_Id)
4552                   then
4553                      Error_Msg_Sloc := Sloc (Def_Id);
4554                      Error_Msg_NE
4555                        ("cannot import abstract subprogram& declared#",
4556                         Arg2, Def_Id);
4557                   end if;
4558
4559                   --  Special processing for Convention_Intrinsic
4560
4561                   if C = Convention_Intrinsic then
4562
4563                      --  Link_Name argument not allowed for intrinsic
4564
4565                      Check_No_Link_Name;
4566
4567                      Set_Is_Intrinsic_Subprogram (Def_Id);
4568
4569                      --  If no external name is present, then check that this
4570                      --  is a valid intrinsic subprogram. If an external name
4571                      --  is present, then this is handled by the back end.
4572
4573                      if No (Arg3) then
4574                         Check_Intrinsic_Subprogram
4575                           (Def_Id, Get_Pragma_Arg (Arg2));
4576                      end if;
4577                   end if;
4578
4579                   --  All interfaced procedures need an external symbol created
4580                   --  for them since they are always referenced from another
4581                   --  object file.
4582
4583                   Set_Is_Public (Def_Id);
4584
4585                   --  Verify that the subprogram does not have a completion
4586                   --  through a renaming declaration. For other completions the
4587                   --  pragma appears as a too late representation.
4588
4589                   declare
4590                      Decl : constant Node_Id := Unit_Declaration_Node (Def_Id);
4591
4592                   begin
4593                      if Present (Decl)
4594                        and then Nkind (Decl) = N_Subprogram_Declaration
4595                        and then Present (Corresponding_Body (Decl))
4596                        and then Nkind (Unit_Declaration_Node
4597                                         (Corresponding_Body (Decl))) =
4598                                              N_Subprogram_Renaming_Declaration
4599                      then
4600                         Error_Msg_Sloc := Sloc (Def_Id);
4601                         Error_Msg_NE
4602                           ("cannot import&, renaming already provided for " &
4603                            "declaration #", N, Def_Id);
4604                      end if;
4605                   end;
4606
4607                   Set_Has_Completion (Def_Id);
4608                   Process_Interface_Name (Def_Id, Arg3, Arg4);
4609                end if;
4610
4611                if Is_Compilation_Unit (Hom_Id) then
4612
4613                   --  Its possible homonyms are not affected by the pragma.
4614                   --  Such homonyms might be present in the context of other
4615                   --  units being compiled.
4616
4617                   exit;
4618
4619                else
4620                   Hom_Id := Homonym (Hom_Id);
4621                end if;
4622             end loop;
4623
4624          --  When the convention is Java or CIL, we also allow Import to be
4625          --  given for packages, generic packages, exceptions, record
4626          --  components, and access to subprograms.
4627
4628          elsif (C = Convention_Java or else C = Convention_CIL)
4629            and then
4630              (Is_Package_Or_Generic_Package (Def_Id)
4631                or else Ekind (Def_Id) = E_Exception
4632                or else Ekind (Def_Id) = E_Access_Subprogram_Type
4633                or else Nkind (Parent (Def_Id)) = N_Component_Declaration)
4634          then
4635             Set_Imported (Def_Id);
4636             Set_Is_Public (Def_Id);
4637             Process_Interface_Name (Def_Id, Arg3, Arg4);
4638
4639          --  Import a CPP class
4640
4641          elsif C = Convention_CPP
4642            and then (Is_Record_Type (Def_Id)
4643                       or else Ekind (Def_Id) = E_Incomplete_Type)
4644          then
4645             if Ekind (Def_Id) = E_Incomplete_Type then
4646                if Present (Full_View (Def_Id)) then
4647                   Def_Id := Full_View (Def_Id);
4648
4649                else
4650                   Error_Msg_N
4651                     ("cannot import 'C'P'P type before full declaration seen",
4652                      Get_Pragma_Arg (Arg2));
4653
4654                   --  Although we have reported the error we decorate it as
4655                   --  CPP_Class to avoid reporting spurious errors
4656
4657                   Set_Is_CPP_Class (Def_Id);
4658                   return;
4659                end if;
4660             end if;
4661
4662             --  Types treated as CPP classes must be declared limited (note:
4663             --  this used to be a warning but there is no real benefit to it
4664             --  since we did effectively intend to treat the type as limited
4665             --  anyway).
4666
4667             if not Is_Limited_Type (Def_Id) then
4668                Error_Msg_N
4669                  ("imported 'C'P'P type must be limited",
4670                   Get_Pragma_Arg (Arg2));
4671             end if;
4672
4673             Set_Is_CPP_Class (Def_Id);
4674
4675             --  Imported CPP types must not have discriminants (because C++
4676             --  classes do not have discriminants).
4677
4678             if Has_Discriminants (Def_Id) then
4679                Error_Msg_N
4680                  ("imported 'C'P'P type cannot have discriminants",
4681                   First (Discriminant_Specifications
4682                           (Declaration_Node (Def_Id))));
4683             end if;
4684
4685             --  Check that components of imported CPP types do not have default
4686             --  expressions. For private types this check is performed when the
4687             --  full view is analyzed (see Process_Full_View).
4688
4689             if not Is_Private_Type (Def_Id) then
4690                Check_CPP_Type_Has_No_Defaults (Def_Id);
4691             end if;
4692
4693          elsif Nkind (Parent (Def_Id)) = N_Incomplete_Type_Declaration then
4694             Check_No_Link_Name;
4695             Check_Arg_Count (3);
4696             Check_Arg_Is_Static_Expression (Arg3, Standard_String);
4697
4698             Process_Import_Predefined_Type;
4699
4700          else
4701             Error_Pragma_Arg
4702               ("second argument of pragma% must be object, subprogram "
4703                & "or incomplete type",
4704                Arg2);
4705          end if;
4706
4707          --  If this pragma applies to a compilation unit, then the unit, which
4708          --  is a subprogram, does not require (or allow) a body. We also do
4709          --  not need to elaborate imported procedures.
4710
4711          if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
4712             declare
4713                Cunit : constant Node_Id := Parent (Parent (N));
4714             begin
4715                Set_Body_Required (Cunit, False);
4716             end;
4717          end if;
4718       end Process_Import_Or_Interface;
4719
4720       --------------------
4721       -- Process_Inline --
4722       --------------------
4723
4724       procedure Process_Inline (Active : Boolean) is
4725          Assoc     : Node_Id;
4726          Decl      : Node_Id;
4727          Subp_Id   : Node_Id;
4728          Subp      : Entity_Id;
4729          Applies   : Boolean;
4730
4731          Effective : Boolean := False;
4732          --  Set True if inline has some effect, i.e. if there is at least one
4733          --  subprogram set as inlined as a result of the use of the pragma.
4734
4735          procedure Make_Inline (Subp : Entity_Id);
4736          --  Subp is the defining unit name of the subprogram declaration. Set
4737          --  the flag, as well as the flag in the corresponding body, if there
4738          --  is one present.
4739
4740          procedure Set_Inline_Flags (Subp : Entity_Id);
4741          --  Sets Is_Inlined and Has_Pragma_Inline flags for Subp and also
4742          --  Has_Pragma_Inline_Always for the Inline_Always case.
4743
4744          function Inlining_Not_Possible (Subp : Entity_Id) return Boolean;
4745          --  Returns True if it can be determined at this stage that inlining
4746          --  is not possible, for example if the body is available and contains
4747          --  exception handlers, we prevent inlining, since otherwise we can
4748          --  get undefined symbols at link time. This function also emits a
4749          --  warning if front-end inlining is enabled and the pragma appears
4750          --  too late.
4751          --
4752          --  ??? is business with link symbols still valid, or does it relate
4753          --  to front end ZCX which is being phased out ???
4754
4755          ---------------------------
4756          -- Inlining_Not_Possible --
4757          ---------------------------
4758
4759          function Inlining_Not_Possible (Subp : Entity_Id) return Boolean is
4760             Decl  : constant Node_Id := Unit_Declaration_Node (Subp);
4761             Stats : Node_Id;
4762
4763          begin
4764             if Nkind (Decl) = N_Subprogram_Body then
4765                Stats := Handled_Statement_Sequence (Decl);
4766                return Present (Exception_Handlers (Stats))
4767                  or else Present (At_End_Proc (Stats));
4768
4769             elsif Nkind (Decl) = N_Subprogram_Declaration
4770               and then Present (Corresponding_Body (Decl))
4771             then
4772                if Front_End_Inlining
4773                  and then Analyzed (Corresponding_Body (Decl))
4774                then
4775                   Error_Msg_N ("pragma appears too late, ignored?", N);
4776                   return True;
4777
4778                --  If the subprogram is a renaming as body, the body is just a
4779                --  call to the renamed subprogram, and inlining is trivially
4780                --  possible.
4781
4782                elsif
4783                  Nkind (Unit_Declaration_Node (Corresponding_Body (Decl))) =
4784                                              N_Subprogram_Renaming_Declaration
4785                then
4786                   return False;
4787
4788                else
4789                   Stats :=
4790                     Handled_Statement_Sequence
4791                         (Unit_Declaration_Node (Corresponding_Body (Decl)));
4792
4793                   return
4794                     Present (Exception_Handlers (Stats))
4795                       or else Present (At_End_Proc (Stats));
4796                end if;
4797
4798             else
4799                --  If body is not available, assume the best, the check is
4800                --  performed again when compiling enclosing package bodies.
4801
4802                return False;
4803             end if;
4804          end Inlining_Not_Possible;
4805
4806          -----------------
4807          -- Make_Inline --
4808          -----------------
4809
4810          procedure Make_Inline (Subp : Entity_Id) is
4811             Kind       : constant Entity_Kind := Ekind (Subp);
4812             Inner_Subp : Entity_Id   := Subp;
4813
4814          begin
4815             --  Ignore if bad type, avoid cascaded error
4816
4817             if Etype (Subp) = Any_Type then
4818                Applies := True;
4819                return;
4820
4821             --  Ignore if all inlining is suppressed
4822
4823             elsif Suppress_All_Inlining then
4824                Applies := True;
4825                return;
4826
4827             --  If inlining is not possible, for now do not treat as an error
4828
4829             elsif Inlining_Not_Possible (Subp) then
4830                Applies := True;
4831                return;
4832
4833             --  Here we have a candidate for inlining, but we must exclude
4834             --  derived operations. Otherwise we would end up trying to inline
4835             --  a phantom declaration, and the result would be to drag in a
4836             --  body which has no direct inlining associated with it. That
4837             --  would not only be inefficient but would also result in the
4838             --  backend doing cross-unit inlining in cases where it was
4839             --  definitely inappropriate to do so.
4840
4841             --  However, a simple Comes_From_Source test is insufficient, since
4842             --  we do want to allow inlining of generic instances which also do
4843             --  not come from source. We also need to recognize specs generated
4844             --  by the front-end for bodies that carry the pragma. Finally,
4845             --  predefined operators do not come from source but are not
4846             --  inlineable either.
4847
4848             elsif Is_Generic_Instance (Subp)
4849               or else Nkind (Parent (Parent (Subp))) = N_Subprogram_Declaration
4850             then
4851                null;
4852
4853             elsif not Comes_From_Source (Subp)
4854               and then Scope (Subp) /= Standard_Standard
4855             then
4856                Applies := True;
4857                return;
4858             end if;
4859
4860             --  The referenced entity must either be the enclosing entity, or
4861             --  an entity declared within the current open scope.
4862
4863             if Present (Scope (Subp))
4864               and then Scope (Subp) /= Current_Scope
4865               and then Subp /= Current_Scope
4866             then
4867                Error_Pragma_Arg
4868                  ("argument of% must be entity in current scope", Assoc);
4869                return;
4870             end if;
4871
4872             --  Processing for procedure, operator or function. If subprogram
4873             --  is aliased (as for an instance) indicate that the renamed
4874             --  entity (if declared in the same unit) is inlined.
4875
4876             if Is_Subprogram (Subp) then
4877                Inner_Subp := Ultimate_Alias (Inner_Subp);
4878
4879                if In_Same_Source_Unit (Subp, Inner_Subp) then
4880                   Set_Inline_Flags (Inner_Subp);
4881
4882                   Decl := Parent (Parent (Inner_Subp));
4883
4884                   if Nkind (Decl) = N_Subprogram_Declaration
4885                     and then Present (Corresponding_Body (Decl))
4886                   then
4887                      Set_Inline_Flags (Corresponding_Body (Decl));
4888
4889                   elsif Is_Generic_Instance (Subp) then
4890
4891                      --  Indicate that the body needs to be created for
4892                      --  inlining subsequent calls. The instantiation node
4893                      --  follows the declaration of the wrapper package
4894                      --  created for it.
4895
4896                      if Scope (Subp) /= Standard_Standard
4897                        and then
4898                          Need_Subprogram_Instance_Body
4899                           (Next (Unit_Declaration_Node (Scope (Alias (Subp)))),
4900                               Subp)
4901                      then
4902                         null;
4903                      end if;
4904
4905                   --  Inline is a program unit pragma (RM 10.1.5) and cannot
4906                   --  appear in a formal part to apply to a formal subprogram.
4907                   --  Do not apply check within an instance or a formal package
4908                   --  the test will have been applied to the original generic.
4909
4910                   elsif Nkind (Decl) in N_Formal_Subprogram_Declaration
4911                     and then List_Containing (Decl) = List_Containing (N)
4912                     and then not In_Instance
4913                   then
4914                      Error_Msg_N
4915                        ("Inline cannot apply to a formal subprogram", N);
4916                   end if;
4917                end if;
4918
4919                Applies := True;
4920
4921             --  For a generic subprogram set flag as well, for use at the point
4922             --  of instantiation, to determine whether the body should be
4923             --  generated.
4924
4925             elsif Is_Generic_Subprogram (Subp) then
4926                Set_Inline_Flags (Subp);
4927                Applies := True;
4928
4929             --  Literals are by definition inlined
4930
4931             elsif Kind = E_Enumeration_Literal then
4932                null;
4933
4934             --  Anything else is an error
4935
4936             else
4937                Error_Pragma_Arg
4938                  ("expect subprogram name for pragma%", Assoc);
4939             end if;
4940          end Make_Inline;
4941
4942          ----------------------
4943          -- Set_Inline_Flags --
4944          ----------------------
4945
4946          procedure Set_Inline_Flags (Subp : Entity_Id) is
4947          begin
4948             if Active then
4949                Set_Is_Inlined (Subp);
4950             end if;
4951
4952             if not Has_Pragma_Inline (Subp) then
4953                Set_Has_Pragma_Inline (Subp);
4954                Effective := True;
4955             end if;
4956
4957             if Prag_Id = Pragma_Inline_Always then
4958                Set_Has_Pragma_Inline_Always (Subp);
4959             end if;
4960          end Set_Inline_Flags;
4961
4962       --  Start of processing for Process_Inline
4963
4964       begin
4965          Check_No_Identifiers;
4966          Check_At_Least_N_Arguments (1);
4967
4968          if Active then
4969             Inline_Processing_Required := True;
4970          end if;
4971
4972          Assoc := Arg1;
4973          while Present (Assoc) loop
4974             Subp_Id := Get_Pragma_Arg (Assoc);
4975             Analyze (Subp_Id);
4976             Applies := False;
4977
4978             if Is_Entity_Name (Subp_Id) then
4979                Subp := Entity (Subp_Id);
4980
4981                if Subp = Any_Id then
4982
4983                   --  If previous error, avoid cascaded errors
4984
4985                   Applies := True;
4986                   Effective := True;
4987
4988                else
4989                   Make_Inline (Subp);
4990
4991                   --  For the pragma case, climb homonym chain. This is
4992                   --  what implements allowing the pragma in the renaming
4993                   --  case, with the result applying to the ancestors, and
4994                   --  also allows Inline to apply to all previous homonyms.
4995
4996                   if not From_Aspect_Specification (N) then
4997                      while Present (Homonym (Subp))
4998                        and then Scope (Homonym (Subp)) = Current_Scope
4999                      loop
5000                         Make_Inline (Homonym (Subp));
5001                         Subp := Homonym (Subp);
5002                      end loop;
5003                   end if;
5004                end if;
5005             end if;
5006
5007             if not Applies then
5008                Error_Pragma_Arg
5009                  ("inappropriate argument for pragma%", Assoc);
5010
5011             elsif not Effective
5012               and then Warn_On_Redundant_Constructs
5013               and then not Suppress_All_Inlining
5014             then
5015                if Inlining_Not_Possible (Subp) then
5016                   Error_Msg_NE
5017                     ("pragma Inline for& is ignored?", N, Entity (Subp_Id));
5018                else
5019                   Error_Msg_NE
5020                     ("pragma Inline for& is redundant?", N, Entity (Subp_Id));
5021                end if;
5022             end if;
5023
5024             Next (Assoc);
5025          end loop;
5026       end Process_Inline;
5027
5028       ----------------------------
5029       -- Process_Interface_Name --
5030       ----------------------------
5031
5032       procedure Process_Interface_Name
5033         (Subprogram_Def : Entity_Id;
5034          Ext_Arg        : Node_Id;
5035          Link_Arg       : Node_Id)
5036       is
5037          Ext_Nam    : Node_Id;
5038          Link_Nam   : Node_Id;
5039          String_Val : String_Id;
5040
5041          procedure Check_Form_Of_Interface_Name
5042            (SN            : Node_Id;
5043             Ext_Name_Case : Boolean);
5044          --  SN is a string literal node for an interface name. This routine
5045          --  performs some minimal checks that the name is reasonable. In
5046          --  particular that no spaces or other obviously incorrect characters
5047          --  appear. This is only a warning, since any characters are allowed.
5048          --  Ext_Name_Case is True for an External_Name, False for a Link_Name.
5049
5050          ----------------------------------
5051          -- Check_Form_Of_Interface_Name --
5052          ----------------------------------
5053
5054          procedure Check_Form_Of_Interface_Name
5055            (SN            : Node_Id;
5056             Ext_Name_Case : Boolean)
5057          is
5058             S  : constant String_Id := Strval (Expr_Value_S (SN));
5059             SL : constant Nat       := String_Length (S);
5060             C  : Char_Code;
5061
5062          begin
5063             if SL = 0 then
5064                Error_Msg_N ("interface name cannot be null string", SN);
5065             end if;
5066
5067             for J in 1 .. SL loop
5068                C := Get_String_Char (S, J);
5069
5070                --  Look for dubious character and issue unconditional warning.
5071                --  Definitely dubious if not in character range.
5072
5073                if not In_Character_Range (C)
5074
5075                   --  For all cases except CLI target,
5076                   --  commas, spaces and slashes are dubious (in CLI, we use
5077                   --  commas and backslashes in external names to specify
5078                   --  assembly version and public key, while slashes and spaces
5079                   --  can be used in names to mark nested classes and
5080                   --  valuetypes).
5081
5082                   or else ((not Ext_Name_Case or else VM_Target /= CLI_Target)
5083                              and then (Get_Character (C) = ','
5084                                          or else
5085                                        Get_Character (C) = '\'))
5086                  or else (VM_Target /= CLI_Target
5087                             and then (Get_Character (C) = ' '
5088                                         or else
5089                                       Get_Character (C) = '/'))
5090                then
5091                   Error_Msg
5092                     ("?interface name contains illegal character",
5093                      Sloc (SN) + Source_Ptr (J));
5094                end if;
5095             end loop;
5096          end Check_Form_Of_Interface_Name;
5097
5098       --  Start of processing for Process_Interface_Name
5099
5100       begin
5101          if No (Link_Arg) then
5102             if No (Ext_Arg) then
5103                if VM_Target = CLI_Target
5104                  and then Ekind (Subprogram_Def) = E_Package
5105                  and then Nkind (Parent (Subprogram_Def)) =
5106                                                  N_Package_Specification
5107                  and then Present (Generic_Parent (Parent (Subprogram_Def)))
5108                then
5109                   Set_Interface_Name
5110                      (Subprogram_Def,
5111                       Interface_Name
5112                         (Generic_Parent (Parent (Subprogram_Def))));
5113                end if;
5114
5115                return;
5116
5117             elsif Chars (Ext_Arg) = Name_Link_Name then
5118                Ext_Nam  := Empty;
5119                Link_Nam := Expression (Ext_Arg);
5120
5121             else
5122                Check_Optional_Identifier (Ext_Arg, Name_External_Name);
5123                Ext_Nam  := Expression (Ext_Arg);
5124                Link_Nam := Empty;
5125             end if;
5126
5127          else
5128             Check_Optional_Identifier (Ext_Arg,  Name_External_Name);
5129             Check_Optional_Identifier (Link_Arg, Name_Link_Name);
5130             Ext_Nam  := Expression (Ext_Arg);
5131             Link_Nam := Expression (Link_Arg);
5132          end if;
5133
5134          --  Check expressions for external name and link name are static
5135
5136          if Present (Ext_Nam) then
5137             Check_Arg_Is_Static_Expression (Ext_Nam, Standard_String);
5138             Check_Form_Of_Interface_Name (Ext_Nam, Ext_Name_Case => True);
5139
5140             --  Verify that external name is not the name of a local entity,
5141             --  which would hide the imported one and could lead to run-time
5142             --  surprises. The problem can only arise for entities declared in
5143             --  a package body (otherwise the external name is fully qualified
5144             --  and will not conflict).
5145
5146             declare
5147                Nam : Name_Id;
5148                E   : Entity_Id;
5149                Par : Node_Id;
5150
5151             begin
5152                if Prag_Id = Pragma_Import then
5153                   String_To_Name_Buffer (Strval (Expr_Value_S (Ext_Nam)));
5154                   Nam := Name_Find;
5155                   E   := Entity_Id (Get_Name_Table_Info (Nam));
5156
5157                   if Nam /= Chars (Subprogram_Def)
5158                     and then Present (E)
5159                     and then not Is_Overloadable (E)
5160                     and then Is_Immediately_Visible (E)
5161                     and then not Is_Imported (E)
5162                     and then Ekind (Scope (E)) = E_Package
5163                   then
5164                      Par := Parent (E);
5165                      while Present (Par) loop
5166                         if Nkind (Par) = N_Package_Body then
5167                            Error_Msg_Sloc := Sloc (E);
5168                            Error_Msg_NE
5169                              ("imported entity is hidden by & declared#",
5170                               Ext_Arg, E);
5171                            exit;
5172                         end if;
5173
5174                         Par := Parent (Par);
5175                      end loop;
5176                   end if;
5177                end if;
5178             end;
5179          end if;
5180
5181          if Present (Link_Nam) then
5182             Check_Arg_Is_Static_Expression (Link_Nam, Standard_String);
5183             Check_Form_Of_Interface_Name (Link_Nam, Ext_Name_Case => False);
5184          end if;
5185
5186          --  If there is no link name, just set the external name
5187
5188          if No (Link_Nam) then
5189             Link_Nam := Adjust_External_Name_Case (Expr_Value_S (Ext_Nam));
5190
5191          --  For the Link_Name case, the given literal is preceded by an
5192          --  asterisk, which indicates to GCC that the given name should be
5193          --  taken literally, and in particular that no prepending of
5194          --  underlines should occur, even in systems where this is the
5195          --  normal default.
5196
5197          else
5198             Start_String;
5199
5200             if VM_Target = No_VM then
5201                Store_String_Char (Get_Char_Code ('*'));
5202             end if;
5203
5204             String_Val := Strval (Expr_Value_S (Link_Nam));
5205             Store_String_Chars (String_Val);
5206             Link_Nam :=
5207               Make_String_Literal (Sloc (Link_Nam),
5208                 Strval => End_String);
5209          end if;
5210
5211          --  Set the interface name. If the entity is a generic instance, use
5212          --  its alias, which is the callable entity.
5213
5214          if Is_Generic_Instance (Subprogram_Def) then
5215             Set_Encoded_Interface_Name
5216               (Alias (Get_Base_Subprogram (Subprogram_Def)), Link_Nam);
5217          else
5218             Set_Encoded_Interface_Name
5219               (Get_Base_Subprogram (Subprogram_Def), Link_Nam);
5220          end if;
5221
5222          --  We allow duplicated export names in CIL/Java, as they are always
5223          --  enclosed in a namespace that differentiates them, and overloaded
5224          --  entities are supported by the VM.
5225
5226          if Convention (Subprogram_Def) /= Convention_CIL
5227               and then
5228             Convention (Subprogram_Def) /= Convention_Java
5229          then
5230             Check_Duplicated_Export_Name (Link_Nam);
5231          end if;
5232       end Process_Interface_Name;
5233
5234       -----------------------------------------
5235       -- Process_Interrupt_Or_Attach_Handler --
5236       -----------------------------------------
5237
5238       procedure Process_Interrupt_Or_Attach_Handler is
5239          Arg1_X       : constant Node_Id   := Get_Pragma_Arg (Arg1);
5240          Handler_Proc : constant Entity_Id := Entity (Arg1_X);
5241          Proc_Scope   : constant Entity_Id := Scope (Handler_Proc);
5242
5243       begin
5244          Set_Is_Interrupt_Handler (Handler_Proc);
5245
5246          --  If the pragma is not associated with a handler procedure within a
5247          --  protected type, then it must be for a nonprotected procedure for
5248          --  the AAMP target, in which case we don't associate a representation
5249          --  item with the procedure's scope.
5250
5251          if Ekind (Proc_Scope) = E_Protected_Type then
5252             if Prag_Id = Pragma_Interrupt_Handler
5253                  or else
5254                Prag_Id = Pragma_Attach_Handler
5255             then
5256                Record_Rep_Item (Proc_Scope, N);
5257             end if;
5258          end if;
5259       end Process_Interrupt_Or_Attach_Handler;
5260
5261       --------------------------------------------------
5262       -- Process_Restrictions_Or_Restriction_Warnings --
5263       --------------------------------------------------
5264
5265       --  Note: some of the simple identifier cases were handled in par-prag,
5266       --  but it is harmless (and more straightforward) to simply handle all
5267       --  cases here, even if it means we repeat a bit of work in some cases.
5268
5269       procedure Process_Restrictions_Or_Restriction_Warnings
5270         (Warn : Boolean)
5271       is
5272          Arg   : Node_Id;
5273          R_Id  : Restriction_Id;
5274          Id    : Name_Id;
5275          Expr  : Node_Id;
5276          Val   : Uint;
5277
5278          procedure Check_Unit_Name (N : Node_Id);
5279          --  Checks unit name parameter for No_Dependence. Returns if it has
5280          --  an appropriate form, otherwise raises pragma argument error.
5281
5282          ---------------------
5283          -- Check_Unit_Name --
5284          ---------------------
5285
5286          procedure Check_Unit_Name (N : Node_Id) is
5287          begin
5288             if Nkind (N) = N_Selected_Component then
5289                Check_Unit_Name (Prefix (N));
5290                Check_Unit_Name (Selector_Name (N));
5291
5292             elsif Nkind (N) = N_Identifier then
5293                return;
5294
5295             else
5296                Error_Pragma_Arg
5297                  ("wrong form for unit name for No_Dependence", N);
5298             end if;
5299          end Check_Unit_Name;
5300
5301       --  Start of processing for Process_Restrictions_Or_Restriction_Warnings
5302
5303       begin
5304          --  Ignore all Restrictions pragma in CodePeer mode
5305
5306          if CodePeer_Mode then
5307             return;
5308          end if;
5309
5310          Check_Ada_83_Warning;
5311          Check_At_Least_N_Arguments (1);
5312          Check_Valid_Configuration_Pragma;
5313
5314          Arg := Arg1;
5315          while Present (Arg) loop
5316             Id := Chars (Arg);
5317             Expr := Get_Pragma_Arg (Arg);
5318
5319             --  Case of no restriction identifier present
5320
5321             if Id = No_Name then
5322                if Nkind (Expr) /= N_Identifier then
5323                   Error_Pragma_Arg
5324                     ("invalid form for restriction", Arg);
5325                end if;
5326
5327                R_Id :=
5328                  Get_Restriction_Id
5329                    (Process_Restriction_Synonyms (Expr));
5330
5331                if R_Id not in All_Boolean_Restrictions then
5332                   Error_Msg_Name_1 := Pname;
5333                   Error_Msg_N
5334                     ("invalid restriction identifier&", Get_Pragma_Arg (Arg));
5335
5336                   --  Check for possible misspelling
5337
5338                   for J in Restriction_Id loop
5339                      declare
5340                         Rnm : constant String := Restriction_Id'Image (J);
5341
5342                      begin
5343                         Name_Buffer (1 .. Rnm'Length) := Rnm;
5344                         Name_Len := Rnm'Length;
5345                         Set_Casing (All_Lower_Case);
5346
5347                         if Is_Bad_Spelling_Of (Chars (Expr), Name_Enter) then
5348                            Set_Casing
5349                              (Identifier_Casing (Current_Source_File));
5350                            Error_Msg_String (1 .. Rnm'Length) :=
5351                              Name_Buffer (1 .. Name_Len);
5352                            Error_Msg_Strlen := Rnm'Length;
5353                            Error_Msg_N -- CODEFIX
5354                              ("\possible misspelling of ""~""",
5355                               Get_Pragma_Arg (Arg));
5356                            exit;
5357                         end if;
5358                      end;
5359                   end loop;
5360
5361                   raise Pragma_Exit;
5362                end if;
5363
5364                if Implementation_Restriction (R_Id) then
5365                   Check_Restriction (No_Implementation_Restrictions, Arg);
5366                end if;
5367
5368                --  Special processing for No_Elaboration_Code restriction
5369
5370                if R_Id = No_Elaboration_Code then
5371
5372                   --  Restriction is only recognized within a configuration
5373                   --  pragma file, or within a unit of the main extended
5374                   --  program. Note: the test for Main_Unit is needed to
5375                   --  properly include the case of configuration pragma files.
5376
5377                   if not (Current_Sem_Unit = Main_Unit
5378                            or else In_Extended_Main_Source_Unit (N))
5379                   then
5380                      return;
5381
5382                   --  Don't allow in a subunit unless already specified in
5383                   --  body or spec.
5384
5385                   elsif Nkind (Parent (N)) = N_Compilation_Unit
5386                     and then Nkind (Unit (Parent (N))) = N_Subunit
5387                     and then not Restriction_Active (No_Elaboration_Code)
5388                   then
5389                      Error_Msg_N
5390                        ("invalid specification of ""No_Elaboration_Code""",
5391                         N);
5392                      Error_Msg_N
5393                        ("\restriction cannot be specified in a subunit", N);
5394                      Error_Msg_N
5395                        ("\unless also specified in body or spec", N);
5396                      return;
5397
5398                   --  If we have a No_Elaboration_Code pragma that we
5399                   --  accept, then it needs to be added to the configuration
5400                   --  restrcition set so that we get proper application to
5401                   --  other units in the main extended source as required.
5402
5403                   else
5404                      Add_To_Config_Boolean_Restrictions (No_Elaboration_Code);
5405                   end if;
5406                end if;
5407
5408                --  If this is a warning, then set the warning unless we already
5409                --  have a real restriction active (we never want a warning to
5410                --  override a real restriction).
5411
5412                if Warn then
5413                   if not Restriction_Active (R_Id) then
5414                      Set_Restriction (R_Id, N);
5415                      Restriction_Warnings (R_Id) := True;
5416                   end if;
5417
5418                --  If real restriction case, then set it and make sure that the
5419                --  restriction warning flag is off, since a real restriction
5420                --  always overrides a warning.
5421
5422                else
5423                   Set_Restriction (R_Id, N);
5424                   Restriction_Warnings (R_Id) := False;
5425                end if;
5426
5427                --  Check for obsolescent restrictions in Ada 2005 mode
5428
5429                if not Warn
5430                  and then Ada_Version >= Ada_2005
5431                  and then (R_Id = No_Asynchronous_Control
5432                             or else
5433                            R_Id = No_Unchecked_Deallocation
5434                             or else
5435                            R_Id = No_Unchecked_Conversion)
5436                then
5437                   Check_Restriction (No_Obsolescent_Features, N);
5438                end if;
5439
5440                --  A very special case that must be processed here: pragma
5441                --  Restrictions (No_Exceptions) turns off all run-time
5442                --  checking. This is a bit dubious in terms of the formal
5443                --  language definition, but it is what is intended by RM
5444                --  H.4(12). Restriction_Warnings never affects generated code
5445                --  so this is done only in the real restriction case.
5446
5447                --  Atomic_Synchronization is not a real check, so it is not
5448                --  affected by this processing).
5449
5450                if R_Id = No_Exceptions and then not Warn then
5451                   for J in Scope_Suppress'Range loop
5452                      if J /= Atomic_Synchronization then
5453                         Scope_Suppress (J) := True;
5454                      end if;
5455                   end loop;
5456                end if;
5457
5458             --  Case of No_Dependence => unit-name. Note that the parser
5459             --  already made the necessary entry in the No_Dependence table.
5460
5461             elsif Id = Name_No_Dependence then
5462                Check_Unit_Name (Expr);
5463
5464             --  Case of No_Specification_Of_Aspect => Identifier.
5465
5466             elsif Id = Name_No_Specification_Of_Aspect then
5467                declare
5468                   A_Id : Aspect_Id;
5469
5470                begin
5471                   if Nkind (Expr) /= N_Identifier then
5472                      A_Id := No_Aspect;
5473                   else
5474                      A_Id := Get_Aspect_Id (Chars (Expr));
5475                   end if;
5476
5477                   if A_Id = No_Aspect then
5478                      Error_Pragma_Arg ("invalid restriction name", Arg);
5479                   else
5480                      Set_Restriction_No_Specification_Of_Aspect (Expr, Warn);
5481                   end if;
5482                end;
5483
5484             --  All other cases of restriction identifier present
5485
5486             else
5487                R_Id := Get_Restriction_Id (Process_Restriction_Synonyms (Arg));
5488                Analyze_And_Resolve (Expr, Any_Integer);
5489
5490                if R_Id not in All_Parameter_Restrictions then
5491                   Error_Pragma_Arg
5492                     ("invalid restriction parameter identifier", Arg);
5493
5494                elsif not Is_OK_Static_Expression (Expr) then
5495                   Flag_Non_Static_Expr
5496                     ("value must be static expression!", Expr);
5497                   raise Pragma_Exit;
5498
5499                elsif not Is_Integer_Type (Etype (Expr))
5500                  or else Expr_Value (Expr) < 0
5501                then
5502                   Error_Pragma_Arg
5503                     ("value must be non-negative integer", Arg);
5504                end if;
5505
5506                --  Restriction pragma is active
5507
5508                Val := Expr_Value (Expr);
5509
5510                if not UI_Is_In_Int_Range (Val) then
5511                   Error_Pragma_Arg
5512                     ("pragma ignored, value too large?", Arg);
5513                end if;
5514
5515                --  Warning case. If the real restriction is active, then we
5516                --  ignore the request, since warning never overrides a real
5517                --  restriction. Otherwise we set the proper warning. Note that
5518                --  this circuit sets the warning again if it is already set,
5519                --  which is what we want, since the constant may have changed.
5520
5521                if Warn then
5522                   if not Restriction_Active (R_Id) then
5523                      Set_Restriction
5524                        (R_Id, N, Integer (UI_To_Int (Val)));
5525                      Restriction_Warnings (R_Id) := True;
5526                   end if;
5527
5528                --  Real restriction case, set restriction and make sure warning
5529                --  flag is off since real restriction always overrides warning.
5530
5531                else
5532                   Set_Restriction (R_Id, N, Integer (UI_To_Int (Val)));
5533                   Restriction_Warnings (R_Id) := False;
5534                end if;
5535             end if;
5536
5537             Next (Arg);
5538          end loop;
5539       end Process_Restrictions_Or_Restriction_Warnings;
5540
5541       ---------------------------------
5542       -- Process_Suppress_Unsuppress --
5543       ---------------------------------
5544
5545       --  Note: this procedure makes entries in the check suppress data
5546       --  structures managed by Sem. See spec of package Sem for full
5547       --  details on how we handle recording of check suppression.
5548
5549       procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean) is
5550          C    : Check_Id;
5551          E_Id : Node_Id;
5552          E    : Entity_Id;
5553
5554          In_Package_Spec : constant Boolean :=
5555                              Is_Package_Or_Generic_Package (Current_Scope)
5556                                and then not In_Package_Body (Current_Scope);
5557
5558          procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id);
5559          --  Used to suppress a single check on the given entity
5560
5561          --------------------------------
5562          -- Suppress_Unsuppress_Echeck --
5563          --------------------------------
5564
5565          procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id) is
5566          begin
5567             --  Check for error of trying to set atomic synchronization for
5568             --  a non-atomic variable.
5569
5570             if C = Atomic_Synchronization
5571               and then not (Is_Atomic (E) or else Has_Atomic_Components (E))
5572             then
5573                Error_Msg_N
5574                  ("pragma & requires atomic type or variable",
5575                   Pragma_Identifier (Original_Node (N)));
5576             end if;
5577
5578             Set_Checks_May_Be_Suppressed (E);
5579
5580             if In_Package_Spec then
5581                Push_Global_Suppress_Stack_Entry
5582                  (Entity   => E,
5583                   Check    => C,
5584                   Suppress => Suppress_Case);
5585             else
5586                Push_Local_Suppress_Stack_Entry
5587                  (Entity   => E,
5588                   Check    => C,
5589                   Suppress => Suppress_Case);
5590             end if;
5591
5592             --  If this is a first subtype, and the base type is distinct,
5593             --  then also set the suppress flags on the base type.
5594
5595             if Is_First_Subtype (E)
5596               and then Etype (E) /= E
5597             then
5598                Suppress_Unsuppress_Echeck (Etype (E), C);
5599             end if;
5600          end Suppress_Unsuppress_Echeck;
5601
5602       --  Start of processing for Process_Suppress_Unsuppress
5603
5604       begin
5605          --  Ignore pragma Suppress/Unsuppress in CodePeer and Alfa modes on
5606          --  user code: we want to generate checks for analysis purposes, as
5607          --  set respectively by -gnatC and -gnatd.F
5608
5609          if (CodePeer_Mode or Alfa_Mode)
5610            and then Comes_From_Source (N)
5611          then
5612             return;
5613          end if;
5614
5615          --  Suppress/Unsuppress can appear as a configuration pragma, or in a
5616          --  declarative part or a package spec (RM 11.5(5)).
5617
5618          if not Is_Configuration_Pragma then
5619             Check_Is_In_Decl_Part_Or_Package_Spec;
5620          end if;
5621
5622          Check_At_Least_N_Arguments (1);
5623          Check_At_Most_N_Arguments (2);
5624          Check_No_Identifier (Arg1);
5625          Check_Arg_Is_Identifier (Arg1);
5626
5627          C := Get_Check_Id (Chars (Get_Pragma_Arg (Arg1)));
5628
5629          if C = No_Check_Id then
5630             Error_Pragma_Arg
5631               ("argument of pragma% is not valid check name", Arg1);
5632          end if;
5633
5634          if not Suppress_Case
5635            and then (C = All_Checks or else C = Overflow_Check)
5636          then
5637             Opt.Overflow_Checks_Unsuppressed := True;
5638          end if;
5639
5640          if Arg_Count = 1 then
5641
5642             --  Make an entry in the local scope suppress table. This is the
5643             --  table that directly shows the current value of the scope
5644             --  suppress check for any check id value.
5645
5646             if C = All_Checks then
5647
5648                --  For All_Checks, we set all specific predefined checks with
5649                --  the exception of Elaboration_Check, which is handled
5650                --  specially because of not wanting All_Checks to have the
5651                --  effect of deactivating static elaboration order processing.
5652                --  Atomic_Synchronization is also not affected, since this is
5653                --  not a real check.
5654
5655                for J in Scope_Suppress'Range loop
5656                   if J /= Elaboration_Check
5657                     and then J /= Atomic_Synchronization
5658                   then
5659                      Scope_Suppress (J) := Suppress_Case;
5660                   end if;
5661                end loop;
5662
5663             --  If not All_Checks, and predefined check, then set appropriate
5664             --  scope entry. Note that we will set Elaboration_Check if this
5665             --  is explicitly specified. Atomic_Synchronization is allowed
5666             --  only if internally generated and entity is atomic.
5667
5668             elsif C in Predefined_Check_Id
5669               and then (not Comes_From_Source (N)
5670                          or else C /= Atomic_Synchronization)
5671             then
5672                Scope_Suppress (C) := Suppress_Case;
5673             end if;
5674
5675             --  Also make an entry in the Local_Entity_Suppress table
5676
5677             Push_Local_Suppress_Stack_Entry
5678               (Entity   => Empty,
5679                Check    => C,
5680                Suppress => Suppress_Case);
5681
5682          --  Case of two arguments present, where the check is suppressed for
5683          --  a specified entity (given as the second argument of the pragma)
5684
5685          else
5686             --  This is obsolescent in Ada 2005 mode
5687
5688             if Ada_Version >= Ada_2005 then
5689                Check_Restriction (No_Obsolescent_Features, Arg2);
5690             end if;
5691
5692             Check_Optional_Identifier (Arg2, Name_On);
5693             E_Id := Get_Pragma_Arg (Arg2);
5694             Analyze (E_Id);
5695
5696             if not Is_Entity_Name (E_Id) then
5697                Error_Pragma_Arg
5698                  ("second argument of pragma% must be entity name", Arg2);
5699             end if;
5700
5701             E := Entity (E_Id);
5702
5703             if E = Any_Id then
5704                return;
5705             end if;
5706
5707             --  Enforce RM 11.5(7) which requires that for a pragma that
5708             --  appears within a package spec, the named entity must be
5709             --  within the package spec. We allow the package name itself
5710             --  to be mentioned since that makes sense, although it is not
5711             --  strictly allowed by 11.5(7).
5712
5713             if In_Package_Spec
5714               and then E /= Current_Scope
5715               and then Scope (E) /= Current_Scope
5716             then
5717                Error_Pragma_Arg
5718                  ("entity in pragma% is not in package spec (RM 11.5(7))",
5719                   Arg2);
5720             end if;
5721
5722             --  Loop through homonyms. As noted below, in the case of a package
5723             --  spec, only homonyms within the package spec are considered.
5724
5725             loop
5726                Suppress_Unsuppress_Echeck (E, C);
5727
5728                if Is_Generic_Instance (E)
5729                  and then Is_Subprogram (E)
5730                  and then Present (Alias (E))
5731                then
5732                   Suppress_Unsuppress_Echeck (Alias (E), C);
5733                end if;
5734
5735                --  Move to next homonym if not aspect spec case
5736
5737                exit when From_Aspect_Specification (N);
5738                E := Homonym (E);
5739                exit when No (E);
5740
5741                --  If we are within a package specification, the pragma only
5742                --  applies to homonyms in the same scope.
5743
5744                exit when In_Package_Spec
5745                  and then Scope (E) /= Current_Scope;
5746             end loop;
5747          end if;
5748       end Process_Suppress_Unsuppress;
5749
5750       ------------------
5751       -- Set_Exported --
5752       ------------------
5753
5754       procedure Set_Exported (E : Entity_Id; Arg : Node_Id) is
5755       begin
5756          if Is_Imported (E) then
5757             Error_Pragma_Arg
5758               ("cannot export entity& that was previously imported", Arg);
5759
5760          elsif Present (Address_Clause (E)) and then not CodePeer_Mode then
5761             Error_Pragma_Arg
5762               ("cannot export entity& that has an address clause", Arg);
5763          end if;
5764
5765          Set_Is_Exported (E);
5766
5767          --  Generate a reference for entity explicitly, because the
5768          --  identifier may be overloaded and name resolution will not
5769          --  generate one.
5770
5771          Generate_Reference (E, Arg);
5772
5773          --  Deal with exporting non-library level entity
5774
5775          if not Is_Library_Level_Entity (E) then
5776
5777             --  Not allowed at all for subprograms
5778
5779             if Is_Subprogram (E) then
5780                Error_Pragma_Arg ("local subprogram& cannot be exported", Arg);
5781
5782             --  Otherwise set public and statically allocated
5783
5784             else
5785                Set_Is_Public (E);
5786                Set_Is_Statically_Allocated (E);
5787
5788                --  Warn if the corresponding W flag is set and the pragma comes
5789                --  from source. The latter may not be true e.g. on VMS where we
5790                --  expand export pragmas for exception codes associated with
5791                --  imported or exported exceptions. We do not want to generate
5792                --  a warning for something that the user did not write.
5793
5794                if Warn_On_Export_Import
5795                  and then Comes_From_Source (Arg)
5796                then
5797                   Error_Msg_NE
5798                     ("?& has been made static as a result of Export", Arg, E);
5799                   Error_Msg_N
5800                     ("\this usage is non-standard and non-portable", Arg);
5801                end if;
5802             end if;
5803          end if;
5804
5805          if Warn_On_Export_Import and then Is_Type (E) then
5806             Error_Msg_NE ("exporting a type has no effect?", Arg, E);
5807          end if;
5808
5809          if Warn_On_Export_Import and Inside_A_Generic then
5810             Error_Msg_NE
5811               ("all instances of& will have the same external name?", Arg, E);
5812          end if;
5813       end Set_Exported;
5814
5815       ----------------------------------------------
5816       -- Set_Extended_Import_Export_External_Name --
5817       ----------------------------------------------
5818
5819       procedure Set_Extended_Import_Export_External_Name
5820         (Internal_Ent : Entity_Id;
5821          Arg_External : Node_Id)
5822       is
5823          Old_Name : constant Node_Id := Interface_Name (Internal_Ent);
5824          New_Name : Node_Id;
5825
5826       begin
5827          if No (Arg_External) then
5828             return;
5829          end if;
5830
5831          Check_Arg_Is_External_Name (Arg_External);
5832
5833          if Nkind (Arg_External) = N_String_Literal then
5834             if String_Length (Strval (Arg_External)) = 0 then
5835                return;
5836             else
5837                New_Name := Adjust_External_Name_Case (Arg_External);
5838             end if;
5839
5840          elsif Nkind (Arg_External) = N_Identifier then
5841             New_Name := Get_Default_External_Name (Arg_External);
5842
5843          --  Check_Arg_Is_External_Name should let through only identifiers and
5844          --  string literals or static string expressions (which are folded to
5845          --  string literals).
5846
5847          else
5848             raise Program_Error;
5849          end if;
5850
5851          --  If we already have an external name set (by a prior normal Import
5852          --  or Export pragma), then the external names must match
5853
5854          if Present (Interface_Name (Internal_Ent)) then
5855             Check_Matching_Internal_Names : declare
5856                S1 : constant String_Id := Strval (Old_Name);
5857                S2 : constant String_Id := Strval (New_Name);
5858
5859                procedure Mismatch;
5860                --  Called if names do not match
5861
5862                --------------
5863                -- Mismatch --
5864                --------------
5865
5866                procedure Mismatch is
5867                begin
5868                   Error_Msg_Sloc := Sloc (Old_Name);
5869                   Error_Pragma_Arg
5870                     ("external name does not match that given #",
5871                      Arg_External);
5872                end Mismatch;
5873
5874             --  Start of processing for Check_Matching_Internal_Names
5875
5876             begin
5877                if String_Length (S1) /= String_Length (S2) then
5878                   Mismatch;
5879
5880                else
5881                   for J in 1 .. String_Length (S1) loop
5882                      if Get_String_Char (S1, J) /= Get_String_Char (S2, J) then
5883                         Mismatch;
5884                      end if;
5885                   end loop;
5886                end if;
5887             end Check_Matching_Internal_Names;
5888
5889          --  Otherwise set the given name
5890
5891          else
5892             Set_Encoded_Interface_Name (Internal_Ent, New_Name);
5893             Check_Duplicated_Export_Name (New_Name);
5894          end if;
5895       end Set_Extended_Import_Export_External_Name;
5896
5897       ------------------
5898       -- Set_Imported --
5899       ------------------
5900
5901       procedure Set_Imported (E : Entity_Id) is
5902       begin
5903          --  Error message if already imported or exported
5904
5905          if Is_Exported (E) or else Is_Imported (E) then
5906
5907             --  Error if being set Exported twice
5908
5909             if Is_Exported (E) then
5910                Error_Msg_NE ("entity& was previously exported", N, E);
5911
5912             --  OK if Import/Interface case
5913
5914             elsif Import_Interface_Present (N) then
5915                goto OK;
5916
5917             --  Error if being set Imported twice
5918
5919             else
5920                Error_Msg_NE ("entity& was previously imported", N, E);
5921             end if;
5922
5923             Error_Msg_Name_1 := Pname;
5924             Error_Msg_N
5925               ("\(pragma% applies to all previous entities)", N);
5926
5927             Error_Msg_Sloc  := Sloc (E);
5928             Error_Msg_NE ("\import not allowed for& declared#", N, E);
5929
5930          --  Here if not previously imported or exported, OK to import
5931
5932          else
5933             Set_Is_Imported (E);
5934
5935             --  If the entity is an object that is not at the library level,
5936             --  then it is statically allocated. We do not worry about objects
5937             --  with address clauses in this context since they are not really
5938             --  imported in the linker sense.
5939
5940             if Is_Object (E)
5941               and then not Is_Library_Level_Entity (E)
5942               and then No (Address_Clause (E))
5943             then
5944                Set_Is_Statically_Allocated (E);
5945             end if;
5946          end if;
5947
5948          <<OK>> null;
5949       end Set_Imported;
5950
5951       -------------------------
5952       -- Set_Mechanism_Value --
5953       -------------------------
5954
5955       --  Note: the mechanism name has not been analyzed (and cannot indeed be
5956       --  analyzed, since it is semantic nonsense), so we get it in the exact
5957       --  form created by the parser.
5958
5959       procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id) is
5960          Class        : Node_Id;
5961          Param        : Node_Id;
5962          Mech_Name_Id : Name_Id;
5963
5964          procedure Bad_Class;
5965          --  Signal bad descriptor class name
5966
5967          procedure Bad_Mechanism;
5968          --  Signal bad mechanism name
5969
5970          ---------------
5971          -- Bad_Class --
5972          ---------------
5973
5974          procedure Bad_Class is
5975          begin
5976             Error_Pragma_Arg ("unrecognized descriptor class name", Class);
5977          end Bad_Class;
5978
5979          -------------------------
5980          -- Bad_Mechanism_Value --
5981          -------------------------
5982
5983          procedure Bad_Mechanism is
5984          begin
5985             Error_Pragma_Arg ("unrecognized mechanism name", Mech_Name);
5986          end Bad_Mechanism;
5987
5988       --  Start of processing for Set_Mechanism_Value
5989
5990       begin
5991          if Mechanism (Ent) /= Default_Mechanism then
5992             Error_Msg_NE
5993               ("mechanism for & has already been set", Mech_Name, Ent);
5994          end if;
5995
5996          --  MECHANISM_NAME ::= value | reference | descriptor |
5997          --                     short_descriptor
5998
5999          if Nkind (Mech_Name) = N_Identifier then
6000             if Chars (Mech_Name) = Name_Value then
6001                Set_Mechanism (Ent, By_Copy);
6002                return;
6003
6004             elsif Chars (Mech_Name) = Name_Reference then
6005                Set_Mechanism (Ent, By_Reference);
6006                return;
6007
6008             elsif Chars (Mech_Name) = Name_Descriptor then
6009                Check_VMS (Mech_Name);
6010
6011                --  Descriptor => Short_Descriptor if pragma was given
6012
6013                if Short_Descriptors then
6014                   Set_Mechanism (Ent, By_Short_Descriptor);
6015                else
6016                   Set_Mechanism (Ent, By_Descriptor);
6017                end if;
6018
6019                return;
6020
6021             elsif Chars (Mech_Name) = Name_Short_Descriptor then
6022                Check_VMS (Mech_Name);
6023                Set_Mechanism (Ent, By_Short_Descriptor);
6024                return;
6025
6026             elsif Chars (Mech_Name) = Name_Copy then
6027                Error_Pragma_Arg
6028                  ("bad mechanism name, Value assumed", Mech_Name);
6029
6030             else
6031                Bad_Mechanism;
6032             end if;
6033
6034          --  MECHANISM_NAME ::= descriptor (CLASS_NAME) |
6035          --                     short_descriptor (CLASS_NAME)
6036          --  CLASS_NAME     ::= ubs | ubsb | uba | s | sb | a | nca
6037
6038          --  Note: this form is parsed as an indexed component
6039
6040          elsif Nkind (Mech_Name) = N_Indexed_Component then
6041             Class := First (Expressions (Mech_Name));
6042
6043             if Nkind (Prefix (Mech_Name)) /= N_Identifier
6044              or else not (Chars (Prefix (Mech_Name)) = Name_Descriptor or else
6045                           Chars (Prefix (Mech_Name)) = Name_Short_Descriptor)
6046              or else Present (Next (Class))
6047             then
6048                Bad_Mechanism;
6049             else
6050                Mech_Name_Id := Chars (Prefix (Mech_Name));
6051
6052                --  Change Descriptor => Short_Descriptor if pragma was given
6053
6054                if Mech_Name_Id = Name_Descriptor
6055                  and then Short_Descriptors
6056                then
6057                   Mech_Name_Id := Name_Short_Descriptor;
6058                end if;
6059             end if;
6060
6061          --  MECHANISM_NAME ::= descriptor (Class => CLASS_NAME) |
6062          --                     short_descriptor (Class => CLASS_NAME)
6063          --  CLASS_NAME     ::= ubs | ubsb | uba | s | sb | a | nca
6064
6065          --  Note: this form is parsed as a function call
6066
6067          elsif Nkind (Mech_Name) = N_Function_Call then
6068             Param := First (Parameter_Associations (Mech_Name));
6069
6070             if Nkind (Name (Mech_Name)) /= N_Identifier
6071               or else not (Chars (Name (Mech_Name)) = Name_Descriptor or else
6072                            Chars (Name (Mech_Name)) = Name_Short_Descriptor)
6073               or else Present (Next (Param))
6074               or else No (Selector_Name (Param))
6075               or else Chars (Selector_Name (Param)) /= Name_Class
6076             then
6077                Bad_Mechanism;
6078             else
6079                Class := Explicit_Actual_Parameter (Param);
6080                Mech_Name_Id := Chars (Name (Mech_Name));
6081             end if;
6082
6083          else
6084             Bad_Mechanism;
6085          end if;
6086
6087          --  Fall through here with Class set to descriptor class name
6088
6089          Check_VMS (Mech_Name);
6090
6091          if Nkind (Class) /= N_Identifier then
6092             Bad_Class;
6093
6094          elsif Mech_Name_Id = Name_Descriptor
6095            and then Chars (Class) = Name_UBS
6096          then
6097             Set_Mechanism (Ent, By_Descriptor_UBS);
6098
6099          elsif Mech_Name_Id = Name_Descriptor
6100            and then Chars (Class) = Name_UBSB
6101          then
6102             Set_Mechanism (Ent, By_Descriptor_UBSB);
6103
6104          elsif Mech_Name_Id = Name_Descriptor
6105            and then Chars (Class) = Name_UBA
6106          then
6107             Set_Mechanism (Ent, By_Descriptor_UBA);
6108
6109          elsif Mech_Name_Id = Name_Descriptor
6110            and then Chars (Class) = Name_S
6111          then
6112             Set_Mechanism (Ent, By_Descriptor_S);
6113
6114          elsif Mech_Name_Id = Name_Descriptor
6115            and then Chars (Class) = Name_SB
6116          then
6117             Set_Mechanism (Ent, By_Descriptor_SB);
6118
6119          elsif Mech_Name_Id = Name_Descriptor
6120            and then Chars (Class) = Name_A
6121          then
6122             Set_Mechanism (Ent, By_Descriptor_A);
6123
6124          elsif Mech_Name_Id = Name_Descriptor
6125            and then Chars (Class) = Name_NCA
6126          then
6127             Set_Mechanism (Ent, By_Descriptor_NCA);
6128
6129          elsif Mech_Name_Id = Name_Short_Descriptor
6130            and then Chars (Class) = Name_UBS
6131          then
6132             Set_Mechanism (Ent, By_Short_Descriptor_UBS);
6133
6134          elsif Mech_Name_Id = Name_Short_Descriptor
6135            and then Chars (Class) = Name_UBSB
6136          then
6137             Set_Mechanism (Ent, By_Short_Descriptor_UBSB);
6138
6139          elsif Mech_Name_Id = Name_Short_Descriptor
6140            and then Chars (Class) = Name_UBA
6141          then
6142             Set_Mechanism (Ent, By_Short_Descriptor_UBA);
6143
6144          elsif Mech_Name_Id = Name_Short_Descriptor
6145            and then Chars (Class) = Name_S
6146          then
6147             Set_Mechanism (Ent, By_Short_Descriptor_S);
6148
6149          elsif Mech_Name_Id = Name_Short_Descriptor
6150            and then Chars (Class) = Name_SB
6151          then
6152             Set_Mechanism (Ent, By_Short_Descriptor_SB);
6153
6154          elsif Mech_Name_Id = Name_Short_Descriptor
6155            and then Chars (Class) = Name_A
6156          then
6157             Set_Mechanism (Ent, By_Short_Descriptor_A);
6158
6159          elsif Mech_Name_Id = Name_Short_Descriptor
6160            and then Chars (Class) = Name_NCA
6161          then
6162             Set_Mechanism (Ent, By_Short_Descriptor_NCA);
6163
6164          else
6165             Bad_Class;
6166          end if;
6167       end Set_Mechanism_Value;
6168
6169       ---------------------------
6170       -- Set_Ravenscar_Profile --
6171       ---------------------------
6172
6173       --  The tasks to be done here are
6174
6175       --    Set required policies
6176
6177       --      pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
6178       --      pragma Locking_Policy (Ceiling_Locking)
6179
6180       --    Set Detect_Blocking mode
6181
6182       --    Set required restrictions (see System.Rident for detailed list)
6183
6184       --    Set the No_Dependence rules
6185       --      No_Dependence => Ada.Asynchronous_Task_Control
6186       --      No_Dependence => Ada.Calendar
6187       --      No_Dependence => Ada.Execution_Time.Group_Budget
6188       --      No_Dependence => Ada.Execution_Time.Timers
6189       --      No_Dependence => Ada.Task_Attributes
6190       --      No_Dependence => System.Multiprocessors.Dispatching_Domains
6191
6192       procedure Set_Ravenscar_Profile (N : Node_Id) is
6193          Prefix_Entity   : Entity_Id;
6194          Selector_Entity : Entity_Id;
6195          Prefix_Node     : Node_Id;
6196          Node            : Node_Id;
6197
6198       begin
6199          --  pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
6200
6201          if Task_Dispatching_Policy /= ' '
6202            and then Task_Dispatching_Policy /= 'F'
6203          then
6204             Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
6205             Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
6206
6207          --  Set the FIFO_Within_Priorities policy, but always preserve
6208          --  System_Location since we like the error message with the run time
6209          --  name.
6210
6211          else
6212             Task_Dispatching_Policy := 'F';
6213
6214             if Task_Dispatching_Policy_Sloc /= System_Location then
6215                Task_Dispatching_Policy_Sloc := Loc;
6216             end if;
6217          end if;
6218
6219          --  pragma Locking_Policy (Ceiling_Locking)
6220
6221          if Locking_Policy /= ' '
6222            and then Locking_Policy /= 'C'
6223          then
6224             Error_Msg_Sloc := Locking_Policy_Sloc;
6225             Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
6226
6227          --  Set the Ceiling_Locking policy, but preserve System_Location since
6228          --  we like the error message with the run time name.
6229
6230          else
6231             Locking_Policy := 'C';
6232
6233             if Locking_Policy_Sloc /= System_Location then
6234                Locking_Policy_Sloc := Loc;
6235             end if;
6236          end if;
6237
6238          --  pragma Detect_Blocking
6239
6240          Detect_Blocking := True;
6241
6242          --  Set the corresponding restrictions
6243
6244          Set_Profile_Restrictions
6245            (Ravenscar, N, Warn => Treat_Restrictions_As_Warnings);
6246
6247          --  Set the No_Dependence restrictions
6248
6249          --  The following No_Dependence restrictions:
6250          --    No_Dependence => Ada.Asynchronous_Task_Control
6251          --    No_Dependence => Ada.Calendar
6252          --    No_Dependence => Ada.Task_Attributes
6253          --  are already set by previous call to Set_Profile_Restrictions.
6254
6255          --  Set the following restrictions which were added to Ada 2005:
6256          --    No_Dependence => Ada.Execution_Time.Group_Budget
6257          --    No_Dependence => Ada.Execution_Time.Timers
6258
6259          if Ada_Version >= Ada_2005 then
6260             Name_Buffer (1 .. 3) := "ada";
6261             Name_Len := 3;
6262
6263             Prefix_Entity := Make_Identifier (Loc, Name_Find);
6264
6265             Name_Buffer (1 .. 14) := "execution_time";
6266             Name_Len := 14;
6267
6268             Selector_Entity := Make_Identifier (Loc, Name_Find);
6269
6270             Prefix_Node :=
6271               Make_Selected_Component
6272                 (Sloc          => Loc,
6273                  Prefix        => Prefix_Entity,
6274                  Selector_Name => Selector_Entity);
6275
6276             Name_Buffer (1 .. 13) := "group_budgets";
6277             Name_Len := 13;
6278
6279             Selector_Entity := Make_Identifier (Loc, Name_Find);
6280
6281             Node :=
6282               Make_Selected_Component
6283                 (Sloc          => Loc,
6284                  Prefix        => Prefix_Node,
6285                  Selector_Name => Selector_Entity);
6286
6287             Set_Restriction_No_Dependence
6288               (Unit    => Node,
6289                Warn    => Treat_Restrictions_As_Warnings,
6290                Profile => Ravenscar);
6291
6292             Name_Buffer (1 .. 6) := "timers";
6293             Name_Len := 6;
6294
6295             Selector_Entity := Make_Identifier (Loc, Name_Find);
6296
6297             Node :=
6298               Make_Selected_Component
6299                 (Sloc          => Loc,
6300                  Prefix        => Prefix_Node,
6301                  Selector_Name => Selector_Entity);
6302
6303             Set_Restriction_No_Dependence
6304               (Unit    => Node,
6305                Warn    => Treat_Restrictions_As_Warnings,
6306                Profile => Ravenscar);
6307          end if;
6308
6309          --  Set the following restrictions which was added to Ada 2012 (see
6310          --  AI-0171):
6311          --    No_Dependence => System.Multiprocessors.Dispatching_Domains
6312
6313          if Ada_Version >= Ada_2012 then
6314             Name_Buffer (1 .. 6) := "system";
6315             Name_Len := 6;
6316
6317             Prefix_Entity := Make_Identifier (Loc, Name_Find);
6318
6319             Name_Buffer (1 .. 15) := "multiprocessors";
6320             Name_Len := 15;
6321
6322             Selector_Entity := Make_Identifier (Loc, Name_Find);
6323
6324             Prefix_Node :=
6325               Make_Selected_Component
6326                 (Sloc          => Loc,
6327                  Prefix        => Prefix_Entity,
6328                  Selector_Name => Selector_Entity);
6329
6330             Name_Buffer (1 .. 19) := "dispatching_domains";
6331             Name_Len := 19;
6332
6333             Selector_Entity := Make_Identifier (Loc, Name_Find);
6334
6335             Node :=
6336               Make_Selected_Component
6337                 (Sloc          => Loc,
6338                  Prefix        => Prefix_Node,
6339                  Selector_Name => Selector_Entity);
6340
6341             Set_Restriction_No_Dependence
6342               (Unit    => Node,
6343                Warn    => Treat_Restrictions_As_Warnings,
6344                Profile => Ravenscar);
6345          end if;
6346       end Set_Ravenscar_Profile;
6347
6348    --  Start of processing for Analyze_Pragma
6349
6350    begin
6351       --  The following code is a defense against recursion. Not clear that
6352       --  this can happen legitimately, but perhaps some error situations
6353       --  can cause it, and we did see this recursion during testing.
6354
6355       if Analyzed (N) then
6356          return;
6357       else
6358          Set_Analyzed (N, True);
6359       end if;
6360
6361       --  Deal with unrecognized pragma
6362
6363       Pname := Pragma_Name (N);
6364
6365       if not Is_Pragma_Name (Pname) then
6366          if Warn_On_Unrecognized_Pragma then
6367             Error_Msg_Name_1 := Pname;
6368             Error_Msg_N ("?unrecognized pragma%!", Pragma_Identifier (N));
6369
6370             for PN in First_Pragma_Name .. Last_Pragma_Name loop
6371                if Is_Bad_Spelling_Of (Pname, PN) then
6372                   Error_Msg_Name_1 := PN;
6373                   Error_Msg_N -- CODEFIX
6374                     ("\?possible misspelling of %!", Pragma_Identifier (N));
6375                   exit;
6376                end if;
6377             end loop;
6378          end if;
6379
6380          return;
6381       end if;
6382
6383       --  Here to start processing for recognized pragma
6384
6385       Prag_Id := Get_Pragma_Id (Pname);
6386
6387       if Present (Corresponding_Aspect (N)) then
6388          Pname := Chars (Identifier (Corresponding_Aspect (N)));
6389       end if;
6390
6391       --  Preset arguments
6392
6393       Arg_Count := 0;
6394       Arg1      := Empty;
6395       Arg2      := Empty;
6396       Arg3      := Empty;
6397       Arg4      := Empty;
6398
6399       if Present (Pragma_Argument_Associations (N)) then
6400          Arg_Count := List_Length (Pragma_Argument_Associations (N));
6401          Arg1 := First (Pragma_Argument_Associations (N));
6402
6403          if Present (Arg1) then
6404             Arg2 := Next (Arg1);
6405
6406             if Present (Arg2) then
6407                Arg3 := Next (Arg2);
6408
6409                if Present (Arg3) then
6410                   Arg4 := Next (Arg3);
6411                end if;
6412             end if;
6413          end if;
6414       end if;
6415
6416       --  An enumeration type defines the pragmas that are supported by the
6417       --  implementation. Get_Pragma_Id (in package Prag) transforms a name
6418       --  into the corresponding enumeration value for the following case.
6419
6420       case Prag_Id is
6421
6422          -----------------
6423          -- Abort_Defer --
6424          -----------------
6425
6426          --  pragma Abort_Defer;
6427
6428          when Pragma_Abort_Defer =>
6429             GNAT_Pragma;
6430             Check_Arg_Count (0);
6431
6432             --  The only required semantic processing is to check the
6433             --  placement. This pragma must appear at the start of the
6434             --  statement sequence of a handled sequence of statements.
6435
6436             if Nkind (Parent (N)) /= N_Handled_Sequence_Of_Statements
6437               or else N /= First (Statements (Parent (N)))
6438             then
6439                Pragma_Misplaced;
6440             end if;
6441
6442          ------------
6443          -- Ada_83 --
6444          ------------
6445
6446          --  pragma Ada_83;
6447
6448          --  Note: this pragma also has some specific processing in Par.Prag
6449          --  because we want to set the Ada version mode during parsing.
6450
6451          when Pragma_Ada_83 =>
6452             GNAT_Pragma;
6453             Check_Arg_Count (0);
6454
6455             --  We really should check unconditionally for proper configuration
6456             --  pragma placement, since we really don't want mixed Ada modes
6457             --  within a single unit, and the GNAT reference manual has always
6458             --  said this was a configuration pragma, but we did not check and
6459             --  are hesitant to add the check now.
6460
6461             --  However, we really cannot tolerate mixing Ada 2005 or Ada 2012
6462             --  with Ada 83 or Ada 95, so we must check if we are in Ada 2005
6463             --  or Ada 2012 mode.
6464
6465             if Ada_Version >= Ada_2005 then
6466                Check_Valid_Configuration_Pragma;
6467             end if;
6468
6469             --  Now set Ada 83 mode
6470
6471             Ada_Version := Ada_83;
6472             Ada_Version_Explicit := Ada_Version;
6473
6474          ------------
6475          -- Ada_95 --
6476          ------------
6477
6478          --  pragma Ada_95;
6479
6480          --  Note: this pragma also has some specific processing in Par.Prag
6481          --  because we want to set the Ada 83 version mode during parsing.
6482
6483          when Pragma_Ada_95 =>
6484             GNAT_Pragma;
6485             Check_Arg_Count (0);
6486
6487             --  We really should check unconditionally for proper configuration
6488             --  pragma placement, since we really don't want mixed Ada modes
6489             --  within a single unit, and the GNAT reference manual has always
6490             --  said this was a configuration pragma, but we did not check and
6491             --  are hesitant to add the check now.
6492
6493             --  However, we really cannot tolerate mixing Ada 2005 with Ada 83
6494             --  or Ada 95, so we must check if we are in Ada 2005 mode.
6495
6496             if Ada_Version >= Ada_2005 then
6497                Check_Valid_Configuration_Pragma;
6498             end if;
6499
6500             --  Now set Ada 95 mode
6501
6502             Ada_Version := Ada_95;
6503             Ada_Version_Explicit := Ada_Version;
6504
6505          ---------------------
6506          -- Ada_05/Ada_2005 --
6507          ---------------------
6508
6509          --  pragma Ada_05;
6510          --  pragma Ada_05 (LOCAL_NAME);
6511
6512          --  pragma Ada_2005;
6513          --  pragma Ada_2005 (LOCAL_NAME):
6514
6515          --  Note: these pragmas also have some specific processing in Par.Prag
6516          --  because we want to set the Ada 2005 version mode during parsing.
6517
6518          when Pragma_Ada_05 | Pragma_Ada_2005 => declare
6519             E_Id : Node_Id;
6520
6521          begin
6522             GNAT_Pragma;
6523
6524             if Arg_Count = 1 then
6525                Check_Arg_Is_Local_Name (Arg1);
6526                E_Id := Get_Pragma_Arg (Arg1);
6527
6528                if Etype (E_Id) = Any_Type then
6529                   return;
6530                end if;
6531
6532                Set_Is_Ada_2005_Only (Entity (E_Id));
6533
6534             else
6535                Check_Arg_Count (0);
6536
6537                --  For Ada_2005 we unconditionally enforce the documented
6538                --  configuration pragma placement, since we do not want to
6539                --  tolerate mixed modes in a unit involving Ada 2005. That
6540                --  would cause real difficulties for those cases where there
6541                --  are incompatibilities between Ada 95 and Ada 2005.
6542
6543                Check_Valid_Configuration_Pragma;
6544
6545                --  Now set appropriate Ada mode
6546
6547                Ada_Version          := Ada_2005;
6548                Ada_Version_Explicit := Ada_2005;
6549             end if;
6550          end;
6551
6552          ---------------------
6553          -- Ada_12/Ada_2012 --
6554          ---------------------
6555
6556          --  pragma Ada_12;
6557          --  pragma Ada_12 (LOCAL_NAME);
6558
6559          --  pragma Ada_2012;
6560          --  pragma Ada_2012 (LOCAL_NAME):
6561
6562          --  Note: these pragmas also have some specific processing in Par.Prag
6563          --  because we want to set the Ada 2012 version mode during parsing.
6564
6565          when Pragma_Ada_12 | Pragma_Ada_2012 => declare
6566             E_Id : Node_Id;
6567
6568          begin
6569             GNAT_Pragma;
6570
6571             if Arg_Count = 1 then
6572                Check_Arg_Is_Local_Name (Arg1);
6573                E_Id := Get_Pragma_Arg (Arg1);
6574
6575                if Etype (E_Id) = Any_Type then
6576                   return;
6577                end if;
6578
6579                Set_Is_Ada_2012_Only (Entity (E_Id));
6580
6581             else
6582                Check_Arg_Count (0);
6583
6584                --  For Ada_2012 we unconditionally enforce the documented
6585                --  configuration pragma placement, since we do not want to
6586                --  tolerate mixed modes in a unit involving Ada 2012. That
6587                --  would cause real difficulties for those cases where there
6588                --  are incompatibilities between Ada 95 and Ada 2012. We could
6589                --  allow mixing of Ada 2005 and Ada 2012 but it's not worth it.
6590
6591                Check_Valid_Configuration_Pragma;
6592
6593                --  Now set appropriate Ada mode
6594
6595                Ada_Version          := Ada_2012;
6596                Ada_Version_Explicit := Ada_2012;
6597             end if;
6598          end;
6599
6600          ----------------------
6601          -- All_Calls_Remote --
6602          ----------------------
6603
6604          --  pragma All_Calls_Remote [(library_package_NAME)];
6605
6606          when Pragma_All_Calls_Remote => All_Calls_Remote : declare
6607             Lib_Entity : Entity_Id;
6608
6609          begin
6610             Check_Ada_83_Warning;
6611             Check_Valid_Library_Unit_Pragma;
6612
6613             if Nkind (N) = N_Null_Statement then
6614                return;
6615             end if;
6616
6617             Lib_Entity := Find_Lib_Unit_Name;
6618
6619             --  This pragma should only apply to a RCI unit (RM E.2.3(23))
6620
6621             if Present (Lib_Entity)
6622               and then not Debug_Flag_U
6623             then
6624                if not Is_Remote_Call_Interface (Lib_Entity) then
6625                   Error_Pragma ("pragma% only apply to rci unit");
6626
6627                --  Set flag for entity of the library unit
6628
6629                else
6630                   Set_Has_All_Calls_Remote (Lib_Entity);
6631                end if;
6632
6633             end if;
6634          end All_Calls_Remote;
6635
6636          --------------
6637          -- Annotate --
6638          --------------
6639
6640          --  pragma Annotate (IDENTIFIER [, IDENTIFIER {, ARG}]);
6641          --  ARG ::= NAME | EXPRESSION
6642
6643          --  The first two arguments are by convention intended to refer to an
6644          --  external tool and a tool-specific function. These arguments are
6645          --  not analyzed.
6646
6647          when Pragma_Annotate => Annotate : declare
6648             Arg : Node_Id;
6649             Exp : Node_Id;
6650
6651          begin
6652             GNAT_Pragma;
6653             Check_At_Least_N_Arguments (1);
6654             Check_Arg_Is_Identifier (Arg1);
6655             Check_No_Identifiers;
6656             Store_Note (N);
6657
6658             --  Second parameter is optional, it is never analyzed
6659
6660             if No (Arg2) then
6661                null;
6662
6663             --  Here if we have a second parameter
6664
6665             else
6666                --  Second parameter must be identifier
6667
6668                Check_Arg_Is_Identifier (Arg2);
6669
6670                --  Process remaining parameters if any
6671
6672                Arg := Next (Arg2);
6673                while Present (Arg) loop
6674                   Exp := Get_Pragma_Arg (Arg);
6675                   Analyze (Exp);
6676
6677                   if Is_Entity_Name (Exp) then
6678                      null;
6679
6680                   --  For string literals, we assume Standard_String as the
6681                   --  type, unless the string contains wide or wide_wide
6682                   --  characters.
6683
6684                   elsif Nkind (Exp) = N_String_Literal then
6685                      if Has_Wide_Wide_Character (Exp) then
6686                         Resolve (Exp, Standard_Wide_Wide_String);
6687                      elsif Has_Wide_Character (Exp) then
6688                         Resolve (Exp, Standard_Wide_String);
6689                      else
6690                         Resolve (Exp, Standard_String);
6691                      end if;
6692
6693                   elsif Is_Overloaded (Exp) then
6694                         Error_Pragma_Arg
6695                           ("ambiguous argument for pragma%", Exp);
6696
6697                   else
6698                      Resolve (Exp);
6699                   end if;
6700
6701                   Next (Arg);
6702                end loop;
6703             end if;
6704          end Annotate;
6705
6706          ------------
6707          -- Assert --
6708          ------------
6709
6710          --  pragma Assert ([Check =>] Boolean_EXPRESSION
6711          --                 [, [Message =>] Static_String_EXPRESSION]);
6712
6713          when Pragma_Assert => Assert : declare
6714             Expr : Node_Id;
6715             Newa : List_Id;
6716
6717          begin
6718             Ada_2005_Pragma;
6719             Check_At_Least_N_Arguments (1);
6720             Check_At_Most_N_Arguments (2);
6721             Check_Arg_Order ((Name_Check, Name_Message));
6722             Check_Optional_Identifier (Arg1, Name_Check);
6723
6724             --  We treat pragma Assert as equivalent to:
6725
6726             --    pragma Check (Assertion, condition [, msg]);
6727
6728             --  So rewrite pragma in this manner, and analyze the result
6729
6730             Expr := Get_Pragma_Arg (Arg1);
6731             Newa := New_List (
6732               Make_Pragma_Argument_Association (Loc,
6733                 Expression => Make_Identifier (Loc, Name_Assertion)),
6734
6735               Make_Pragma_Argument_Association (Sloc (Expr),
6736                 Expression => Expr));
6737
6738             if Arg_Count > 1 then
6739                Check_Optional_Identifier (Arg2, Name_Message);
6740                Analyze_And_Resolve (Get_Pragma_Arg (Arg2), Standard_String);
6741                Append_To (Newa, Relocate_Node (Arg2));
6742             end if;
6743
6744             Rewrite (N,
6745               Make_Pragma (Loc,
6746                 Chars                        => Name_Check,
6747                 Pragma_Argument_Associations => Newa));
6748             Analyze (N);
6749          end Assert;
6750
6751          ----------------------
6752          -- Assertion_Policy --
6753          ----------------------
6754
6755          --  pragma Assertion_Policy (Check | Disable |Ignore)
6756
6757          when Pragma_Assertion_Policy => Assertion_Policy : declare
6758             Policy : Node_Id;
6759
6760          begin
6761             Ada_2005_Pragma;
6762             Check_Valid_Configuration_Pragma;
6763             Check_Arg_Count (1);
6764             Check_No_Identifiers;
6765             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Disable, Name_Ignore);
6766
6767             --  We treat pragma Assertion_Policy as equivalent to:
6768
6769             --    pragma Check_Policy (Assertion, policy)
6770
6771             --  So rewrite the pragma in that manner and link on to the chain
6772             --  of Check_Policy pragmas, marking the pragma as analyzed.
6773
6774             Policy := Get_Pragma_Arg (Arg1);
6775
6776             Rewrite (N,
6777               Make_Pragma (Loc,
6778                 Chars => Name_Check_Policy,
6779
6780                 Pragma_Argument_Associations => New_List (
6781                   Make_Pragma_Argument_Association (Loc,
6782                     Expression => Make_Identifier (Loc, Name_Assertion)),
6783
6784                   Make_Pragma_Argument_Association (Loc,
6785                     Expression =>
6786                       Make_Identifier (Sloc (Policy), Chars (Policy))))));
6787
6788             Set_Analyzed (N);
6789             Set_Next_Pragma (N, Opt.Check_Policy_List);
6790             Opt.Check_Policy_List := N;
6791          end Assertion_Policy;
6792
6793          ------------------------------
6794          -- Assume_No_Invalid_Values --
6795          ------------------------------
6796
6797          --  pragma Assume_No_Invalid_Values (On | Off);
6798
6799          when Pragma_Assume_No_Invalid_Values =>
6800             GNAT_Pragma;
6801             Check_Valid_Configuration_Pragma;
6802             Check_Arg_Count (1);
6803             Check_No_Identifiers;
6804             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
6805
6806             if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
6807                Assume_No_Invalid_Values := True;
6808             else
6809                Assume_No_Invalid_Values := False;
6810             end if;
6811
6812          ---------------
6813          -- AST_Entry --
6814          ---------------
6815
6816          --  pragma AST_Entry (entry_IDENTIFIER);
6817
6818          when Pragma_AST_Entry => AST_Entry : declare
6819             Ent : Node_Id;
6820
6821          begin
6822             GNAT_Pragma;
6823             Check_VMS (N);
6824             Check_Arg_Count (1);
6825             Check_No_Identifiers;
6826             Check_Arg_Is_Local_Name (Arg1);
6827             Ent := Entity (Get_Pragma_Arg (Arg1));
6828
6829             --  Note: the implementation of the AST_Entry pragma could handle
6830             --  the entry family case fine, but for now we are consistent with
6831             --  the DEC rules, and do not allow the pragma, which of course
6832             --  has the effect of also forbidding the attribute.
6833
6834             if Ekind (Ent) /= E_Entry then
6835                Error_Pragma_Arg
6836                  ("pragma% argument must be simple entry name", Arg1);
6837
6838             elsif Is_AST_Entry (Ent) then
6839                Error_Pragma_Arg
6840                  ("duplicate % pragma for entry", Arg1);
6841
6842             elsif Has_Homonym (Ent) then
6843                Error_Pragma_Arg
6844                  ("pragma% argument cannot specify overloaded entry", Arg1);
6845
6846             else
6847                declare
6848                   FF : constant Entity_Id := First_Formal (Ent);
6849
6850                begin
6851                   if Present (FF) then
6852                      if Present (Next_Formal (FF)) then
6853                         Error_Pragma_Arg
6854                           ("entry for pragma% can have only one argument",
6855                            Arg1);
6856
6857                      elsif Parameter_Mode (FF) /= E_In_Parameter then
6858                         Error_Pragma_Arg
6859                           ("entry parameter for pragma% must have mode IN",
6860                            Arg1);
6861                      end if;
6862                   end if;
6863                end;
6864
6865                Set_Is_AST_Entry (Ent);
6866             end if;
6867          end AST_Entry;
6868
6869          ------------------
6870          -- Asynchronous --
6871          ------------------
6872
6873          --  pragma Asynchronous (LOCAL_NAME);
6874
6875          when Pragma_Asynchronous => Asynchronous : declare
6876             Nm     : Entity_Id;
6877             C_Ent  : Entity_Id;
6878             L      : List_Id;
6879             S      : Node_Id;
6880             N      : Node_Id;
6881             Formal : Entity_Id;
6882
6883             procedure Process_Async_Pragma;
6884             --  Common processing for procedure and access-to-procedure case
6885
6886             --------------------------
6887             -- Process_Async_Pragma --
6888             --------------------------
6889
6890             procedure Process_Async_Pragma is
6891             begin
6892                if No (L) then
6893                   Set_Is_Asynchronous (Nm);
6894                   return;
6895                end if;
6896
6897                --  The formals should be of mode IN (RM E.4.1(6))
6898
6899                S := First (L);
6900                while Present (S) loop
6901                   Formal := Defining_Identifier (S);
6902
6903                   if Nkind (Formal) = N_Defining_Identifier
6904                     and then Ekind (Formal) /= E_In_Parameter
6905                   then
6906                      Error_Pragma_Arg
6907                        ("pragma% procedure can only have IN parameter",
6908                         Arg1);
6909                   end if;
6910
6911                   Next (S);
6912                end loop;
6913
6914                Set_Is_Asynchronous (Nm);
6915             end Process_Async_Pragma;
6916
6917          --  Start of processing for pragma Asynchronous
6918
6919          begin
6920             Check_Ada_83_Warning;
6921             Check_No_Identifiers;
6922             Check_Arg_Count (1);
6923             Check_Arg_Is_Local_Name (Arg1);
6924
6925             if Debug_Flag_U then
6926                return;
6927             end if;
6928
6929             C_Ent := Cunit_Entity (Current_Sem_Unit);
6930             Analyze (Get_Pragma_Arg (Arg1));
6931             Nm := Entity (Get_Pragma_Arg (Arg1));
6932
6933             if not Is_Remote_Call_Interface (C_Ent)
6934               and then not Is_Remote_Types (C_Ent)
6935             then
6936                --  This pragma should only appear in an RCI or Remote Types
6937                --  unit (RM E.4.1(4)).
6938
6939                Error_Pragma
6940                  ("pragma% not in Remote_Call_Interface or " &
6941                   "Remote_Types unit");
6942             end if;
6943
6944             if Ekind (Nm) = E_Procedure
6945               and then Nkind (Parent (Nm)) = N_Procedure_Specification
6946             then
6947                if not Is_Remote_Call_Interface (Nm) then
6948                   Error_Pragma_Arg
6949                     ("pragma% cannot be applied on non-remote procedure",
6950                      Arg1);
6951                end if;
6952
6953                L := Parameter_Specifications (Parent (Nm));
6954                Process_Async_Pragma;
6955                return;
6956
6957             elsif Ekind (Nm) = E_Function then
6958                Error_Pragma_Arg
6959                  ("pragma% cannot be applied to function", Arg1);
6960
6961             elsif Is_Remote_Access_To_Subprogram_Type (Nm) then
6962                   if Is_Record_Type (Nm) then
6963
6964                   --  A record type that is the Equivalent_Type for a remote
6965                   --  access-to-subprogram type.
6966
6967                      N := Declaration_Node (Corresponding_Remote_Type (Nm));
6968
6969                   else
6970                      --  A non-expanded RAS type (distribution is not enabled)
6971
6972                      N := Declaration_Node (Nm);
6973                   end if;
6974
6975                if Nkind (N) = N_Full_Type_Declaration
6976                  and then Nkind (Type_Definition (N)) =
6977                                      N_Access_Procedure_Definition
6978                then
6979                   L := Parameter_Specifications (Type_Definition (N));
6980                   Process_Async_Pragma;
6981
6982                   if Is_Asynchronous (Nm)
6983                     and then Expander_Active
6984                     and then Get_PCS_Name /= Name_No_DSA
6985                   then
6986                      RACW_Type_Is_Asynchronous (Underlying_RACW_Type (Nm));
6987                   end if;
6988
6989                else
6990                   Error_Pragma_Arg
6991                     ("pragma% cannot reference access-to-function type",
6992                     Arg1);
6993                end if;
6994
6995             --  Only other possibility is Access-to-class-wide type
6996
6997             elsif Is_Access_Type (Nm)
6998               and then Is_Class_Wide_Type (Designated_Type (Nm))
6999             then
7000                Check_First_Subtype (Arg1);
7001                Set_Is_Asynchronous (Nm);
7002                if Expander_Active then
7003                   RACW_Type_Is_Asynchronous (Nm);
7004                end if;
7005
7006             else
7007                Error_Pragma_Arg ("inappropriate argument for pragma%", Arg1);
7008             end if;
7009          end Asynchronous;
7010
7011          ------------
7012          -- Atomic --
7013          ------------
7014
7015          --  pragma Atomic (LOCAL_NAME);
7016
7017          when Pragma_Atomic =>
7018             Process_Atomic_Shared_Volatile;
7019
7020          -----------------------
7021          -- Atomic_Components --
7022          -----------------------
7023
7024          --  pragma Atomic_Components (array_LOCAL_NAME);
7025
7026          --  This processing is shared by Volatile_Components
7027
7028          when Pragma_Atomic_Components   |
7029               Pragma_Volatile_Components =>
7030
7031          Atomic_Components : declare
7032             E_Id : Node_Id;
7033             E    : Entity_Id;
7034             D    : Node_Id;
7035             K    : Node_Kind;
7036
7037          begin
7038             Check_Ada_83_Warning;
7039             Check_No_Identifiers;
7040             Check_Arg_Count (1);
7041             Check_Arg_Is_Local_Name (Arg1);
7042             E_Id := Get_Pragma_Arg (Arg1);
7043
7044             if Etype (E_Id) = Any_Type then
7045                return;
7046             end if;
7047
7048             E := Entity (E_Id);
7049
7050             Check_Duplicate_Pragma (E);
7051
7052             if Rep_Item_Too_Early (E, N)
7053                  or else
7054                Rep_Item_Too_Late (E, N)
7055             then
7056                return;
7057             end if;
7058
7059             D := Declaration_Node (E);
7060             K := Nkind (D);
7061
7062             if (K = N_Full_Type_Declaration and then Is_Array_Type (E))
7063               or else
7064                 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
7065                    and then Nkind (D) = N_Object_Declaration
7066                    and then Nkind (Object_Definition (D)) =
7067                                        N_Constrained_Array_Definition)
7068             then
7069                --  The flag is set on the object, or on the base type
7070
7071                if Nkind (D) /= N_Object_Declaration then
7072                   E := Base_Type (E);
7073                end if;
7074
7075                Set_Has_Volatile_Components (E);
7076
7077                if Prag_Id = Pragma_Atomic_Components then
7078                   Set_Has_Atomic_Components (E);
7079                end if;
7080
7081             else
7082                Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
7083             end if;
7084          end Atomic_Components;
7085          --------------------
7086          -- Attach_Handler --
7087          --------------------
7088
7089          --  pragma Attach_Handler (handler_NAME, EXPRESSION);
7090
7091          when Pragma_Attach_Handler =>
7092             Check_Ada_83_Warning;
7093             Check_No_Identifiers;
7094             Check_Arg_Count (2);
7095
7096             if No_Run_Time_Mode then
7097                Error_Msg_CRT ("Attach_Handler pragma", N);
7098             else
7099                Check_Interrupt_Or_Attach_Handler;
7100
7101                --  The expression that designates the attribute may depend on a
7102                --  discriminant, and is therefore a per-object expression, to
7103                --  be expanded in the init proc. If expansion is enabled, then
7104                --  perform semantic checks on a copy only.
7105
7106                if Expander_Active then
7107                   declare
7108                      Temp : constant Node_Id :=
7109                               New_Copy_Tree (Get_Pragma_Arg (Arg2));
7110                   begin
7111                      Set_Parent (Temp, N);
7112                      Preanalyze_And_Resolve (Temp, RTE (RE_Interrupt_ID));
7113                   end;
7114
7115                else
7116                   Analyze (Get_Pragma_Arg (Arg2));
7117                   Resolve (Get_Pragma_Arg (Arg2), RTE (RE_Interrupt_ID));
7118                end if;
7119
7120                Process_Interrupt_Or_Attach_Handler;
7121             end if;
7122
7123          --------------------
7124          -- C_Pass_By_Copy --
7125          --------------------
7126
7127          --  pragma C_Pass_By_Copy ([Max_Size =>] static_integer_EXPRESSION);
7128
7129          when Pragma_C_Pass_By_Copy => C_Pass_By_Copy : declare
7130             Arg : Node_Id;
7131             Val : Uint;
7132
7133          begin
7134             GNAT_Pragma;
7135             Check_Valid_Configuration_Pragma;
7136             Check_Arg_Count (1);
7137             Check_Optional_Identifier (Arg1, "max_size");
7138
7139             Arg := Get_Pragma_Arg (Arg1);
7140             Check_Arg_Is_Static_Expression (Arg, Any_Integer);
7141
7142             Val := Expr_Value (Arg);
7143
7144             if Val <= 0 then
7145                Error_Pragma_Arg
7146                  ("maximum size for pragma% must be positive", Arg1);
7147
7148             elsif UI_Is_In_Int_Range (Val) then
7149                Default_C_Record_Mechanism := UI_To_Int (Val);
7150
7151             --  If a giant value is given, Int'Last will do well enough.
7152             --  If sometime someone complains that a record larger than
7153             --  two gigabytes is not copied, we will worry about it then!
7154
7155             else
7156                Default_C_Record_Mechanism := Mechanism_Type'Last;
7157             end if;
7158          end C_Pass_By_Copy;
7159
7160          -----------
7161          -- Check --
7162          -----------
7163
7164          --  pragma Check ([Name    =>] IDENTIFIER,
7165          --                [Check   =>] Boolean_EXPRESSION
7166          --              [,[Message =>] String_EXPRESSION]);
7167
7168          when Pragma_Check => Check : declare
7169             Expr : Node_Id;
7170             Eloc : Source_Ptr;
7171
7172             Check_On : Boolean;
7173             --  Set True if category of assertions referenced by Name enabled
7174
7175          begin
7176             GNAT_Pragma;
7177             Check_At_Least_N_Arguments (2);
7178             Check_At_Most_N_Arguments (3);
7179             Check_Optional_Identifier (Arg1, Name_Name);
7180             Check_Optional_Identifier (Arg2, Name_Check);
7181
7182             if Arg_Count = 3 then
7183                Check_Optional_Identifier (Arg3, Name_Message);
7184                Analyze_And_Resolve (Get_Pragma_Arg (Arg3), Standard_String);
7185             end if;
7186
7187             Check_Arg_Is_Identifier (Arg1);
7188
7189             --  Completely ignore if disabled
7190
7191             if Check_Disabled (Chars (Get_Pragma_Arg (Arg1))) then
7192                Rewrite (N, Make_Null_Statement (Loc));
7193                Analyze (N);
7194                return;
7195             end if;
7196
7197             --  Indicate if pragma is enabled. The Original_Node reference here
7198             --  is to deal with pragma Assert rewritten as a Check pragma.
7199
7200             Check_On := Check_Enabled (Chars (Get_Pragma_Arg (Arg1)));
7201
7202             if Check_On then
7203                Set_SCO_Pragma_Enabled (Loc);
7204             end if;
7205
7206             --  If expansion is active and the check is not enabled then we
7207             --  rewrite the Check as:
7208
7209             --    if False and then condition then
7210             --       null;
7211             --    end if;
7212
7213             --  The reason we do this rewriting during semantic analysis rather
7214             --  than as part of normal expansion is that we cannot analyze and
7215             --  expand the code for the boolean expression directly, or it may
7216             --  cause insertion of actions that would escape the attempt to
7217             --  suppress the check code.
7218
7219             --  Note that the Sloc for the if statement corresponds to the
7220             --  argument condition, not the pragma itself. The reason for this
7221             --  is that we may generate a warning if the condition is False at
7222             --  compile time, and we do not want to delete this warning when we
7223             --  delete the if statement.
7224
7225             Expr := Get_Pragma_Arg (Arg2);
7226
7227             if Expander_Active and then not Check_On then
7228                Eloc := Sloc (Expr);
7229
7230                Rewrite (N,
7231                  Make_If_Statement (Eloc,
7232                    Condition =>
7233                      Make_And_Then (Eloc,
7234                        Left_Opnd  => New_Occurrence_Of (Standard_False, Eloc),
7235                        Right_Opnd => Expr),
7236                    Then_Statements => New_List (
7237                      Make_Null_Statement (Eloc))));
7238
7239                Analyze (N);
7240
7241             --  Check is active
7242
7243             else
7244                Analyze_And_Resolve (Expr, Any_Boolean);
7245             end if;
7246          end Check;
7247
7248          ----------------
7249          -- Check_Name --
7250          ----------------
7251
7252          --  pragma Check_Name (check_IDENTIFIER);
7253
7254          when Pragma_Check_Name =>
7255             Check_No_Identifiers;
7256             GNAT_Pragma;
7257             Check_Valid_Configuration_Pragma;
7258             Check_Arg_Count (1);
7259             Check_Arg_Is_Identifier (Arg1);
7260
7261             declare
7262                Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
7263
7264             begin
7265                for J in Check_Names.First .. Check_Names.Last loop
7266                   if Check_Names.Table (J) = Nam then
7267                      return;
7268                   end if;
7269                end loop;
7270
7271                Check_Names.Append (Nam);
7272             end;
7273
7274          ------------------
7275          -- Check_Policy --
7276          ------------------
7277
7278          --  pragma Check_Policy (
7279          --    [Name   =>] IDENTIFIER,
7280          --    [Policy =>] POLICY_IDENTIFIER);
7281
7282          --  POLICY_IDENTIFIER ::= ON | OFF | CHECK | DISABLE | IGNORE
7283
7284          --  Note: this is a configuration pragma, but it is allowed to appear
7285          --  anywhere else.
7286
7287          when Pragma_Check_Policy =>
7288             GNAT_Pragma;
7289             Check_Arg_Count (2);
7290             Check_Optional_Identifier (Arg1, Name_Name);
7291             Check_Optional_Identifier (Arg2, Name_Policy);
7292             Check_Arg_Is_One_Of
7293               (Arg2, Name_On, Name_Off, Name_Check, Name_Disable, Name_Ignore);
7294
7295             --  A Check_Policy pragma can appear either as a configuration
7296             --  pragma, or in a declarative part or a package spec (see RM
7297             --  11.5(5) for rules for Suppress/Unsuppress which are also
7298             --  followed for Check_Policy).
7299
7300             if not Is_Configuration_Pragma then
7301                Check_Is_In_Decl_Part_Or_Package_Spec;
7302             end if;
7303
7304             Set_Next_Pragma (N, Opt.Check_Policy_List);
7305             Opt.Check_Policy_List := N;
7306
7307          ---------------------
7308          -- CIL_Constructor --
7309          ---------------------
7310
7311          --  pragma CIL_Constructor ([Entity =>] LOCAL_NAME);
7312
7313          --  Processing for this pragma is shared with Java_Constructor
7314
7315          -------------
7316          -- Comment --
7317          -------------
7318
7319          --  pragma Comment (static_string_EXPRESSION)
7320
7321          --  Processing for pragma Comment shares the circuitry for pragma
7322          --  Ident. The only differences are that Ident enforces a limit of 31
7323          --  characters on its argument, and also enforces limitations on
7324          --  placement for DEC compatibility. Pragma Comment shares neither of
7325          --  these restrictions.
7326
7327          -------------------
7328          -- Common_Object --
7329          -------------------
7330
7331          --  pragma Common_Object (
7332          --        [Internal =>] LOCAL_NAME
7333          --     [, [External =>] EXTERNAL_SYMBOL]
7334          --     [, [Size     =>] EXTERNAL_SYMBOL]);
7335
7336          --  Processing for this pragma is shared with Psect_Object
7337
7338          ------------------------
7339          -- Compile_Time_Error --
7340          ------------------------
7341
7342          --  pragma Compile_Time_Error
7343          --    (boolean_EXPRESSION, static_string_EXPRESSION);
7344
7345          when Pragma_Compile_Time_Error =>
7346             GNAT_Pragma;
7347             Process_Compile_Time_Warning_Or_Error;
7348
7349          --------------------------
7350          -- Compile_Time_Warning --
7351          --------------------------
7352
7353          --  pragma Compile_Time_Warning
7354          --    (boolean_EXPRESSION, static_string_EXPRESSION);
7355
7356          when Pragma_Compile_Time_Warning =>
7357             GNAT_Pragma;
7358             Process_Compile_Time_Warning_Or_Error;
7359
7360          -------------------
7361          -- Compiler_Unit --
7362          -------------------
7363
7364          when Pragma_Compiler_Unit =>
7365             GNAT_Pragma;
7366             Check_Arg_Count (0);
7367             Set_Is_Compiler_Unit (Get_Source_Unit (N));
7368
7369          -----------------------------
7370          -- Complete_Representation --
7371          -----------------------------
7372
7373          --  pragma Complete_Representation;
7374
7375          when Pragma_Complete_Representation =>
7376             GNAT_Pragma;
7377             Check_Arg_Count (0);
7378
7379             if Nkind (Parent (N)) /= N_Record_Representation_Clause then
7380                Error_Pragma
7381                  ("pragma & must appear within record representation clause");
7382             end if;
7383
7384          ----------------------------
7385          -- Complex_Representation --
7386          ----------------------------
7387
7388          --  pragma Complex_Representation ([Entity =>] LOCAL_NAME);
7389
7390          when Pragma_Complex_Representation => Complex_Representation : declare
7391             E_Id : Entity_Id;
7392             E    : Entity_Id;
7393             Ent  : Entity_Id;
7394
7395          begin
7396             GNAT_Pragma;
7397             Check_Arg_Count (1);
7398             Check_Optional_Identifier (Arg1, Name_Entity);
7399             Check_Arg_Is_Local_Name (Arg1);
7400             E_Id := Get_Pragma_Arg (Arg1);
7401
7402             if Etype (E_Id) = Any_Type then
7403                return;
7404             end if;
7405
7406             E := Entity (E_Id);
7407
7408             if not Is_Record_Type (E) then
7409                Error_Pragma_Arg
7410                  ("argument for pragma% must be record type", Arg1);
7411             end if;
7412
7413             Ent := First_Entity (E);
7414
7415             if No (Ent)
7416               or else No (Next_Entity (Ent))
7417               or else Present (Next_Entity (Next_Entity (Ent)))
7418               or else not Is_Floating_Point_Type (Etype (Ent))
7419               or else Etype (Ent) /= Etype (Next_Entity (Ent))
7420             then
7421                Error_Pragma_Arg
7422                  ("record for pragma% must have two fields of the same "
7423                   & "floating-point type", Arg1);
7424
7425             else
7426                Set_Has_Complex_Representation (Base_Type (E));
7427
7428                --  We need to treat the type has having a non-standard
7429                --  representation, for back-end purposes, even though in
7430                --  general a complex will have the default representation
7431                --  of a record with two real components.
7432
7433                Set_Has_Non_Standard_Rep (Base_Type (E));
7434             end if;
7435          end Complex_Representation;
7436
7437          -------------------------
7438          -- Component_Alignment --
7439          -------------------------
7440
7441          --  pragma Component_Alignment (
7442          --        [Form =>] ALIGNMENT_CHOICE
7443          --     [, [Name =>] type_LOCAL_NAME]);
7444          --
7445          --   ALIGNMENT_CHOICE ::=
7446          --     Component_Size
7447          --   | Component_Size_4
7448          --   | Storage_Unit
7449          --   | Default
7450
7451          when Pragma_Component_Alignment => Component_AlignmentP : declare
7452             Args  : Args_List (1 .. 2);
7453             Names : constant Name_List (1 .. 2) := (
7454                       Name_Form,
7455                       Name_Name);
7456
7457             Form  : Node_Id renames Args (1);
7458             Name  : Node_Id renames Args (2);
7459
7460             Atype : Component_Alignment_Kind;
7461             Typ   : Entity_Id;
7462
7463          begin
7464             GNAT_Pragma;
7465             Gather_Associations (Names, Args);
7466
7467             if No (Form) then
7468                Error_Pragma ("missing Form argument for pragma%");
7469             end if;
7470
7471             Check_Arg_Is_Identifier (Form);
7472
7473             --  Get proper alignment, note that Default = Component_Size on all
7474             --  machines we have so far, and we want to set this value rather
7475             --  than the default value to indicate that it has been explicitly
7476             --  set (and thus will not get overridden by the default component
7477             --  alignment for the current scope)
7478
7479             if Chars (Form) = Name_Component_Size then
7480                Atype := Calign_Component_Size;
7481
7482             elsif Chars (Form) = Name_Component_Size_4 then
7483                Atype := Calign_Component_Size_4;
7484
7485             elsif Chars (Form) = Name_Default then
7486                Atype := Calign_Component_Size;
7487
7488             elsif Chars (Form) = Name_Storage_Unit then
7489                Atype := Calign_Storage_Unit;
7490
7491             else
7492                Error_Pragma_Arg
7493                  ("invalid Form parameter for pragma%", Form);
7494             end if;
7495
7496             --  Case with no name, supplied, affects scope table entry
7497
7498             if No (Name) then
7499                Scope_Stack.Table
7500                  (Scope_Stack.Last).Component_Alignment_Default := Atype;
7501
7502             --  Case of name supplied
7503
7504             else
7505                Check_Arg_Is_Local_Name (Name);
7506                Find_Type (Name);
7507                Typ := Entity (Name);
7508
7509                if Typ = Any_Type
7510                  or else Rep_Item_Too_Early (Typ, N)
7511                then
7512                   return;
7513                else
7514                   Typ := Underlying_Type (Typ);
7515                end if;
7516
7517                if not Is_Record_Type (Typ)
7518                  and then not Is_Array_Type (Typ)
7519                then
7520                   Error_Pragma_Arg
7521                     ("Name parameter of pragma% must identify record or " &
7522                      "array type", Name);
7523                end if;
7524
7525                --  An explicit Component_Alignment pragma overrides an
7526                --  implicit pragma Pack, but not an explicit one.
7527
7528                if not Has_Pragma_Pack (Base_Type (Typ)) then
7529                   Set_Is_Packed (Base_Type (Typ), False);
7530                   Set_Component_Alignment (Base_Type (Typ), Atype);
7531                end if;
7532             end if;
7533          end Component_AlignmentP;
7534
7535          ----------------
7536          -- Controlled --
7537          ----------------
7538
7539          --  pragma Controlled (first_subtype_LOCAL_NAME);
7540
7541          when Pragma_Controlled => Controlled : declare
7542             Arg : Node_Id;
7543
7544          begin
7545             Check_No_Identifiers;
7546             Check_Arg_Count (1);
7547             Check_Arg_Is_Local_Name (Arg1);
7548             Arg := Get_Pragma_Arg (Arg1);
7549
7550             if not Is_Entity_Name (Arg)
7551               or else not Is_Access_Type (Entity (Arg))
7552             then
7553                Error_Pragma_Arg ("pragma% requires access type", Arg1);
7554             else
7555                Set_Has_Pragma_Controlled (Base_Type (Entity (Arg)));
7556             end if;
7557          end Controlled;
7558
7559          ----------------
7560          -- Convention --
7561          ----------------
7562
7563          --  pragma Convention ([Convention =>] convention_IDENTIFIER,
7564          --    [Entity =>] LOCAL_NAME);
7565
7566          when Pragma_Convention => Convention : declare
7567             C : Convention_Id;
7568             E : Entity_Id;
7569             pragma Warnings (Off, C);
7570             pragma Warnings (Off, E);
7571          begin
7572             Check_Arg_Order ((Name_Convention, Name_Entity));
7573             Check_Ada_83_Warning;
7574             Check_Arg_Count (2);
7575             Process_Convention (C, E);
7576          end Convention;
7577
7578          ---------------------------
7579          -- Convention_Identifier --
7580          ---------------------------
7581
7582          --  pragma Convention_Identifier ([Name =>] IDENTIFIER,
7583          --    [Convention =>] convention_IDENTIFIER);
7584
7585          when Pragma_Convention_Identifier => Convention_Identifier : declare
7586             Idnam : Name_Id;
7587             Cname : Name_Id;
7588
7589          begin
7590             GNAT_Pragma;
7591             Check_Arg_Order ((Name_Name, Name_Convention));
7592             Check_Arg_Count (2);
7593             Check_Optional_Identifier (Arg1, Name_Name);
7594             Check_Optional_Identifier (Arg2, Name_Convention);
7595             Check_Arg_Is_Identifier (Arg1);
7596             Check_Arg_Is_Identifier (Arg2);
7597             Idnam := Chars (Get_Pragma_Arg (Arg1));
7598             Cname := Chars (Get_Pragma_Arg (Arg2));
7599
7600             if Is_Convention_Name (Cname) then
7601                Record_Convention_Identifier
7602                  (Idnam, Get_Convention_Id (Cname));
7603             else
7604                Error_Pragma_Arg
7605                  ("second arg for % pragma must be convention", Arg2);
7606             end if;
7607          end Convention_Identifier;
7608
7609          ---------------
7610          -- CPP_Class --
7611          ---------------
7612
7613          --  pragma CPP_Class ([Entity =>] local_NAME)
7614
7615          when Pragma_CPP_Class => CPP_Class : declare
7616             Arg : Node_Id;
7617             Typ : Entity_Id;
7618
7619          begin
7620             if Warn_On_Obsolescent_Feature then
7621                Error_Msg_N
7622                  ("'G'N'A'T pragma cpp'_class is now obsolete; replace it" &
7623                   " by pragma import?", N);
7624             end if;
7625
7626             GNAT_Pragma;
7627             Check_Arg_Count (1);
7628             Check_Optional_Identifier (Arg1, Name_Entity);
7629             Check_Arg_Is_Local_Name (Arg1);
7630
7631             Arg := Get_Pragma_Arg (Arg1);
7632             Analyze (Arg);
7633
7634             if Etype (Arg) = Any_Type then
7635                return;
7636             end if;
7637
7638             if not Is_Entity_Name (Arg)
7639               or else not Is_Type (Entity (Arg))
7640             then
7641                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
7642             end if;
7643
7644             Typ := Entity (Arg);
7645
7646             if not Is_Tagged_Type (Typ) then
7647                Error_Pragma_Arg ("pragma% applicable to tagged types ", Arg1);
7648             end if;
7649
7650             --  Types treated as CPP classes must be declared limited (note:
7651             --  this used to be a warning but there is no real benefit to it
7652             --  since we did effectively intend to treat the type as limited
7653             --  anyway).
7654
7655             if not Is_Limited_Type (Typ) then
7656                Error_Msg_N
7657                  ("imported 'C'P'P type must be limited",
7658                   Get_Pragma_Arg (Arg1));
7659             end if;
7660
7661             Set_Is_CPP_Class (Typ);
7662             Set_Convention (Typ, Convention_CPP);
7663
7664             --  Imported CPP types must not have discriminants (because C++
7665             --  classes do not have discriminants).
7666
7667             if Has_Discriminants (Typ) then
7668                Error_Msg_N
7669                  ("imported 'C'P'P type cannot have discriminants",
7670                   First (Discriminant_Specifications
7671                           (Declaration_Node (Typ))));
7672             end if;
7673
7674             --  Components of imported CPP types must not have default
7675             --  expressions because the constructor (if any) is in the
7676             --  C++ side.
7677
7678             if Is_Incomplete_Or_Private_Type (Typ)
7679               and then No (Underlying_Type (Typ))
7680             then
7681                --  It should be an error to apply pragma CPP to a private
7682                --  type if the underlying type is not visible (as it is
7683                --  for any representation item). For now, for backward
7684                --  compatibility we do nothing but we cannot check components
7685                --  because they are not available at this stage. All this code
7686                --  will be removed when we cleanup this obsolete GNAT pragma???
7687
7688                null;
7689
7690             else
7691                declare
7692                   Tdef  : constant Node_Id :=
7693                             Type_Definition (Declaration_Node (Typ));
7694                   Clist : Node_Id;
7695                   Comp  : Node_Id;
7696
7697                begin
7698                   if Nkind (Tdef) = N_Record_Definition then
7699                      Clist := Component_List (Tdef);
7700                   else
7701                      pragma Assert (Nkind (Tdef) = N_Derived_Type_Definition);
7702                      Clist := Component_List (Record_Extension_Part (Tdef));
7703                   end if;
7704
7705                   if Present (Clist) then
7706                      Comp := First (Component_Items (Clist));
7707                      while Present (Comp) loop
7708                         if Present (Expression (Comp)) then
7709                            Error_Msg_N
7710                              ("component of imported 'C'P'P type cannot have" &
7711                               " default expression", Expression (Comp));
7712                         end if;
7713
7714                         Next (Comp);
7715                      end loop;
7716                   end if;
7717                end;
7718             end if;
7719          end CPP_Class;
7720
7721          ---------------------
7722          -- CPP_Constructor --
7723          ---------------------
7724
7725          --  pragma CPP_Constructor ([Entity =>] LOCAL_NAME
7726          --    [, [External_Name =>] static_string_EXPRESSION ]
7727          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
7728
7729          when Pragma_CPP_Constructor => CPP_Constructor : declare
7730             Elmt    : Elmt_Id;
7731             Id      : Entity_Id;
7732             Def_Id  : Entity_Id;
7733             Tag_Typ : Entity_Id;
7734
7735          begin
7736             GNAT_Pragma;
7737             Check_At_Least_N_Arguments (1);
7738             Check_At_Most_N_Arguments (3);
7739             Check_Optional_Identifier (Arg1, Name_Entity);
7740             Check_Arg_Is_Local_Name (Arg1);
7741
7742             Id := Get_Pragma_Arg (Arg1);
7743             Find_Program_Unit_Name (Id);
7744
7745             --  If we did not find the name, we are done
7746
7747             if Etype (Id) = Any_Type then
7748                return;
7749             end if;
7750
7751             Def_Id := Entity (Id);
7752
7753             --  Check if already defined as constructor
7754
7755             if Is_Constructor (Def_Id) then
7756                Error_Msg_N
7757                  ("?duplicate argument for pragma 'C'P'P_Constructor", Arg1);
7758                return;
7759             end if;
7760
7761             if Ekind (Def_Id) = E_Function
7762               and then (Is_CPP_Class (Etype (Def_Id))
7763                          or else (Is_Class_Wide_Type (Etype (Def_Id))
7764                                    and then
7765                                   Is_CPP_Class (Root_Type (Etype (Def_Id)))))
7766             then
7767                if Arg_Count >= 2 then
7768                   Set_Imported (Def_Id);
7769                   Set_Is_Public (Def_Id);
7770                   Process_Interface_Name (Def_Id, Arg2, Arg3);
7771                end if;
7772
7773                Set_Has_Completion (Def_Id);
7774                Set_Is_Constructor (Def_Id);
7775
7776                --  Imported C++ constructors are not dispatching primitives
7777                --  because in C++ they don't have a dispatch table slot.
7778                --  However, in Ada the constructor has the profile of a
7779                --  function that returns a tagged type and therefore it has
7780                --  been treated as a primitive operation during semantic
7781                --  analysis. We now remove it from the list of primitive
7782                --  operations of the type.
7783
7784                if Is_Tagged_Type (Etype (Def_Id))
7785                  and then not Is_Class_Wide_Type (Etype (Def_Id))
7786                then
7787                   pragma Assert (Is_Dispatching_Operation (Def_Id));
7788                   Tag_Typ := Etype (Def_Id);
7789
7790                   Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
7791                   while Present (Elmt) and then Node (Elmt) /= Def_Id loop
7792                      Next_Elmt (Elmt);
7793                   end loop;
7794
7795                   Remove_Elmt (Primitive_Operations (Tag_Typ), Elmt);
7796                   Set_Is_Dispatching_Operation (Def_Id, False);
7797                end if;
7798
7799                --  For backward compatibility, if the constructor returns a
7800                --  class wide type, and we internally change the return type to
7801                --  the corresponding root type.
7802
7803                if Is_Class_Wide_Type (Etype (Def_Id)) then
7804                   Set_Etype (Def_Id, Root_Type (Etype (Def_Id)));
7805                end if;
7806             else
7807                Error_Pragma_Arg
7808                  ("pragma% requires function returning a 'C'P'P_Class type",
7809                    Arg1);
7810             end if;
7811          end CPP_Constructor;
7812
7813          -----------------
7814          -- CPP_Virtual --
7815          -----------------
7816
7817          when Pragma_CPP_Virtual => CPP_Virtual : declare
7818          begin
7819             GNAT_Pragma;
7820
7821             if Warn_On_Obsolescent_Feature then
7822                Error_Msg_N
7823                  ("'G'N'A'T pragma cpp'_virtual is now obsolete and has " &
7824                   "no effect?", N);
7825             end if;
7826          end CPP_Virtual;
7827
7828          ----------------
7829          -- CPP_Vtable --
7830          ----------------
7831
7832          when Pragma_CPP_Vtable => CPP_Vtable : declare
7833          begin
7834             GNAT_Pragma;
7835
7836             if Warn_On_Obsolescent_Feature then
7837                Error_Msg_N
7838                  ("'G'N'A'T pragma cpp'_vtable is now obsolete and has " &
7839                   "no effect?", N);
7840             end if;
7841          end CPP_Vtable;
7842
7843          ---------
7844          -- CPU --
7845          ---------
7846
7847          --  pragma CPU (EXPRESSION);
7848
7849          when Pragma_CPU => CPU : declare
7850             P   : constant Node_Id := Parent (N);
7851             Arg : Node_Id;
7852
7853          begin
7854             Ada_2012_Pragma;
7855             Check_No_Identifiers;
7856             Check_Arg_Count (1);
7857
7858             --  Subprogram case
7859
7860             if Nkind (P) = N_Subprogram_Body then
7861                Check_In_Main_Program;
7862
7863                Arg := Get_Pragma_Arg (Arg1);
7864                Analyze_And_Resolve (Arg, Any_Integer);
7865
7866                --  Must be static
7867
7868                if not Is_Static_Expression (Arg) then
7869                   Flag_Non_Static_Expr
7870                     ("main subprogram affinity is not static!", Arg);
7871                   raise Pragma_Exit;
7872
7873                --  If constraint error, then we already signalled an error
7874
7875                elsif Raises_Constraint_Error (Arg) then
7876                   null;
7877
7878                --  Otherwise check in range
7879
7880                else
7881                   declare
7882                      CPU_Id : constant Entity_Id := RTE (RE_CPU_Range);
7883                      --  This is the entity System.Multiprocessors.CPU_Range;
7884
7885                      Val : constant Uint := Expr_Value (Arg);
7886
7887                   begin
7888                      if Val < Expr_Value (Type_Low_Bound (CPU_Id))
7889                           or else
7890                         Val > Expr_Value (Type_High_Bound (CPU_Id))
7891                      then
7892                         Error_Pragma_Arg
7893                           ("main subprogram CPU is out of range", Arg1);
7894                      end if;
7895                   end;
7896                end if;
7897
7898                Set_Main_CPU
7899                     (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
7900
7901             --  Task case
7902
7903             elsif Nkind (P) = N_Task_Definition then
7904                Arg := Get_Pragma_Arg (Arg1);
7905
7906                --  The expression must be analyzed in the special manner
7907                --  described in "Handling of Default and Per-Object
7908                --  Expressions" in sem.ads.
7909
7910                Preanalyze_Spec_Expression (Arg, RTE (RE_CPU_Range));
7911
7912             --  Anything else is incorrect
7913
7914             else
7915                Pragma_Misplaced;
7916             end if;
7917
7918             if Has_Pragma_CPU (P) then
7919                Error_Pragma ("duplicate pragma% not allowed");
7920             else
7921                Set_Has_Pragma_CPU (P, True);
7922
7923                if Nkind (P) = N_Task_Definition then
7924                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
7925                end if;
7926             end if;
7927          end CPU;
7928
7929          -----------
7930          -- Debug --
7931          -----------
7932
7933          --  pragma Debug ([boolean_EXPRESSION,] PROCEDURE_CALL_STATEMENT);
7934
7935          when Pragma_Debug => Debug : declare
7936             Cond : Node_Id;
7937             Call : Node_Id;
7938
7939          begin
7940             GNAT_Pragma;
7941
7942             --  Skip analysis if disabled
7943
7944             if Debug_Pragmas_Disabled then
7945                Rewrite (N, Make_Null_Statement (Loc));
7946                Analyze (N);
7947                return;
7948             end if;
7949
7950             Cond :=
7951               New_Occurrence_Of
7952                 (Boolean_Literals (Debug_Pragmas_Enabled and Expander_Active),
7953                  Loc);
7954
7955             if Debug_Pragmas_Enabled then
7956                Set_SCO_Pragma_Enabled (Loc);
7957             end if;
7958
7959             if Arg_Count = 2 then
7960                Cond :=
7961                  Make_And_Then (Loc,
7962                    Left_Opnd  => Relocate_Node (Cond),
7963                    Right_Opnd => Get_Pragma_Arg (Arg1));
7964                Call := Get_Pragma_Arg (Arg2);
7965             else
7966                Call := Get_Pragma_Arg (Arg1);
7967             end if;
7968
7969             if Nkind_In (Call,
7970                  N_Indexed_Component,
7971                  N_Function_Call,
7972                  N_Identifier,
7973                  N_Expanded_Name,
7974                  N_Selected_Component)
7975             then
7976                --  If this pragma Debug comes from source, its argument was
7977                --  parsed as a name form (which is syntactically identical).
7978                --  In a generic context a parameterless call will be left as
7979                --  an expanded name (if global) or selected_component if local.
7980                --  Change it to a procedure call statement now.
7981
7982                Change_Name_To_Procedure_Call_Statement (Call);
7983
7984             elsif Nkind (Call) = N_Procedure_Call_Statement then
7985
7986                --  Already in the form of a procedure call statement: nothing
7987                --  to do (could happen in case of an internally generated
7988                --  pragma Debug).
7989
7990                null;
7991
7992             else
7993                --  All other cases: diagnose error
7994
7995                Error_Msg
7996                  ("argument of pragma ""Debug"" is not procedure call",
7997                   Sloc (Call));
7998                return;
7999             end if;
8000
8001             --  Rewrite into a conditional with an appropriate condition. We
8002             --  wrap the procedure call in a block so that overhead from e.g.
8003             --  use of the secondary stack does not generate execution overhead
8004             --  for suppressed conditions.
8005
8006             --  Normally the analysis that follows will freeze the subprogram
8007             --  being called. However, if the call is to a null procedure,
8008             --  we want to freeze it before creating the block, because the
8009             --  analysis that follows may be done with expansion disabled, in
8010             --  which case the body will not be generated, leading to spurious
8011             --  errors.
8012
8013             if Nkind (Call) = N_Procedure_Call_Statement
8014               and then Is_Entity_Name (Name (Call))
8015             then
8016                Analyze (Name (Call));
8017                Freeze_Before (N, Entity (Name (Call)));
8018             end if;
8019
8020             Rewrite (N, Make_Implicit_If_Statement (N,
8021               Condition => Cond,
8022                  Then_Statements => New_List (
8023                    Make_Block_Statement (Loc,
8024                      Handled_Statement_Sequence =>
8025                        Make_Handled_Sequence_Of_Statements (Loc,
8026                          Statements => New_List (Relocate_Node (Call)))))));
8027             Analyze (N);
8028          end Debug;
8029
8030          ------------------
8031          -- Debug_Policy --
8032          ------------------
8033
8034          --  pragma Debug_Policy (Check | Ignore)
8035
8036          when Pragma_Debug_Policy =>
8037             GNAT_Pragma;
8038             Check_Arg_Count (1);
8039             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Disable, Name_Ignore);
8040             Debug_Pragmas_Enabled :=
8041               Chars (Get_Pragma_Arg (Arg1)) = Name_Check;
8042             Debug_Pragmas_Disabled :=
8043               Chars (Get_Pragma_Arg (Arg1)) = Name_Disable;
8044
8045          ---------------------
8046          -- Detect_Blocking --
8047          ---------------------
8048
8049          --  pragma Detect_Blocking;
8050
8051          when Pragma_Detect_Blocking =>
8052             Ada_2005_Pragma;
8053             Check_Arg_Count (0);
8054             Check_Valid_Configuration_Pragma;
8055             Detect_Blocking := True;
8056
8057          --------------------------
8058          -- Default_Storage_Pool --
8059          --------------------------
8060
8061          --  pragma Default_Storage_Pool (storage_pool_NAME | null);
8062
8063          when Pragma_Default_Storage_Pool =>
8064             Ada_2012_Pragma;
8065             Check_Arg_Count (1);
8066
8067             --  Default_Storage_Pool can appear as a configuration pragma, or
8068             --  in a declarative part or a package spec.
8069
8070             if not Is_Configuration_Pragma then
8071                Check_Is_In_Decl_Part_Or_Package_Spec;
8072             end if;
8073
8074             --  Case of Default_Storage_Pool (null);
8075
8076             if Nkind (Expression (Arg1)) = N_Null then
8077                Analyze (Expression (Arg1));
8078
8079                --  This is an odd case, this is not really an expression, so
8080                --  we don't have a type for it. So just set the type to Empty.
8081
8082                Set_Etype (Expression (Arg1), Empty);
8083
8084             --  Case of Default_Storage_Pool (storage_pool_NAME);
8085
8086             else
8087                --  If it's a configuration pragma, then the only allowed
8088                --  argument is "null".
8089
8090                if Is_Configuration_Pragma then
8091                   Error_Pragma_Arg ("NULL expected", Arg1);
8092                end if;
8093
8094                --  The expected type for a non-"null" argument is
8095                --  Root_Storage_Pool'Class.
8096
8097                Analyze_And_Resolve
8098                  (Get_Pragma_Arg (Arg1),
8099                   Typ => Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
8100             end if;
8101
8102             --  Finally, record the pool name (or null). Freeze.Freeze_Entity
8103             --  for an access type will use this information to set the
8104             --  appropriate attributes of the access type.
8105
8106             Default_Pool := Expression (Arg1);
8107
8108          ------------------------------------
8109          -- Disable_Atomic_Synchronization --
8110          ------------------------------------
8111
8112          --  pragma Disable_Atomic_Synchronization [(Entity)];
8113
8114          when Pragma_Disable_Atomic_Synchronization =>
8115             Process_Disable_Enable_Atomic_Sync (Name_Suppress);
8116
8117          -------------------
8118          -- Discard_Names --
8119          -------------------
8120
8121          --  pragma Discard_Names [([On =>] LOCAL_NAME)];
8122
8123          when Pragma_Discard_Names => Discard_Names : declare
8124             E    : Entity_Id;
8125             E_Id : Entity_Id;
8126
8127          begin
8128             Check_Ada_83_Warning;
8129
8130             --  Deal with configuration pragma case
8131
8132             if Arg_Count = 0 and then Is_Configuration_Pragma then
8133                Global_Discard_Names := True;
8134                return;
8135
8136             --  Otherwise, check correct appropriate context
8137
8138             else
8139                Check_Is_In_Decl_Part_Or_Package_Spec;
8140
8141                if Arg_Count = 0 then
8142
8143                   --  If there is no parameter, then from now on this pragma
8144                   --  applies to any enumeration, exception or tagged type
8145                   --  defined in the current declarative part, and recursively
8146                   --  to any nested scope.
8147
8148                   Set_Discard_Names (Current_Scope);
8149                   return;
8150
8151                else
8152                   Check_Arg_Count (1);
8153                   Check_Optional_Identifier (Arg1, Name_On);
8154                   Check_Arg_Is_Local_Name (Arg1);
8155
8156                   E_Id := Get_Pragma_Arg (Arg1);
8157
8158                   if Etype (E_Id) = Any_Type then
8159                      return;
8160                   else
8161                      E := Entity (E_Id);
8162                   end if;
8163
8164                   if (Is_First_Subtype (E)
8165                       and then
8166                         (Is_Enumeration_Type (E) or else Is_Tagged_Type (E)))
8167                     or else Ekind (E) = E_Exception
8168                   then
8169                      Set_Discard_Names (E);
8170                   else
8171                      Error_Pragma_Arg
8172                        ("inappropriate entity for pragma%", Arg1);
8173                   end if;
8174
8175                end if;
8176             end if;
8177          end Discard_Names;
8178
8179          ------------------------
8180          -- Dispatching_Domain --
8181          ------------------------
8182
8183          --  pragma Dispatching_Domain (EXPRESSION);
8184
8185          when Pragma_Dispatching_Domain => Dispatching_Domain : declare
8186             P   : constant Node_Id := Parent (N);
8187             Arg : Node_Id;
8188
8189          begin
8190             Ada_2012_Pragma;
8191             Check_No_Identifiers;
8192             Check_Arg_Count (1);
8193
8194             --  This pragma is born obsolete, but not the aspect
8195
8196             if not From_Aspect_Specification (N) then
8197                Check_Restriction
8198                  (No_Obsolescent_Features, Pragma_Identifier (N));
8199             end if;
8200
8201             if Nkind (P) = N_Task_Definition then
8202                Arg := Get_Pragma_Arg (Arg1);
8203
8204                --  The expression must be analyzed in the special manner
8205                --  described in "Handling of Default and Per-Object
8206                --  Expressions" in sem.ads.
8207
8208                Preanalyze_Spec_Expression (Arg, RTE (RE_Dispatching_Domain));
8209
8210             --  Anything else is incorrect
8211
8212             else
8213                Pragma_Misplaced;
8214             end if;
8215
8216             if Has_Pragma_Dispatching_Domain (P) then
8217                Error_Pragma ("duplicate pragma% not allowed");
8218             else
8219                Set_Has_Pragma_Dispatching_Domain (P, True);
8220
8221                if Nkind (P) = N_Task_Definition then
8222                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
8223                end if;
8224             end if;
8225          end Dispatching_Domain;
8226
8227          ---------------
8228          -- Elaborate --
8229          ---------------
8230
8231          --  pragma Elaborate (library_unit_NAME {, library_unit_NAME});
8232
8233          when Pragma_Elaborate => Elaborate : declare
8234             Arg   : Node_Id;
8235             Citem : Node_Id;
8236
8237          begin
8238             --  Pragma must be in context items list of a compilation unit
8239
8240             if not Is_In_Context_Clause then
8241                Pragma_Misplaced;
8242             end if;
8243
8244             --  Must be at least one argument
8245
8246             if Arg_Count = 0 then
8247                Error_Pragma ("pragma% requires at least one argument");
8248             end if;
8249
8250             --  In Ada 83 mode, there can be no items following it in the
8251             --  context list except other pragmas and implicit with clauses
8252             --  (e.g. those added by use of Rtsfind). In Ada 95 mode, this
8253             --  placement rule does not apply.
8254
8255             if Ada_Version = Ada_83 and then Comes_From_Source (N) then
8256                Citem := Next (N);
8257                while Present (Citem) loop
8258                   if Nkind (Citem) = N_Pragma
8259                     or else (Nkind (Citem) = N_With_Clause
8260                               and then Implicit_With (Citem))
8261                   then
8262                      null;
8263                   else
8264                      Error_Pragma
8265                        ("(Ada 83) pragma% must be at end of context clause");
8266                   end if;
8267
8268                   Next (Citem);
8269                end loop;
8270             end if;
8271
8272             --  Finally, the arguments must all be units mentioned in a with
8273             --  clause in the same context clause. Note we already checked (in
8274             --  Par.Prag) that the arguments are all identifiers or selected
8275             --  components.
8276
8277             Arg := Arg1;
8278             Outer : while Present (Arg) loop
8279                Citem := First (List_Containing (N));
8280                Inner : while Citem /= N loop
8281                   if Nkind (Citem) = N_With_Clause
8282                     and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
8283                   then
8284                      Set_Elaborate_Present (Citem, True);
8285                      Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
8286                      Generate_Reference (Entity (Name (Citem)), Citem);
8287
8288                      --  With the pragma present, elaboration calls on
8289                      --  subprograms from the named unit need no further
8290                      --  checks, as long as the pragma appears in the current
8291                      --  compilation unit. If the pragma appears in some unit
8292                      --  in the context, there might still be a need for an
8293                      --  Elaborate_All_Desirable from the current compilation
8294                      --  to the named unit, so we keep the check enabled.
8295
8296                      if In_Extended_Main_Source_Unit (N) then
8297                         Set_Suppress_Elaboration_Warnings
8298                           (Entity (Name (Citem)));
8299                      end if;
8300
8301                      exit Inner;
8302                   end if;
8303
8304                   Next (Citem);
8305                end loop Inner;
8306
8307                if Citem = N then
8308                   Error_Pragma_Arg
8309                     ("argument of pragma% is not withed unit", Arg);
8310                end if;
8311
8312                Next (Arg);
8313             end loop Outer;
8314
8315             --  Give a warning if operating in static mode with -gnatwl
8316             --  (elaboration warnings enabled) switch set.
8317
8318             if Elab_Warnings and not Dynamic_Elaboration_Checks then
8319                Error_Msg_N
8320                  ("?use of pragma Elaborate may not be safe", N);
8321                Error_Msg_N
8322                  ("?use pragma Elaborate_All instead if possible", N);
8323             end if;
8324          end Elaborate;
8325
8326          -------------------
8327          -- Elaborate_All --
8328          -------------------
8329
8330          --  pragma Elaborate_All (library_unit_NAME {, library_unit_NAME});
8331
8332          when Pragma_Elaborate_All => Elaborate_All : declare
8333             Arg   : Node_Id;
8334             Citem : Node_Id;
8335
8336          begin
8337             Check_Ada_83_Warning;
8338
8339             --  Pragma must be in context items list of a compilation unit
8340
8341             if not Is_In_Context_Clause then
8342                Pragma_Misplaced;
8343             end if;
8344
8345             --  Must be at least one argument
8346
8347             if Arg_Count = 0 then
8348                Error_Pragma ("pragma% requires at least one argument");
8349             end if;
8350
8351             --  Note: unlike pragma Elaborate, pragma Elaborate_All does not
8352             --  have to appear at the end of the context clause, but may
8353             --  appear mixed in with other items, even in Ada 83 mode.
8354
8355             --  Final check: the arguments must all be units mentioned in
8356             --  a with clause in the same context clause. Note that we
8357             --  already checked (in Par.Prag) that all the arguments are
8358             --  either identifiers or selected components.
8359
8360             Arg := Arg1;
8361             Outr : while Present (Arg) loop
8362                Citem := First (List_Containing (N));
8363                Innr : while Citem /= N loop
8364                   if Nkind (Citem) = N_With_Clause
8365                     and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
8366                   then
8367                      Set_Elaborate_All_Present (Citem, True);
8368                      Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
8369
8370                      --  Suppress warnings and elaboration checks on the named
8371                      --  unit if the pragma is in the current compilation, as
8372                      --  for pragma Elaborate.
8373
8374                      if In_Extended_Main_Source_Unit (N) then
8375                         Set_Suppress_Elaboration_Warnings
8376                           (Entity (Name (Citem)));
8377                      end if;
8378                      exit Innr;
8379                   end if;
8380
8381                   Next (Citem);
8382                end loop Innr;
8383
8384                if Citem = N then
8385                   Set_Error_Posted (N);
8386                   Error_Pragma_Arg
8387                     ("argument of pragma% is not withed unit", Arg);
8388                end if;
8389
8390                Next (Arg);
8391             end loop Outr;
8392          end Elaborate_All;
8393
8394          --------------------
8395          -- Elaborate_Body --
8396          --------------------
8397
8398          --  pragma Elaborate_Body [( library_unit_NAME )];
8399
8400          when Pragma_Elaborate_Body => Elaborate_Body : declare
8401             Cunit_Node : Node_Id;
8402             Cunit_Ent  : Entity_Id;
8403
8404          begin
8405             Check_Ada_83_Warning;
8406             Check_Valid_Library_Unit_Pragma;
8407
8408             if Nkind (N) = N_Null_Statement then
8409                return;
8410             end if;
8411
8412             Cunit_Node := Cunit (Current_Sem_Unit);
8413             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
8414
8415             if Nkind_In (Unit (Cunit_Node), N_Package_Body,
8416                                             N_Subprogram_Body)
8417             then
8418                Error_Pragma ("pragma% must refer to a spec, not a body");
8419             else
8420                Set_Body_Required (Cunit_Node, True);
8421                Set_Has_Pragma_Elaborate_Body (Cunit_Ent);
8422
8423                --  If we are in dynamic elaboration mode, then we suppress
8424                --  elaboration warnings for the unit, since it is definitely
8425                --  fine NOT to do dynamic checks at the first level (and such
8426                --  checks will be suppressed because no elaboration boolean
8427                --  is created for Elaborate_Body packages).
8428
8429                --  But in the static model of elaboration, Elaborate_Body is
8430                --  definitely NOT good enough to ensure elaboration safety on
8431                --  its own, since the body may WITH other units that are not
8432                --  safe from an elaboration point of view, so a client must
8433                --  still do an Elaborate_All on such units.
8434
8435                --  Debug flag -gnatdD restores the old behavior of 3.13, where
8436                --  Elaborate_Body always suppressed elab warnings.
8437
8438                if Dynamic_Elaboration_Checks or Debug_Flag_DD then
8439                   Set_Suppress_Elaboration_Warnings (Cunit_Ent);
8440                end if;
8441             end if;
8442          end Elaborate_Body;
8443
8444          ------------------------
8445          -- Elaboration_Checks --
8446          ------------------------
8447
8448          --  pragma Elaboration_Checks (Static | Dynamic);
8449
8450          when Pragma_Elaboration_Checks =>
8451             GNAT_Pragma;
8452             Check_Arg_Count (1);
8453             Check_Arg_Is_One_Of (Arg1, Name_Static, Name_Dynamic);
8454             Dynamic_Elaboration_Checks :=
8455               (Chars (Get_Pragma_Arg (Arg1)) = Name_Dynamic);
8456
8457          ---------------
8458          -- Eliminate --
8459          ---------------
8460
8461          --  pragma Eliminate (
8462          --      [Unit_Name  =>] IDENTIFIER | SELECTED_COMPONENT,
8463          --    [,[Entity     =>] IDENTIFIER |
8464          --                      SELECTED_COMPONENT |
8465          --                      STRING_LITERAL]
8466          --    [,                OVERLOADING_RESOLUTION]);
8467
8468          --  OVERLOADING_RESOLUTION ::= PARAMETER_AND_RESULT_TYPE_PROFILE |
8469          --                             SOURCE_LOCATION
8470
8471          --  PARAMETER_AND_RESULT_TYPE_PROFILE ::= PROCEDURE_PROFILE |
8472          --                                        FUNCTION_PROFILE
8473
8474          --  PROCEDURE_PROFILE ::= Parameter_Types => PARAMETER_TYPES
8475
8476          --  FUNCTION_PROFILE ::= [Parameter_Types => PARAMETER_TYPES,]
8477          --                       Result_Type => result_SUBTYPE_NAME]
8478
8479          --  PARAMETER_TYPES ::= (SUBTYPE_NAME {, SUBTYPE_NAME})
8480          --  SUBTYPE_NAME    ::= STRING_LITERAL
8481
8482          --  SOURCE_LOCATION ::= Source_Location => SOURCE_TRACE
8483          --  SOURCE_TRACE    ::= STRING_LITERAL
8484
8485          when Pragma_Eliminate => Eliminate : declare
8486             Args  : Args_List (1 .. 5);
8487             Names : constant Name_List (1 .. 5) := (
8488                       Name_Unit_Name,
8489                       Name_Entity,
8490                       Name_Parameter_Types,
8491                       Name_Result_Type,
8492                       Name_Source_Location);
8493
8494             Unit_Name       : Node_Id renames Args (1);
8495             Entity          : Node_Id renames Args (2);
8496             Parameter_Types : Node_Id renames Args (3);
8497             Result_Type     : Node_Id renames Args (4);
8498             Source_Location : Node_Id renames Args (5);
8499
8500          begin
8501             GNAT_Pragma;
8502             Check_Valid_Configuration_Pragma;
8503             Gather_Associations (Names, Args);
8504
8505             if No (Unit_Name) then
8506                Error_Pragma ("missing Unit_Name argument for pragma%");
8507             end if;
8508
8509             if No (Entity)
8510               and then (Present (Parameter_Types)
8511                           or else
8512                         Present (Result_Type)
8513                           or else
8514                         Present (Source_Location))
8515             then
8516                Error_Pragma ("missing Entity argument for pragma%");
8517             end if;
8518
8519             if (Present (Parameter_Types)
8520                   or else
8521                 Present (Result_Type))
8522               and then
8523                 Present (Source_Location)
8524             then
8525                Error_Pragma
8526                  ("parameter profile and source location cannot " &
8527                   "be used together in pragma%");
8528             end if;
8529
8530             Process_Eliminate_Pragma
8531               (N,
8532                Unit_Name,
8533                Entity,
8534                Parameter_Types,
8535                Result_Type,
8536                Source_Location);
8537          end Eliminate;
8538
8539          -----------------------------------
8540          -- Enable_Atomic_Synchronization --
8541          -----------------------------------
8542
8543          --  pragma Enable_Atomic_Synchronization [(Entity)];
8544
8545          when Pragma_Enable_Atomic_Synchronization =>
8546             Process_Disable_Enable_Atomic_Sync (Name_Unsuppress);
8547
8548          ------------
8549          -- Export --
8550          ------------
8551
8552          --  pragma Export (
8553          --    [   Convention    =>] convention_IDENTIFIER,
8554          --    [   Entity        =>] local_NAME
8555          --    [, [External_Name =>] static_string_EXPRESSION ]
8556          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
8557
8558          when Pragma_Export => Export : declare
8559             C      : Convention_Id;
8560             Def_Id : Entity_Id;
8561
8562             pragma Warnings (Off, C);
8563
8564          begin
8565             Check_Ada_83_Warning;
8566             Check_Arg_Order
8567               ((Name_Convention,
8568                 Name_Entity,
8569                 Name_External_Name,
8570                 Name_Link_Name));
8571             Check_At_Least_N_Arguments (2);
8572             Check_At_Most_N_Arguments  (4);
8573             Process_Convention (C, Def_Id);
8574
8575             if Ekind (Def_Id) /= E_Constant then
8576                Note_Possible_Modification
8577                  (Get_Pragma_Arg (Arg2), Sure => False);
8578             end if;
8579
8580             Process_Interface_Name (Def_Id, Arg3, Arg4);
8581             Set_Exported (Def_Id, Arg2);
8582
8583             --  If the entity is a deferred constant, propagate the information
8584             --  to the full view, because gigi elaborates the full view only.
8585
8586             if Ekind (Def_Id) = E_Constant
8587               and then Present (Full_View (Def_Id))
8588             then
8589                declare
8590                   Id2 : constant Entity_Id := Full_View (Def_Id);
8591                begin
8592                   Set_Is_Exported    (Id2, Is_Exported          (Def_Id));
8593                   Set_First_Rep_Item (Id2, First_Rep_Item       (Def_Id));
8594                   Set_Interface_Name (Id2, Einfo.Interface_Name (Def_Id));
8595                end;
8596             end if;
8597          end Export;
8598
8599          ----------------------
8600          -- Export_Exception --
8601          ----------------------
8602
8603          --  pragma Export_Exception (
8604          --        [Internal         =>] LOCAL_NAME
8605          --     [, [External         =>] EXTERNAL_SYMBOL]
8606          --     [, [Form     =>] Ada | VMS]
8607          --     [, [Code     =>] static_integer_EXPRESSION]);
8608
8609          when Pragma_Export_Exception => Export_Exception : declare
8610             Args  : Args_List (1 .. 4);
8611             Names : constant Name_List (1 .. 4) := (
8612                       Name_Internal,
8613                       Name_External,
8614                       Name_Form,
8615                       Name_Code);
8616
8617             Internal : Node_Id renames Args (1);
8618             External : Node_Id renames Args (2);
8619             Form     : Node_Id renames Args (3);
8620             Code     : Node_Id renames Args (4);
8621
8622          begin
8623             GNAT_Pragma;
8624
8625             if Inside_A_Generic then
8626                Error_Pragma ("pragma% cannot be used for generic entities");
8627             end if;
8628
8629             Gather_Associations (Names, Args);
8630             Process_Extended_Import_Export_Exception_Pragma (
8631               Arg_Internal => Internal,
8632               Arg_External => External,
8633               Arg_Form     => Form,
8634               Arg_Code     => Code);
8635
8636             if not Is_VMS_Exception (Entity (Internal)) then
8637                Set_Exported (Entity (Internal), Internal);
8638             end if;
8639          end Export_Exception;
8640
8641          ---------------------
8642          -- Export_Function --
8643          ---------------------
8644
8645          --  pragma Export_Function (
8646          --        [Internal         =>] LOCAL_NAME
8647          --     [, [External         =>] EXTERNAL_SYMBOL]
8648          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8649          --     [, [Result_Type      =>] TYPE_DESIGNATOR]
8650          --     [, [Mechanism        =>] MECHANISM]
8651          --     [, [Result_Mechanism =>] MECHANISM_NAME]);
8652
8653          --  EXTERNAL_SYMBOL ::=
8654          --    IDENTIFIER
8655          --  | static_string_EXPRESSION
8656
8657          --  PARAMETER_TYPES ::=
8658          --    null
8659          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8660
8661          --  TYPE_DESIGNATOR ::=
8662          --    subtype_NAME
8663          --  | subtype_Name ' Access
8664
8665          --  MECHANISM ::=
8666          --    MECHANISM_NAME
8667          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8668
8669          --  MECHANISM_ASSOCIATION ::=
8670          --    [formal_parameter_NAME =>] MECHANISM_NAME
8671
8672          --  MECHANISM_NAME ::=
8673          --    Value
8674          --  | Reference
8675          --  | Descriptor [([Class =>] CLASS_NAME)]
8676
8677          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8678
8679          when Pragma_Export_Function => Export_Function : declare
8680             Args  : Args_List (1 .. 6);
8681             Names : constant Name_List (1 .. 6) := (
8682                       Name_Internal,
8683                       Name_External,
8684                       Name_Parameter_Types,
8685                       Name_Result_Type,
8686                       Name_Mechanism,
8687                       Name_Result_Mechanism);
8688
8689             Internal         : Node_Id renames Args (1);
8690             External         : Node_Id renames Args (2);
8691             Parameter_Types  : Node_Id renames Args (3);
8692             Result_Type      : Node_Id renames Args (4);
8693             Mechanism        : Node_Id renames Args (5);
8694             Result_Mechanism : Node_Id renames Args (6);
8695
8696          begin
8697             GNAT_Pragma;
8698             Gather_Associations (Names, Args);
8699             Process_Extended_Import_Export_Subprogram_Pragma (
8700               Arg_Internal         => Internal,
8701               Arg_External         => External,
8702               Arg_Parameter_Types  => Parameter_Types,
8703               Arg_Result_Type      => Result_Type,
8704               Arg_Mechanism        => Mechanism,
8705               Arg_Result_Mechanism => Result_Mechanism);
8706          end Export_Function;
8707
8708          -------------------
8709          -- Export_Object --
8710          -------------------
8711
8712          --  pragma Export_Object (
8713          --        [Internal =>] LOCAL_NAME
8714          --     [, [External =>] EXTERNAL_SYMBOL]
8715          --     [, [Size     =>] EXTERNAL_SYMBOL]);
8716
8717          --  EXTERNAL_SYMBOL ::=
8718          --    IDENTIFIER
8719          --  | static_string_EXPRESSION
8720
8721          --  PARAMETER_TYPES ::=
8722          --    null
8723          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8724
8725          --  TYPE_DESIGNATOR ::=
8726          --    subtype_NAME
8727          --  | subtype_Name ' Access
8728
8729          --  MECHANISM ::=
8730          --    MECHANISM_NAME
8731          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8732
8733          --  MECHANISM_ASSOCIATION ::=
8734          --    [formal_parameter_NAME =>] MECHANISM_NAME
8735
8736          --  MECHANISM_NAME ::=
8737          --    Value
8738          --  | Reference
8739          --  | Descriptor [([Class =>] CLASS_NAME)]
8740
8741          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8742
8743          when Pragma_Export_Object => Export_Object : declare
8744             Args  : Args_List (1 .. 3);
8745             Names : constant Name_List (1 .. 3) := (
8746                       Name_Internal,
8747                       Name_External,
8748                       Name_Size);
8749
8750             Internal : Node_Id renames Args (1);
8751             External : Node_Id renames Args (2);
8752             Size     : Node_Id renames Args (3);
8753
8754          begin
8755             GNAT_Pragma;
8756             Gather_Associations (Names, Args);
8757             Process_Extended_Import_Export_Object_Pragma (
8758               Arg_Internal => Internal,
8759               Arg_External => External,
8760               Arg_Size     => Size);
8761          end Export_Object;
8762
8763          ----------------------
8764          -- Export_Procedure --
8765          ----------------------
8766
8767          --  pragma Export_Procedure (
8768          --        [Internal         =>] LOCAL_NAME
8769          --     [, [External         =>] EXTERNAL_SYMBOL]
8770          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8771          --     [, [Mechanism        =>] MECHANISM]);
8772
8773          --  EXTERNAL_SYMBOL ::=
8774          --    IDENTIFIER
8775          --  | static_string_EXPRESSION
8776
8777          --  PARAMETER_TYPES ::=
8778          --    null
8779          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8780
8781          --  TYPE_DESIGNATOR ::=
8782          --    subtype_NAME
8783          --  | subtype_Name ' Access
8784
8785          --  MECHANISM ::=
8786          --    MECHANISM_NAME
8787          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8788
8789          --  MECHANISM_ASSOCIATION ::=
8790          --    [formal_parameter_NAME =>] MECHANISM_NAME
8791
8792          --  MECHANISM_NAME ::=
8793          --    Value
8794          --  | Reference
8795          --  | Descriptor [([Class =>] CLASS_NAME)]
8796
8797          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8798
8799          when Pragma_Export_Procedure => Export_Procedure : declare
8800             Args  : Args_List (1 .. 4);
8801             Names : constant Name_List (1 .. 4) := (
8802                       Name_Internal,
8803                       Name_External,
8804                       Name_Parameter_Types,
8805                       Name_Mechanism);
8806
8807             Internal        : Node_Id renames Args (1);
8808             External        : Node_Id renames Args (2);
8809             Parameter_Types : Node_Id renames Args (3);
8810             Mechanism       : Node_Id renames Args (4);
8811
8812          begin
8813             GNAT_Pragma;
8814             Gather_Associations (Names, Args);
8815             Process_Extended_Import_Export_Subprogram_Pragma (
8816               Arg_Internal        => Internal,
8817               Arg_External        => External,
8818               Arg_Parameter_Types => Parameter_Types,
8819               Arg_Mechanism       => Mechanism);
8820          end Export_Procedure;
8821
8822          ------------------
8823          -- Export_Value --
8824          ------------------
8825
8826          --  pragma Export_Value (
8827          --     [Value     =>] static_integer_EXPRESSION,
8828          --     [Link_Name =>] static_string_EXPRESSION);
8829
8830          when Pragma_Export_Value =>
8831             GNAT_Pragma;
8832             Check_Arg_Order ((Name_Value, Name_Link_Name));
8833             Check_Arg_Count (2);
8834
8835             Check_Optional_Identifier (Arg1, Name_Value);
8836             Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
8837
8838             Check_Optional_Identifier (Arg2, Name_Link_Name);
8839             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
8840
8841          -----------------------------
8842          -- Export_Valued_Procedure --
8843          -----------------------------
8844
8845          --  pragma Export_Valued_Procedure (
8846          --        [Internal         =>] LOCAL_NAME
8847          --     [, [External         =>] EXTERNAL_SYMBOL,]
8848          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8849          --     [, [Mechanism        =>] MECHANISM]);
8850
8851          --  EXTERNAL_SYMBOL ::=
8852          --    IDENTIFIER
8853          --  | static_string_EXPRESSION
8854
8855          --  PARAMETER_TYPES ::=
8856          --    null
8857          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8858
8859          --  TYPE_DESIGNATOR ::=
8860          --    subtype_NAME
8861          --  | subtype_Name ' Access
8862
8863          --  MECHANISM ::=
8864          --    MECHANISM_NAME
8865          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8866
8867          --  MECHANISM_ASSOCIATION ::=
8868          --    [formal_parameter_NAME =>] MECHANISM_NAME
8869
8870          --  MECHANISM_NAME ::=
8871          --    Value
8872          --  | Reference
8873          --  | Descriptor [([Class =>] CLASS_NAME)]
8874
8875          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8876
8877          when Pragma_Export_Valued_Procedure =>
8878          Export_Valued_Procedure : declare
8879             Args  : Args_List (1 .. 4);
8880             Names : constant Name_List (1 .. 4) := (
8881                       Name_Internal,
8882                       Name_External,
8883                       Name_Parameter_Types,
8884                       Name_Mechanism);
8885
8886             Internal        : Node_Id renames Args (1);
8887             External        : Node_Id renames Args (2);
8888             Parameter_Types : Node_Id renames Args (3);
8889             Mechanism       : Node_Id renames Args (4);
8890
8891          begin
8892             GNAT_Pragma;
8893             Gather_Associations (Names, Args);
8894             Process_Extended_Import_Export_Subprogram_Pragma (
8895               Arg_Internal        => Internal,
8896               Arg_External        => External,
8897               Arg_Parameter_Types => Parameter_Types,
8898               Arg_Mechanism       => Mechanism);
8899          end Export_Valued_Procedure;
8900
8901          -------------------
8902          -- Extend_System --
8903          -------------------
8904
8905          --  pragma Extend_System ([Name =>] Identifier);
8906
8907          when Pragma_Extend_System => Extend_System : declare
8908          begin
8909             GNAT_Pragma;
8910             Check_Valid_Configuration_Pragma;
8911             Check_Arg_Count (1);
8912             Check_Optional_Identifier (Arg1, Name_Name);
8913             Check_Arg_Is_Identifier (Arg1);
8914
8915             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
8916
8917             if Name_Len > 4
8918               and then Name_Buffer (1 .. 4) = "aux_"
8919             then
8920                if Present (System_Extend_Pragma_Arg) then
8921                   if Chars (Get_Pragma_Arg (Arg1)) =
8922                      Chars (Expression (System_Extend_Pragma_Arg))
8923                   then
8924                      null;
8925                   else
8926                      Error_Msg_Sloc := Sloc (System_Extend_Pragma_Arg);
8927                      Error_Pragma ("pragma% conflicts with that #");
8928                   end if;
8929
8930                else
8931                   System_Extend_Pragma_Arg := Arg1;
8932
8933                   if not GNAT_Mode then
8934                      System_Extend_Unit := Arg1;
8935                   end if;
8936                end if;
8937             else
8938                Error_Pragma ("incorrect name for pragma%, must be Aux_xxx");
8939             end if;
8940          end Extend_System;
8941
8942          ------------------------
8943          -- Extensions_Allowed --
8944          ------------------------
8945
8946          --  pragma Extensions_Allowed (ON | OFF);
8947
8948          when Pragma_Extensions_Allowed =>
8949             GNAT_Pragma;
8950             Check_Arg_Count (1);
8951             Check_No_Identifiers;
8952             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
8953
8954             if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
8955                Extensions_Allowed := True;
8956                Ada_Version := Ada_Version_Type'Last;
8957
8958             else
8959                Extensions_Allowed := False;
8960                Ada_Version := Ada_Version_Explicit;
8961             end if;
8962
8963          --------------
8964          -- External --
8965          --------------
8966
8967          --  pragma External (
8968          --    [   Convention    =>] convention_IDENTIFIER,
8969          --    [   Entity        =>] local_NAME
8970          --    [, [External_Name =>] static_string_EXPRESSION ]
8971          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
8972
8973          when Pragma_External => External : declare
8974                Def_Id : Entity_Id;
8975
8976                C : Convention_Id;
8977                pragma Warnings (Off, C);
8978
8979          begin
8980             GNAT_Pragma;
8981             Check_Arg_Order
8982               ((Name_Convention,
8983                 Name_Entity,
8984                 Name_External_Name,
8985                 Name_Link_Name));
8986             Check_At_Least_N_Arguments (2);
8987             Check_At_Most_N_Arguments  (4);
8988             Process_Convention (C, Def_Id);
8989             Note_Possible_Modification
8990               (Get_Pragma_Arg (Arg2), Sure => False);
8991             Process_Interface_Name (Def_Id, Arg3, Arg4);
8992             Set_Exported (Def_Id, Arg2);
8993          end External;
8994
8995          --------------------------
8996          -- External_Name_Casing --
8997          --------------------------
8998
8999          --  pragma External_Name_Casing (
9000          --    UPPERCASE | LOWERCASE
9001          --    [, AS_IS | UPPERCASE | LOWERCASE]);
9002
9003          when Pragma_External_Name_Casing => External_Name_Casing : declare
9004          begin
9005             GNAT_Pragma;
9006             Check_No_Identifiers;
9007
9008             if Arg_Count = 2 then
9009                Check_Arg_Is_One_Of
9010                  (Arg2, Name_As_Is, Name_Uppercase, Name_Lowercase);
9011
9012                case Chars (Get_Pragma_Arg (Arg2)) is
9013                   when Name_As_Is     =>
9014                      Opt.External_Name_Exp_Casing := As_Is;
9015
9016                   when Name_Uppercase =>
9017                      Opt.External_Name_Exp_Casing := Uppercase;
9018
9019                   when Name_Lowercase =>
9020                      Opt.External_Name_Exp_Casing := Lowercase;
9021
9022                   when others =>
9023                      null;
9024                end case;
9025
9026             else
9027                Check_Arg_Count (1);
9028             end if;
9029
9030             Check_Arg_Is_One_Of (Arg1, Name_Uppercase, Name_Lowercase);
9031
9032             case Chars (Get_Pragma_Arg (Arg1)) is
9033                when Name_Uppercase =>
9034                   Opt.External_Name_Imp_Casing := Uppercase;
9035
9036                when Name_Lowercase =>
9037                   Opt.External_Name_Imp_Casing := Lowercase;
9038
9039                when others =>
9040                   null;
9041             end case;
9042          end External_Name_Casing;
9043
9044          --------------------------
9045          -- Favor_Top_Level --
9046          --------------------------
9047
9048          --  pragma Favor_Top_Level (type_NAME);
9049
9050          when Pragma_Favor_Top_Level => Favor_Top_Level : declare
9051                Named_Entity : Entity_Id;
9052
9053          begin
9054             GNAT_Pragma;
9055             Check_No_Identifiers;
9056             Check_Arg_Count (1);
9057             Check_Arg_Is_Local_Name (Arg1);
9058             Named_Entity := Entity (Get_Pragma_Arg (Arg1));
9059
9060             --  If it's an access-to-subprogram type (in particular, not a
9061             --  subtype), set the flag on that type.
9062
9063             if Is_Access_Subprogram_Type (Named_Entity) then
9064                Set_Can_Use_Internal_Rep (Named_Entity, False);
9065
9066             --  Otherwise it's an error (name denotes the wrong sort of entity)
9067
9068             else
9069                Error_Pragma_Arg
9070                  ("access-to-subprogram type expected",
9071                   Get_Pragma_Arg (Arg1));
9072             end if;
9073          end Favor_Top_Level;
9074
9075          ---------------
9076          -- Fast_Math --
9077          ---------------
9078
9079          --  pragma Fast_Math;
9080
9081          when Pragma_Fast_Math =>
9082             GNAT_Pragma;
9083             Check_No_Identifiers;
9084             Check_Valid_Configuration_Pragma;
9085             Fast_Math := True;
9086
9087          ---------------------------
9088          -- Finalize_Storage_Only --
9089          ---------------------------
9090
9091          --  pragma Finalize_Storage_Only (first_subtype_LOCAL_NAME);
9092
9093          when Pragma_Finalize_Storage_Only => Finalize_Storage : declare
9094             Assoc   : constant Node_Id := Arg1;
9095             Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
9096             Typ     : Entity_Id;
9097
9098          begin
9099             GNAT_Pragma;
9100             Check_No_Identifiers;
9101             Check_Arg_Count (1);
9102             Check_Arg_Is_Local_Name (Arg1);
9103
9104             Find_Type (Type_Id);
9105             Typ := Entity (Type_Id);
9106
9107             if Typ = Any_Type
9108               or else Rep_Item_Too_Early (Typ, N)
9109             then
9110                return;
9111             else
9112                Typ := Underlying_Type (Typ);
9113             end if;
9114
9115             if not Is_Controlled (Typ) then
9116                Error_Pragma ("pragma% must specify controlled type");
9117             end if;
9118
9119             Check_First_Subtype (Arg1);
9120
9121             if Finalize_Storage_Only (Typ) then
9122                Error_Pragma ("duplicate pragma%, only one allowed");
9123
9124             elsif not Rep_Item_Too_Late (Typ, N) then
9125                Set_Finalize_Storage_Only (Base_Type (Typ), True);
9126             end if;
9127          end Finalize_Storage;
9128
9129          --------------------------
9130          -- Float_Representation --
9131          --------------------------
9132
9133          --  pragma Float_Representation (FLOAT_REP[, float_type_LOCAL_NAME]);
9134
9135          --  FLOAT_REP ::= VAX_Float | IEEE_Float
9136
9137          when Pragma_Float_Representation => Float_Representation : declare
9138             Argx : Node_Id;
9139             Digs : Nat;
9140             Ent  : Entity_Id;
9141
9142          begin
9143             GNAT_Pragma;
9144
9145             if Arg_Count = 1 then
9146                Check_Valid_Configuration_Pragma;
9147             else
9148                Check_Arg_Count (2);
9149                Check_Optional_Identifier (Arg2, Name_Entity);
9150                Check_Arg_Is_Local_Name (Arg2);
9151             end if;
9152
9153             Check_No_Identifier (Arg1);
9154             Check_Arg_Is_One_Of (Arg1, Name_VAX_Float, Name_IEEE_Float);
9155
9156             if not OpenVMS_On_Target then
9157                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9158                   Error_Pragma
9159                     ("?pragma% ignored (applies only to Open'V'M'S)");
9160                end if;
9161
9162                return;
9163             end if;
9164
9165             --  One argument case
9166
9167             if Arg_Count = 1 then
9168                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9169                   if Opt.Float_Format = 'I' then
9170                      Error_Pragma ("'I'E'E'E format previously specified");
9171                   end if;
9172
9173                   Opt.Float_Format := 'V';
9174
9175                else
9176                   if Opt.Float_Format = 'V' then
9177                      Error_Pragma ("'V'A'X format previously specified");
9178                   end if;
9179
9180                   Opt.Float_Format := 'I';
9181                end if;
9182
9183                Set_Standard_Fpt_Formats;
9184
9185             --  Two argument case
9186
9187             else
9188                Argx := Get_Pragma_Arg (Arg2);
9189
9190                if not Is_Entity_Name (Argx)
9191                  or else not Is_Floating_Point_Type (Entity (Argx))
9192                then
9193                   Error_Pragma_Arg
9194                     ("second argument of% pragma must be floating-point type",
9195                      Arg2);
9196                end if;
9197
9198                Ent  := Entity (Argx);
9199                Digs := UI_To_Int (Digits_Value (Ent));
9200
9201                --  Two arguments, VAX_Float case
9202
9203                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9204                   case Digs is
9205                      when  6 => Set_F_Float (Ent);
9206                      when  9 => Set_D_Float (Ent);
9207                      when 15 => Set_G_Float (Ent);
9208
9209                      when others =>
9210                         Error_Pragma_Arg
9211                           ("wrong digits value, must be 6,9 or 15", Arg2);
9212                   end case;
9213
9214                --  Two arguments, IEEE_Float case
9215
9216                else
9217                   case Digs is
9218                      when  6 => Set_IEEE_Short (Ent);
9219                      when 15 => Set_IEEE_Long  (Ent);
9220
9221                      when others =>
9222                         Error_Pragma_Arg
9223                           ("wrong digits value, must be 6 or 15", Arg2);
9224                   end case;
9225                end if;
9226             end if;
9227          end Float_Representation;
9228
9229          -----------
9230          -- Ident --
9231          -----------
9232
9233          --  pragma Ident (static_string_EXPRESSION)
9234
9235          --  Note: pragma Comment shares this processing. Pragma Comment is
9236          --  identical to Ident, except that the restriction of the argument to
9237          --  31 characters and the placement restrictions are not enforced for
9238          --  pragma Comment.
9239
9240          when Pragma_Ident | Pragma_Comment => Ident : declare
9241             Str : Node_Id;
9242
9243          begin
9244             GNAT_Pragma;
9245             Check_Arg_Count (1);
9246             Check_No_Identifiers;
9247             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
9248             Store_Note (N);
9249
9250             --  For pragma Ident, preserve DEC compatibility by requiring the
9251             --  pragma to appear in a declarative part or package spec.
9252
9253             if Prag_Id = Pragma_Ident then
9254                Check_Is_In_Decl_Part_Or_Package_Spec;
9255             end if;
9256
9257             Str := Expr_Value_S (Get_Pragma_Arg (Arg1));
9258
9259             declare
9260                CS : Node_Id;
9261                GP : Node_Id;
9262
9263             begin
9264                GP := Parent (Parent (N));
9265
9266                if Nkind_In (GP, N_Package_Declaration,
9267                                 N_Generic_Package_Declaration)
9268                then
9269                   GP := Parent (GP);
9270                end if;
9271
9272                --  If we have a compilation unit, then record the ident value,
9273                --  checking for improper duplication.
9274
9275                if Nkind (GP) = N_Compilation_Unit then
9276                   CS := Ident_String (Current_Sem_Unit);
9277
9278                   if Present (CS) then
9279
9280                      --  For Ident, we do not permit multiple instances
9281
9282                      if Prag_Id = Pragma_Ident then
9283                         Error_Pragma ("duplicate% pragma not permitted");
9284
9285                      --  For Comment, we concatenate the string, unless we want
9286                      --  to preserve the tree structure for ASIS.
9287
9288                      elsif not ASIS_Mode then
9289                         Start_String (Strval (CS));
9290                         Store_String_Char (' ');
9291                         Store_String_Chars (Strval (Str));
9292                         Set_Strval (CS, End_String);
9293                      end if;
9294
9295                   else
9296                      --  In VMS, the effect of IDENT is achieved by passing
9297                      --  --identification=name as a --for-linker switch.
9298
9299                      if OpenVMS_On_Target then
9300                         Start_String;
9301                         Store_String_Chars
9302                           ("--for-linker=--identification=");
9303                         String_To_Name_Buffer (Strval (Str));
9304                         Store_String_Chars (Name_Buffer (1 .. Name_Len));
9305
9306                         --  Only the last processed IDENT is saved. The main
9307                         --  purpose is so an IDENT associated with a main
9308                         --  procedure will be used in preference to an IDENT
9309                         --  associated with a with'd package.
9310
9311                         Replace_Linker_Option_String
9312                           (End_String, "--for-linker=--identification=");
9313                      end if;
9314
9315                      Set_Ident_String (Current_Sem_Unit, Str);
9316                   end if;
9317
9318                --  For subunits, we just ignore the Ident, since in GNAT these
9319                --  are not separate object files, and hence not separate units
9320                --  in the unit table.
9321
9322                elsif Nkind (GP) = N_Subunit then
9323                   null;
9324
9325                --  Otherwise we have a misplaced pragma Ident, but we ignore
9326                --  this if we are in an instantiation, since it comes from
9327                --  a generic, and has no relevance to the instantiation.
9328
9329                elsif Prag_Id = Pragma_Ident then
9330                   if Instantiation_Location (Loc) = No_Location then
9331                      Error_Pragma ("pragma% only allowed at outer level");
9332                   end if;
9333                end if;
9334             end;
9335          end Ident;
9336
9337          ----------------------------
9338          -- Implementation_Defined --
9339          ----------------------------
9340
9341          --  pragma Implementation_Defined (local_NAME);
9342
9343          --  Marks previously declared entity as implementation defined. For
9344          --  an overloaded entity, applies to the most recent homonym.
9345
9346          --  pragma Implementation_Defined;
9347
9348          --  The form with no arguments appears anywhere within a scope, most
9349          --  typically a package spec, and indicates that all entities that are
9350          --  defined within the package spec are Implementation_Defined.
9351
9352          when Pragma_Implementation_Defined => Implementation_Defined : declare
9353             Ent : Entity_Id;
9354
9355          begin
9356             Check_No_Identifiers;
9357
9358             --  Form with no arguments
9359
9360             if Arg_Count = 0 then
9361                Set_Is_Implementation_Defined (Current_Scope);
9362
9363             --  Form with one argument
9364
9365             else
9366                Check_Arg_Count (1);
9367                Check_Arg_Is_Local_Name (Arg1);
9368                Ent := Entity (Get_Pragma_Arg (Arg1));
9369                Set_Is_Implementation_Defined (Ent);
9370             end if;
9371          end Implementation_Defined;
9372
9373          -----------------
9374          -- Implemented --
9375          -----------------
9376
9377          --  pragma Implemented (procedure_LOCAL_NAME, implementation_kind);
9378          --  implementation_kind ::=
9379          --    By_Entry | By_Protected_Procedure | By_Any | Optional
9380
9381          --  "By_Any" and "Optional" are treated as synonyms in order to
9382          --  support Ada 2012 aspect Synchronization.
9383
9384          when Pragma_Implemented => Implemented : declare
9385             Proc_Id : Entity_Id;
9386             Typ     : Entity_Id;
9387
9388          begin
9389             Ada_2012_Pragma;
9390             Check_Arg_Count (2);
9391             Check_No_Identifiers;
9392             Check_Arg_Is_Identifier (Arg1);
9393             Check_Arg_Is_Local_Name (Arg1);
9394             Check_Arg_Is_One_Of (Arg2,
9395               Name_By_Any,
9396               Name_By_Entry,
9397               Name_By_Protected_Procedure,
9398               Name_Optional);
9399
9400             --  Extract the name of the local procedure
9401
9402             Proc_Id := Entity (Get_Pragma_Arg (Arg1));
9403
9404             --  Ada 2012 (AI05-0030): The procedure_LOCAL_NAME must denote a
9405             --  primitive procedure of a synchronized tagged type.
9406
9407             if Ekind (Proc_Id) = E_Procedure
9408               and then Is_Primitive (Proc_Id)
9409               and then Present (First_Formal (Proc_Id))
9410             then
9411                Typ := Etype (First_Formal (Proc_Id));
9412
9413                if Is_Tagged_Type (Typ)
9414                  and then
9415
9416                   --  Check for a protected, a synchronized or a task interface
9417
9418                    ((Is_Interface (Typ)
9419                        and then Is_Synchronized_Interface (Typ))
9420
9421                   --  Check for a protected type or a task type that implements
9422                   --  an interface.
9423
9424                    or else
9425                     (Is_Concurrent_Record_Type (Typ)
9426                        and then Present (Interfaces (Typ)))
9427
9428                   --  Check for a private record extension with keyword
9429                   --  "synchronized".
9430
9431                    or else
9432                     (Ekind_In (Typ, E_Record_Type_With_Private,
9433                                     E_Record_Subtype_With_Private)
9434                        and then Synchronized_Present (Parent (Typ))))
9435                then
9436                   null;
9437                else
9438                   Error_Pragma_Arg
9439                     ("controlling formal must be of synchronized " &
9440                      "tagged type", Arg1);
9441                   return;
9442                end if;
9443
9444             --  Procedures declared inside a protected type must be accepted
9445
9446             elsif Ekind (Proc_Id) = E_Procedure
9447               and then Is_Protected_Type (Scope (Proc_Id))
9448             then
9449                null;
9450
9451             --  The first argument is not a primitive procedure
9452
9453             else
9454                Error_Pragma_Arg
9455                  ("pragma % must be applied to a primitive procedure", Arg1);
9456                return;
9457             end if;
9458
9459             --  Ada 2012 (AI05-0030): Cannot apply the implementation_kind
9460             --  By_Protected_Procedure to the primitive procedure of a task
9461             --  interface.
9462
9463             if Chars (Arg2) = Name_By_Protected_Procedure
9464               and then Is_Interface (Typ)
9465               and then Is_Task_Interface (Typ)
9466             then
9467                Error_Pragma_Arg
9468                  ("implementation kind By_Protected_Procedure cannot be " &
9469                   "applied to a task interface primitive", Arg2);
9470                return;
9471             end if;
9472
9473             Record_Rep_Item (Proc_Id, N);
9474          end Implemented;
9475
9476          ----------------------
9477          -- Implicit_Packing --
9478          ----------------------
9479
9480          --  pragma Implicit_Packing;
9481
9482          when Pragma_Implicit_Packing =>
9483             GNAT_Pragma;
9484             Check_Arg_Count (0);
9485             Implicit_Packing := True;
9486
9487          ------------
9488          -- Import --
9489          ------------
9490
9491          --  pragma Import (
9492          --       [Convention    =>] convention_IDENTIFIER,
9493          --       [Entity        =>] local_NAME
9494          --    [, [External_Name =>] static_string_EXPRESSION ]
9495          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
9496
9497          when Pragma_Import =>
9498             Check_Ada_83_Warning;
9499             Check_Arg_Order
9500               ((Name_Convention,
9501                 Name_Entity,
9502                 Name_External_Name,
9503                 Name_Link_Name));
9504             Check_At_Least_N_Arguments (2);
9505             Check_At_Most_N_Arguments  (4);
9506             Process_Import_Or_Interface;
9507
9508          ----------------------
9509          -- Import_Exception --
9510          ----------------------
9511
9512          --  pragma Import_Exception (
9513          --        [Internal         =>] LOCAL_NAME
9514          --     [, [External         =>] EXTERNAL_SYMBOL]
9515          --     [, [Form     =>] Ada | VMS]
9516          --     [, [Code     =>] static_integer_EXPRESSION]);
9517
9518          when Pragma_Import_Exception => Import_Exception : declare
9519             Args  : Args_List (1 .. 4);
9520             Names : constant Name_List (1 .. 4) := (
9521                       Name_Internal,
9522                       Name_External,
9523                       Name_Form,
9524                       Name_Code);
9525
9526             Internal : Node_Id renames Args (1);
9527             External : Node_Id renames Args (2);
9528             Form     : Node_Id renames Args (3);
9529             Code     : Node_Id renames Args (4);
9530
9531          begin
9532             GNAT_Pragma;
9533             Gather_Associations (Names, Args);
9534
9535             if Present (External) and then Present (Code) then
9536                Error_Pragma
9537                  ("cannot give both External and Code options for pragma%");
9538             end if;
9539
9540             Process_Extended_Import_Export_Exception_Pragma (
9541               Arg_Internal => Internal,
9542               Arg_External => External,
9543               Arg_Form     => Form,
9544               Arg_Code     => Code);
9545
9546             if not Is_VMS_Exception (Entity (Internal)) then
9547                Set_Imported (Entity (Internal));
9548             end if;
9549          end Import_Exception;
9550
9551          ---------------------
9552          -- Import_Function --
9553          ---------------------
9554
9555          --  pragma Import_Function (
9556          --        [Internal                 =>] LOCAL_NAME,
9557          --     [, [External                 =>] EXTERNAL_SYMBOL]
9558          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9559          --     [, [Result_Type              =>] SUBTYPE_MARK]
9560          --     [, [Mechanism                =>] MECHANISM]
9561          --     [, [Result_Mechanism         =>] MECHANISM_NAME]
9562          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9563
9564          --  EXTERNAL_SYMBOL ::=
9565          --    IDENTIFIER
9566          --  | static_string_EXPRESSION
9567
9568          --  PARAMETER_TYPES ::=
9569          --    null
9570          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9571
9572          --  TYPE_DESIGNATOR ::=
9573          --    subtype_NAME
9574          --  | subtype_Name ' Access
9575
9576          --  MECHANISM ::=
9577          --    MECHANISM_NAME
9578          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9579
9580          --  MECHANISM_ASSOCIATION ::=
9581          --    [formal_parameter_NAME =>] MECHANISM_NAME
9582
9583          --  MECHANISM_NAME ::=
9584          --    Value
9585          --  | Reference
9586          --  | Descriptor [([Class =>] CLASS_NAME)]
9587
9588          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9589
9590          when Pragma_Import_Function => Import_Function : declare
9591             Args  : Args_List (1 .. 7);
9592             Names : constant Name_List (1 .. 7) := (
9593                       Name_Internal,
9594                       Name_External,
9595                       Name_Parameter_Types,
9596                       Name_Result_Type,
9597                       Name_Mechanism,
9598                       Name_Result_Mechanism,
9599                       Name_First_Optional_Parameter);
9600
9601             Internal                 : Node_Id renames Args (1);
9602             External                 : Node_Id renames Args (2);
9603             Parameter_Types          : Node_Id renames Args (3);
9604             Result_Type              : Node_Id renames Args (4);
9605             Mechanism                : Node_Id renames Args (5);
9606             Result_Mechanism         : Node_Id renames Args (6);
9607             First_Optional_Parameter : Node_Id renames Args (7);
9608
9609          begin
9610             GNAT_Pragma;
9611             Gather_Associations (Names, Args);
9612             Process_Extended_Import_Export_Subprogram_Pragma (
9613               Arg_Internal                 => Internal,
9614               Arg_External                 => External,
9615               Arg_Parameter_Types          => Parameter_Types,
9616               Arg_Result_Type              => Result_Type,
9617               Arg_Mechanism                => Mechanism,
9618               Arg_Result_Mechanism         => Result_Mechanism,
9619               Arg_First_Optional_Parameter => First_Optional_Parameter);
9620          end Import_Function;
9621
9622          -------------------
9623          -- Import_Object --
9624          -------------------
9625
9626          --  pragma Import_Object (
9627          --        [Internal =>] LOCAL_NAME
9628          --     [, [External =>] EXTERNAL_SYMBOL]
9629          --     [, [Size     =>] EXTERNAL_SYMBOL]);
9630
9631          --  EXTERNAL_SYMBOL ::=
9632          --    IDENTIFIER
9633          --  | static_string_EXPRESSION
9634
9635          when Pragma_Import_Object => Import_Object : declare
9636             Args  : Args_List (1 .. 3);
9637             Names : constant Name_List (1 .. 3) := (
9638                       Name_Internal,
9639                       Name_External,
9640                       Name_Size);
9641
9642             Internal : Node_Id renames Args (1);
9643             External : Node_Id renames Args (2);
9644             Size     : Node_Id renames Args (3);
9645
9646          begin
9647             GNAT_Pragma;
9648             Gather_Associations (Names, Args);
9649             Process_Extended_Import_Export_Object_Pragma (
9650               Arg_Internal => Internal,
9651               Arg_External => External,
9652               Arg_Size     => Size);
9653          end Import_Object;
9654
9655          ----------------------
9656          -- Import_Procedure --
9657          ----------------------
9658
9659          --  pragma Import_Procedure (
9660          --        [Internal                 =>] LOCAL_NAME
9661          --     [, [External                 =>] EXTERNAL_SYMBOL]
9662          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9663          --     [, [Mechanism                =>] MECHANISM]
9664          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9665
9666          --  EXTERNAL_SYMBOL ::=
9667          --    IDENTIFIER
9668          --  | static_string_EXPRESSION
9669
9670          --  PARAMETER_TYPES ::=
9671          --    null
9672          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9673
9674          --  TYPE_DESIGNATOR ::=
9675          --    subtype_NAME
9676          --  | subtype_Name ' Access
9677
9678          --  MECHANISM ::=
9679          --    MECHANISM_NAME
9680          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9681
9682          --  MECHANISM_ASSOCIATION ::=
9683          --    [formal_parameter_NAME =>] MECHANISM_NAME
9684
9685          --  MECHANISM_NAME ::=
9686          --    Value
9687          --  | Reference
9688          --  | Descriptor [([Class =>] CLASS_NAME)]
9689
9690          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9691
9692          when Pragma_Import_Procedure => Import_Procedure : declare
9693             Args  : Args_List (1 .. 5);
9694             Names : constant Name_List (1 .. 5) := (
9695                       Name_Internal,
9696                       Name_External,
9697                       Name_Parameter_Types,
9698                       Name_Mechanism,
9699                       Name_First_Optional_Parameter);
9700
9701             Internal                 : Node_Id renames Args (1);
9702             External                 : Node_Id renames Args (2);
9703             Parameter_Types          : Node_Id renames Args (3);
9704             Mechanism                : Node_Id renames Args (4);
9705             First_Optional_Parameter : Node_Id renames Args (5);
9706
9707          begin
9708             GNAT_Pragma;
9709             Gather_Associations (Names, Args);
9710             Process_Extended_Import_Export_Subprogram_Pragma (
9711               Arg_Internal                 => Internal,
9712               Arg_External                 => External,
9713               Arg_Parameter_Types          => Parameter_Types,
9714               Arg_Mechanism                => Mechanism,
9715               Arg_First_Optional_Parameter => First_Optional_Parameter);
9716          end Import_Procedure;
9717
9718          -----------------------------
9719          -- Import_Valued_Procedure --
9720          -----------------------------
9721
9722          --  pragma Import_Valued_Procedure (
9723          --        [Internal                 =>] LOCAL_NAME
9724          --     [, [External                 =>] EXTERNAL_SYMBOL]
9725          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9726          --     [, [Mechanism                =>] MECHANISM]
9727          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9728
9729          --  EXTERNAL_SYMBOL ::=
9730          --    IDENTIFIER
9731          --  | static_string_EXPRESSION
9732
9733          --  PARAMETER_TYPES ::=
9734          --    null
9735          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9736
9737          --  TYPE_DESIGNATOR ::=
9738          --    subtype_NAME
9739          --  | subtype_Name ' Access
9740
9741          --  MECHANISM ::=
9742          --    MECHANISM_NAME
9743          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9744
9745          --  MECHANISM_ASSOCIATION ::=
9746          --    [formal_parameter_NAME =>] MECHANISM_NAME
9747
9748          --  MECHANISM_NAME ::=
9749          --    Value
9750          --  | Reference
9751          --  | Descriptor [([Class =>] CLASS_NAME)]
9752
9753          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9754
9755          when Pragma_Import_Valued_Procedure =>
9756          Import_Valued_Procedure : declare
9757             Args  : Args_List (1 .. 5);
9758             Names : constant Name_List (1 .. 5) := (
9759                       Name_Internal,
9760                       Name_External,
9761                       Name_Parameter_Types,
9762                       Name_Mechanism,
9763                       Name_First_Optional_Parameter);
9764
9765             Internal                 : Node_Id renames Args (1);
9766             External                 : Node_Id renames Args (2);
9767             Parameter_Types          : Node_Id renames Args (3);
9768             Mechanism                : Node_Id renames Args (4);
9769             First_Optional_Parameter : Node_Id renames Args (5);
9770
9771          begin
9772             GNAT_Pragma;
9773             Gather_Associations (Names, Args);
9774             Process_Extended_Import_Export_Subprogram_Pragma (
9775               Arg_Internal                 => Internal,
9776               Arg_External                 => External,
9777               Arg_Parameter_Types          => Parameter_Types,
9778               Arg_Mechanism                => Mechanism,
9779               Arg_First_Optional_Parameter => First_Optional_Parameter);
9780          end Import_Valued_Procedure;
9781
9782          -----------------
9783          -- Independent --
9784          -----------------
9785
9786          --  pragma Independent (LOCAL_NAME);
9787
9788          when Pragma_Independent => Independent : declare
9789             E_Id : Node_Id;
9790             E    : Entity_Id;
9791             D    : Node_Id;
9792             K    : Node_Kind;
9793
9794          begin
9795             Check_Ada_83_Warning;
9796             Ada_2012_Pragma;
9797             Check_No_Identifiers;
9798             Check_Arg_Count (1);
9799             Check_Arg_Is_Local_Name (Arg1);
9800             E_Id := Get_Pragma_Arg (Arg1);
9801
9802             if Etype (E_Id) = Any_Type then
9803                return;
9804             end if;
9805
9806             E := Entity (E_Id);
9807             D := Declaration_Node (E);
9808             K := Nkind (D);
9809
9810             --  Check duplicate before we chain ourselves!
9811
9812             Check_Duplicate_Pragma (E);
9813
9814             --  Check appropriate entity
9815
9816             if Is_Type (E) then
9817                if Rep_Item_Too_Early (E, N)
9818                     or else
9819                   Rep_Item_Too_Late (E, N)
9820                then
9821                   return;
9822                else
9823                   Check_First_Subtype (Arg1);
9824                end if;
9825
9826             elsif K = N_Object_Declaration
9827               or else (K = N_Component_Declaration
9828                        and then Original_Record_Component (E) = E)
9829             then
9830                if Rep_Item_Too_Late (E, N) then
9831                   return;
9832                end if;
9833
9834             else
9835                Error_Pragma_Arg
9836                  ("inappropriate entity for pragma%", Arg1);
9837             end if;
9838
9839             Independence_Checks.Append ((N, E));
9840          end Independent;
9841
9842          ----------------------------
9843          -- Independent_Components --
9844          ----------------------------
9845
9846          --  pragma Atomic_Components (array_LOCAL_NAME);
9847
9848          --  This processing is shared by Volatile_Components
9849
9850          when Pragma_Independent_Components => Independent_Components : declare
9851             E_Id : Node_Id;
9852             E    : Entity_Id;
9853             D    : Node_Id;
9854             K    : Node_Kind;
9855
9856          begin
9857             Check_Ada_83_Warning;
9858             Ada_2012_Pragma;
9859             Check_No_Identifiers;
9860             Check_Arg_Count (1);
9861             Check_Arg_Is_Local_Name (Arg1);
9862             E_Id := Get_Pragma_Arg (Arg1);
9863
9864             if Etype (E_Id) = Any_Type then
9865                return;
9866             end if;
9867
9868             E := Entity (E_Id);
9869
9870             --  Check duplicate before we chain ourselves!
9871
9872             Check_Duplicate_Pragma (E);
9873
9874             --  Check appropriate entity
9875
9876             if Rep_Item_Too_Early (E, N)
9877                  or else
9878                Rep_Item_Too_Late (E, N)
9879             then
9880                return;
9881             end if;
9882
9883             D := Declaration_Node (E);
9884             K := Nkind (D);
9885
9886             if (K = N_Full_Type_Declaration
9887                  and then (Is_Array_Type (E) or else Is_Record_Type (E)))
9888               or else
9889                 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
9890                    and then Nkind (D) = N_Object_Declaration
9891                    and then Nkind (Object_Definition (D)) =
9892                                        N_Constrained_Array_Definition)
9893             then
9894                Independence_Checks.Append ((N, E));
9895
9896             else
9897                Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
9898             end if;
9899          end Independent_Components;
9900
9901          ------------------------
9902          -- Initialize_Scalars --
9903          ------------------------
9904
9905          --  pragma Initialize_Scalars;
9906
9907          when Pragma_Initialize_Scalars =>
9908             GNAT_Pragma;
9909             Check_Arg_Count (0);
9910             Check_Valid_Configuration_Pragma;
9911             Check_Restriction (No_Initialize_Scalars, N);
9912
9913             --  Initialize_Scalars creates false positives in CodePeer, and
9914             --  incorrect negative results in Alfa mode, so ignore this pragma
9915             --  in these modes.
9916
9917             if not Restriction_Active (No_Initialize_Scalars)
9918               and then not (CodePeer_Mode or Alfa_Mode)
9919             then
9920                Init_Or_Norm_Scalars := True;
9921                Initialize_Scalars := True;
9922             end if;
9923
9924          ------------
9925          -- Inline --
9926          ------------
9927
9928          --  pragma Inline ( NAME {, NAME} );
9929
9930          when Pragma_Inline =>
9931
9932             --  Pragma is active if inlining option is active
9933
9934             Process_Inline (Inline_Active);
9935
9936          -------------------
9937          -- Inline_Always --
9938          -------------------
9939
9940          --  pragma Inline_Always ( NAME {, NAME} );
9941
9942          when Pragma_Inline_Always =>
9943             GNAT_Pragma;
9944
9945             --  Pragma always active unless in CodePeer or Alfa mode, since
9946             --  this causes walk order issues.
9947
9948             if not (CodePeer_Mode or Alfa_Mode) then
9949                Process_Inline (True);
9950             end if;
9951
9952          --------------------
9953          -- Inline_Generic --
9954          --------------------
9955
9956          --  pragma Inline_Generic (NAME {, NAME});
9957
9958          when Pragma_Inline_Generic =>
9959             GNAT_Pragma;
9960             Process_Generic_List;
9961
9962          ----------------------
9963          -- Inspection_Point --
9964          ----------------------
9965
9966          --  pragma Inspection_Point [(object_NAME {, object_NAME})];
9967
9968          when Pragma_Inspection_Point => Inspection_Point : declare
9969             Arg : Node_Id;
9970             Exp : Node_Id;
9971
9972          begin
9973             if Arg_Count > 0 then
9974                Arg := Arg1;
9975                loop
9976                   Exp := Get_Pragma_Arg (Arg);
9977                   Analyze (Exp);
9978
9979                   if not Is_Entity_Name (Exp)
9980                     or else not Is_Object (Entity (Exp))
9981                   then
9982                      Error_Pragma_Arg ("object name required", Arg);
9983                   end if;
9984
9985                   Next (Arg);
9986                   exit when No (Arg);
9987                end loop;
9988             end if;
9989          end Inspection_Point;
9990
9991          ---------------
9992          -- Interface --
9993          ---------------
9994
9995          --  pragma Interface (
9996          --    [   Convention    =>] convention_IDENTIFIER,
9997          --    [   Entity        =>] local_NAME
9998          --    [, [External_Name =>] static_string_EXPRESSION ]
9999          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
10000
10001          when Pragma_Interface =>
10002             GNAT_Pragma;
10003             Check_Arg_Order
10004               ((Name_Convention,
10005                 Name_Entity,
10006                 Name_External_Name,
10007                 Name_Link_Name));
10008             Check_At_Least_N_Arguments (2);
10009             Check_At_Most_N_Arguments  (4);
10010             Process_Import_Or_Interface;
10011
10012             --  In Ada 2005, the permission to use Interface (a reserved word)
10013             --  as a pragma name is considered an obsolescent feature.
10014
10015             if Ada_Version >= Ada_2005 then
10016                Check_Restriction
10017                  (No_Obsolescent_Features, Pragma_Identifier (N));
10018             end if;
10019
10020          --------------------
10021          -- Interface_Name --
10022          --------------------
10023
10024          --  pragma Interface_Name (
10025          --    [  Entity        =>] local_NAME
10026          --    [,[External_Name =>] static_string_EXPRESSION ]
10027          --    [,[Link_Name     =>] static_string_EXPRESSION ]);
10028
10029          when Pragma_Interface_Name => Interface_Name : declare
10030             Id     : Node_Id;
10031             Def_Id : Entity_Id;
10032             Hom_Id : Entity_Id;
10033             Found  : Boolean;
10034
10035          begin
10036             GNAT_Pragma;
10037             Check_Arg_Order
10038               ((Name_Entity, Name_External_Name, Name_Link_Name));
10039             Check_At_Least_N_Arguments (2);
10040             Check_At_Most_N_Arguments  (3);
10041             Id := Get_Pragma_Arg (Arg1);
10042             Analyze (Id);
10043
10044             if not Is_Entity_Name (Id) then
10045                Error_Pragma_Arg
10046                  ("first argument for pragma% must be entity name", Arg1);
10047             elsif Etype (Id) = Any_Type then
10048                return;
10049             else
10050                Def_Id := Entity (Id);
10051             end if;
10052
10053             --  Special DEC-compatible processing for the object case, forces
10054             --  object to be imported.
10055
10056             if Ekind (Def_Id) = E_Variable then
10057                Kill_Size_Check_Code (Def_Id);
10058                Note_Possible_Modification (Id, Sure => False);
10059
10060                --  Initialization is not allowed for imported variable
10061
10062                if Present (Expression (Parent (Def_Id)))
10063                  and then Comes_From_Source (Expression (Parent (Def_Id)))
10064                then
10065                   Error_Msg_Sloc := Sloc (Def_Id);
10066                   Error_Pragma_Arg
10067                     ("no initialization allowed for declaration of& #",
10068                      Arg2);
10069
10070                else
10071                   --  For compatibility, support VADS usage of providing both
10072                   --  pragmas Interface and Interface_Name to obtain the effect
10073                   --  of a single Import pragma.
10074
10075                   if Is_Imported (Def_Id)
10076                     and then Present (First_Rep_Item (Def_Id))
10077                     and then Nkind (First_Rep_Item (Def_Id)) = N_Pragma
10078                     and then
10079                       Pragma_Name (First_Rep_Item (Def_Id)) = Name_Interface
10080                   then
10081                      null;
10082                   else
10083                      Set_Imported (Def_Id);
10084                   end if;
10085
10086                   Set_Is_Public (Def_Id);
10087                   Process_Interface_Name (Def_Id, Arg2, Arg3);
10088                end if;
10089
10090             --  Otherwise must be subprogram
10091
10092             elsif not Is_Subprogram (Def_Id) then
10093                Error_Pragma_Arg
10094                  ("argument of pragma% is not subprogram", Arg1);
10095
10096             else
10097                Check_At_Most_N_Arguments (3);
10098                Hom_Id := Def_Id;
10099                Found := False;
10100
10101                --  Loop through homonyms
10102
10103                loop
10104                   Def_Id := Get_Base_Subprogram (Hom_Id);
10105
10106                   if Is_Imported (Def_Id) then
10107                      Process_Interface_Name (Def_Id, Arg2, Arg3);
10108                      Found := True;
10109                   end if;
10110
10111                   exit when From_Aspect_Specification (N);
10112                   Hom_Id := Homonym (Hom_Id);
10113
10114                   exit when No (Hom_Id)
10115                     or else Scope (Hom_Id) /= Current_Scope;
10116                end loop;
10117
10118                if not Found then
10119                   Error_Pragma_Arg
10120                     ("argument of pragma% is not imported subprogram",
10121                      Arg1);
10122                end if;
10123             end if;
10124          end Interface_Name;
10125
10126          -----------------------
10127          -- Interrupt_Handler --
10128          -----------------------
10129
10130          --  pragma Interrupt_Handler (handler_NAME);
10131
10132          when Pragma_Interrupt_Handler =>
10133             Check_Ada_83_Warning;
10134             Check_Arg_Count (1);
10135             Check_No_Identifiers;
10136
10137             if No_Run_Time_Mode then
10138                Error_Msg_CRT ("Interrupt_Handler pragma", N);
10139             else
10140                Check_Interrupt_Or_Attach_Handler;
10141                Process_Interrupt_Or_Attach_Handler;
10142             end if;
10143
10144          ------------------------
10145          -- Interrupt_Priority --
10146          ------------------------
10147
10148          --  pragma Interrupt_Priority [(EXPRESSION)];
10149
10150          when Pragma_Interrupt_Priority => Interrupt_Priority : declare
10151             P   : constant Node_Id := Parent (N);
10152             Arg : Node_Id;
10153
10154          begin
10155             Check_Ada_83_Warning;
10156
10157             if Arg_Count /= 0 then
10158                Arg := Get_Pragma_Arg (Arg1);
10159                Check_Arg_Count (1);
10160                Check_No_Identifiers;
10161
10162                --  The expression must be analyzed in the special manner
10163                --  described in "Handling of Default and Per-Object
10164                --  Expressions" in sem.ads.
10165
10166                Preanalyze_Spec_Expression (Arg, RTE (RE_Interrupt_Priority));
10167             end if;
10168
10169             if not Nkind_In (P, N_Task_Definition, N_Protected_Definition) then
10170                Pragma_Misplaced;
10171                return;
10172
10173             elsif Has_Pragma_Priority (P) then
10174                Error_Pragma ("duplicate pragma% not allowed");
10175
10176             else
10177                Set_Has_Pragma_Priority (P, True);
10178                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
10179             end if;
10180          end Interrupt_Priority;
10181
10182          ---------------------
10183          -- Interrupt_State --
10184          ---------------------
10185
10186          --  pragma Interrupt_State (
10187          --    [Name  =>] INTERRUPT_ID,
10188          --    [State =>] INTERRUPT_STATE);
10189
10190          --  INTERRUPT_ID => IDENTIFIER | static_integer_EXPRESSION
10191          --  INTERRUPT_STATE => System | Runtime | User
10192
10193          --  Note: if the interrupt id is given as an identifier, then it must
10194          --  be one of the identifiers in Ada.Interrupts.Names. Otherwise it is
10195          --  given as a static integer expression which must be in the range of
10196          --  Ada.Interrupts.Interrupt_ID.
10197
10198          when Pragma_Interrupt_State => Interrupt_State : declare
10199
10200             Int_Id : constant Entity_Id := RTE (RE_Interrupt_ID);
10201             --  This is the entity Ada.Interrupts.Interrupt_ID;
10202
10203             State_Type : Character;
10204             --  Set to 's'/'r'/'u' for System/Runtime/User
10205
10206             IST_Num : Pos;
10207             --  Index to entry in Interrupt_States table
10208
10209             Int_Val : Uint;
10210             --  Value of interrupt
10211
10212             Arg1X : constant Node_Id := Get_Pragma_Arg (Arg1);
10213             --  The first argument to the pragma
10214
10215             Int_Ent : Entity_Id;
10216             --  Interrupt entity in Ada.Interrupts.Names
10217
10218          begin
10219             GNAT_Pragma;
10220             Check_Arg_Order ((Name_Name, Name_State));
10221             Check_Arg_Count (2);
10222
10223             Check_Optional_Identifier (Arg1, Name_Name);
10224             Check_Optional_Identifier (Arg2, Name_State);
10225             Check_Arg_Is_Identifier (Arg2);
10226
10227             --  First argument is identifier
10228
10229             if Nkind (Arg1X) = N_Identifier then
10230
10231                --  Search list of names in Ada.Interrupts.Names
10232
10233                Int_Ent := First_Entity (RTE (RE_Names));
10234                loop
10235                   if No (Int_Ent) then
10236                      Error_Pragma_Arg ("invalid interrupt name", Arg1);
10237
10238                   elsif Chars (Int_Ent) = Chars (Arg1X) then
10239                      Int_Val := Expr_Value (Constant_Value (Int_Ent));
10240                      exit;
10241                   end if;
10242
10243                   Next_Entity (Int_Ent);
10244                end loop;
10245
10246             --  First argument is not an identifier, so it must be a static
10247             --  expression of type Ada.Interrupts.Interrupt_ID.
10248
10249             else
10250                Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
10251                Int_Val := Expr_Value (Arg1X);
10252
10253                if Int_Val < Expr_Value (Type_Low_Bound (Int_Id))
10254                     or else
10255                   Int_Val > Expr_Value (Type_High_Bound (Int_Id))
10256                then
10257                   Error_Pragma_Arg
10258                     ("value not in range of type " &
10259                      """Ada.Interrupts.Interrupt_'I'D""", Arg1);
10260                end if;
10261             end if;
10262
10263             --  Check OK state
10264
10265             case Chars (Get_Pragma_Arg (Arg2)) is
10266                when Name_Runtime => State_Type := 'r';
10267                when Name_System  => State_Type := 's';
10268                when Name_User    => State_Type := 'u';
10269
10270                when others =>
10271                   Error_Pragma_Arg ("invalid interrupt state", Arg2);
10272             end case;
10273
10274             --  Check if entry is already stored
10275
10276             IST_Num := Interrupt_States.First;
10277             loop
10278                --  If entry not found, add it
10279
10280                if IST_Num > Interrupt_States.Last then
10281                   Interrupt_States.Append
10282                     ((Interrupt_Number => UI_To_Int (Int_Val),
10283                       Interrupt_State  => State_Type,
10284                       Pragma_Loc       => Loc));
10285                   exit;
10286
10287                --  Case of entry for the same entry
10288
10289                elsif Int_Val = Interrupt_States.Table (IST_Num).
10290                                                            Interrupt_Number
10291                then
10292                   --  If state matches, done, no need to make redundant entry
10293
10294                   exit when
10295                     State_Type = Interrupt_States.Table (IST_Num).
10296                                                            Interrupt_State;
10297
10298                   --  Otherwise if state does not match, error
10299
10300                   Error_Msg_Sloc :=
10301                     Interrupt_States.Table (IST_Num).Pragma_Loc;
10302                   Error_Pragma_Arg
10303                     ("state conflicts with that given #", Arg2);
10304                   exit;
10305                end if;
10306
10307                IST_Num := IST_Num + 1;
10308             end loop;
10309          end Interrupt_State;
10310
10311          ---------------
10312          -- Invariant --
10313          ---------------
10314
10315          --  pragma Invariant
10316          --    ([Entity =>]    type_LOCAL_NAME,
10317          --     [Check  =>]    EXPRESSION
10318          --     [,[Message =>] String_Expression]);
10319
10320          when Pragma_Invariant => Invariant : declare
10321             Type_Id : Node_Id;
10322             Typ     : Entity_Id;
10323
10324             Discard : Boolean;
10325             pragma Unreferenced (Discard);
10326
10327          begin
10328             GNAT_Pragma;
10329             Check_At_Least_N_Arguments (2);
10330             Check_At_Most_N_Arguments (3);
10331             Check_Optional_Identifier (Arg1, Name_Entity);
10332             Check_Optional_Identifier (Arg2, Name_Check);
10333
10334             if Arg_Count = 3 then
10335                Check_Optional_Identifier (Arg3, Name_Message);
10336                Check_Arg_Is_Static_Expression (Arg3, Standard_String);
10337             end if;
10338
10339             Check_Arg_Is_Local_Name (Arg1);
10340
10341             Type_Id := Get_Pragma_Arg (Arg1);
10342             Find_Type (Type_Id);
10343             Typ := Entity (Type_Id);
10344
10345             if Typ = Any_Type then
10346                return;
10347
10348             --  An invariant must apply to a private type, or appear in the
10349             --  private part of a package spec and apply to a completion.
10350
10351             elsif Ekind_In (Typ, E_Private_Type,
10352                                  E_Record_Type_With_Private,
10353                                  E_Limited_Private_Type)
10354             then
10355                null;
10356
10357             elsif In_Private_Part (Current_Scope)
10358               and then Has_Private_Declaration (Typ)
10359             then
10360                null;
10361
10362             elsif In_Private_Part (Current_Scope) then
10363                Error_Pragma_Arg
10364                  ("pragma% only allowed for private type " &
10365                   "declared in visible part", Arg1);
10366
10367             else
10368                Error_Pragma_Arg
10369                  ("pragma% only allowed for private type", Arg1);
10370             end if;
10371
10372             --  Note that the type has at least one invariant, and also that
10373             --  it has inheritable invariants if we have Invariant'Class.
10374
10375             Set_Has_Invariants (Typ);
10376
10377             if Class_Present (N) then
10378                Set_Has_Inheritable_Invariants (Typ);
10379             end if;
10380
10381             --  The remaining processing is simply to link the pragma on to
10382             --  the rep item chain, for processing when the type is frozen.
10383             --  This is accomplished by a call to Rep_Item_Too_Late.
10384
10385             Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
10386          end Invariant;
10387
10388          ----------------------
10389          -- Java_Constructor --
10390          ----------------------
10391
10392          --  pragma Java_Constructor ([Entity =>] LOCAL_NAME);
10393
10394          --  Also handles pragma CIL_Constructor
10395
10396          when Pragma_CIL_Constructor | Pragma_Java_Constructor =>
10397          Java_Constructor : declare
10398             Convention  : Convention_Id;
10399             Def_Id      : Entity_Id;
10400             Hom_Id      : Entity_Id;
10401             Id          : Entity_Id;
10402             This_Formal : Entity_Id;
10403
10404          begin
10405             GNAT_Pragma;
10406             Check_Arg_Count (1);
10407             Check_Optional_Identifier (Arg1, Name_Entity);
10408             Check_Arg_Is_Local_Name (Arg1);
10409
10410             Id := Get_Pragma_Arg (Arg1);
10411             Find_Program_Unit_Name (Id);
10412
10413             --  If we did not find the name, we are done
10414
10415             if Etype (Id) = Any_Type then
10416                return;
10417             end if;
10418
10419             --  Check wrong use of pragma in wrong VM target
10420
10421             if VM_Target = No_VM then
10422                return;
10423
10424             elsif VM_Target = CLI_Target
10425               and then Prag_Id = Pragma_Java_Constructor
10426             then
10427                Error_Pragma ("must use pragma 'C'I'L_'Constructor");
10428
10429             elsif VM_Target = JVM_Target
10430               and then Prag_Id = Pragma_CIL_Constructor
10431             then
10432                Error_Pragma ("must use pragma 'Java_'Constructor");
10433             end if;
10434
10435             case Prag_Id is
10436                when Pragma_CIL_Constructor  => Convention := Convention_CIL;
10437                when Pragma_Java_Constructor => Convention := Convention_Java;
10438                when others                  => null;
10439             end case;
10440
10441             Hom_Id := Entity (Id);
10442
10443             --  Loop through homonyms
10444
10445             loop
10446                Def_Id := Get_Base_Subprogram (Hom_Id);
10447
10448                --  The constructor is required to be a function
10449
10450                if Ekind (Def_Id) /= E_Function then
10451                   if VM_Target = JVM_Target then
10452                      Error_Pragma_Arg
10453                        ("pragma% requires function returning a " &
10454                         "'Java access type", Def_Id);
10455                   else
10456                      Error_Pragma_Arg
10457                        ("pragma% requires function returning a " &
10458                         "'C'I'L access type", Def_Id);
10459                   end if;
10460                end if;
10461
10462                --  Check arguments: For tagged type the first formal must be
10463                --  named "this" and its type must be a named access type
10464                --  designating a class-wide tagged type that has convention
10465                --  CIL/Java. The first formal must also have a null default
10466                --  value. For example:
10467
10468                --      type Typ is tagged ...
10469                --      type Ref is access all Typ;
10470                --      pragma Convention (CIL, Typ);
10471
10472                --      function New_Typ (This : Ref) return Ref;
10473                --      function New_Typ (This : Ref; I : Integer) return Ref;
10474                --      pragma Cil_Constructor (New_Typ);
10475
10476                --  Reason: The first formal must NOT be a primitive of the
10477                --  tagged type.
10478
10479                --  This rule also applies to constructors of delegates used
10480                --  to interface with standard target libraries. For example:
10481
10482                --      type Delegate is access procedure ...
10483                --      pragma Import (CIL, Delegate, ...);
10484
10485                --      function new_Delegate
10486                --        (This : Delegate := null; ... ) return Delegate;
10487
10488                --  For value-types this rule does not apply.
10489
10490                if not Is_Value_Type (Etype (Def_Id)) then
10491                   if No (First_Formal (Def_Id)) then
10492                      Error_Msg_Name_1 := Pname;
10493                      Error_Msg_N ("% function must have parameters", Def_Id);
10494                      return;
10495                   end if;
10496
10497                   --  In the JRE library we have several occurrences in which
10498                   --  the "this" parameter is not the first formal.
10499
10500                   This_Formal := First_Formal (Def_Id);
10501
10502                   --  In the JRE library we have several occurrences in which
10503                   --  the "this" parameter is not the first formal. Search for
10504                   --  it.
10505
10506                   if VM_Target = JVM_Target then
10507                      while Present (This_Formal)
10508                        and then Get_Name_String (Chars (This_Formal)) /= "this"
10509                      loop
10510                         Next_Formal (This_Formal);
10511                      end loop;
10512
10513                      if No (This_Formal) then
10514                         This_Formal := First_Formal (Def_Id);
10515                      end if;
10516                   end if;
10517
10518                   --  Warning: The first parameter should be named "this".
10519                   --  We temporarily allow it because we have the following
10520                   --  case in the Java runtime (file s-osinte.ads) ???
10521
10522                   --    function new_Thread
10523                   --      (Self_Id : System.Address) return Thread_Id;
10524                   --    pragma Java_Constructor (new_Thread);
10525
10526                   if VM_Target = JVM_Target
10527                     and then Get_Name_String (Chars (First_Formal (Def_Id)))
10528                                = "self_id"
10529                     and then Etype (First_Formal (Def_Id)) = RTE (RE_Address)
10530                   then
10531                      null;
10532
10533                   elsif Get_Name_String (Chars (This_Formal)) /= "this" then
10534                      Error_Msg_Name_1 := Pname;
10535                      Error_Msg_N
10536                        ("first formal of % function must be named `this`",
10537                         Parent (This_Formal));
10538
10539                   elsif not Is_Access_Type (Etype (This_Formal)) then
10540                      Error_Msg_Name_1 := Pname;
10541                      Error_Msg_N
10542                        ("first formal of % function must be an access type",
10543                         Parameter_Type (Parent (This_Formal)));
10544
10545                   --  For delegates the type of the first formal must be a
10546                   --  named access-to-subprogram type (see previous example)
10547
10548                   elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type
10549                     and then Ekind (Etype (This_Formal))
10550                                /= E_Access_Subprogram_Type
10551                   then
10552                      Error_Msg_Name_1 := Pname;
10553                      Error_Msg_N
10554                        ("first formal of % function must be a named access" &
10555                         " to subprogram type",
10556                         Parameter_Type (Parent (This_Formal)));
10557
10558                   --  Warning: We should reject anonymous access types because
10559                   --  the constructor must not be handled as a primitive of the
10560                   --  tagged type. We temporarily allow it because this profile
10561                   --  is currently generated by cil2ada???
10562
10563                   elsif Ekind (Etype (Def_Id)) /= E_Access_Subprogram_Type
10564                     and then not Ekind_In (Etype (This_Formal),
10565                                              E_Access_Type,
10566                                              E_General_Access_Type,
10567                                              E_Anonymous_Access_Type)
10568                   then
10569                      Error_Msg_Name_1 := Pname;
10570                      Error_Msg_N
10571                        ("first formal of % function must be a named access" &
10572                         " type",
10573                         Parameter_Type (Parent (This_Formal)));
10574
10575                   elsif Atree.Convention
10576                          (Designated_Type (Etype (This_Formal))) /= Convention
10577                   then
10578                      Error_Msg_Name_1 := Pname;
10579
10580                      if Convention = Convention_Java then
10581                         Error_Msg_N
10582                           ("pragma% requires convention 'Cil in designated" &
10583                            " type",
10584                            Parameter_Type (Parent (This_Formal)));
10585                      else
10586                         Error_Msg_N
10587                           ("pragma% requires convention 'Java in designated" &
10588                            " type",
10589                            Parameter_Type (Parent (This_Formal)));
10590                      end if;
10591
10592                   elsif No (Expression (Parent (This_Formal)))
10593                     or else Nkind (Expression (Parent (This_Formal))) /= N_Null
10594                   then
10595                      Error_Msg_Name_1 := Pname;
10596                      Error_Msg_N
10597                        ("pragma% requires first formal with default `null`",
10598                         Parameter_Type (Parent (This_Formal)));
10599                   end if;
10600                end if;
10601
10602                --  Check result type: the constructor must be a function
10603                --  returning:
10604                --   * a value type (only allowed in the CIL compiler)
10605                --   * an access-to-subprogram type with convention Java/CIL
10606                --   * an access-type designating a type that has convention
10607                --     Java/CIL.
10608
10609                if Is_Value_Type (Etype (Def_Id)) then
10610                   null;
10611
10612                --  Access-to-subprogram type with convention Java/CIL
10613
10614                elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type then
10615                   if Atree.Convention (Etype (Def_Id)) /= Convention then
10616                      if Convention = Convention_Java then
10617                         Error_Pragma_Arg
10618                           ("pragma% requires function returning a " &
10619                            "'Java access type", Arg1);
10620                      else
10621                         pragma Assert (Convention = Convention_CIL);
10622                         Error_Pragma_Arg
10623                           ("pragma% requires function returning a " &
10624                            "'C'I'L access type", Arg1);
10625                      end if;
10626                   end if;
10627
10628                elsif Ekind (Etype (Def_Id)) in Access_Kind then
10629                   if not Ekind_In (Etype (Def_Id), E_Access_Type,
10630                                                    E_General_Access_Type)
10631                     or else
10632                       Atree.Convention
10633                         (Designated_Type (Etype (Def_Id))) /= Convention
10634                   then
10635                      Error_Msg_Name_1 := Pname;
10636
10637                      if Convention = Convention_Java then
10638                         Error_Pragma_Arg
10639                           ("pragma% requires function returning a named" &
10640                            "'Java access type", Arg1);
10641                      else
10642                         Error_Pragma_Arg
10643                           ("pragma% requires function returning a named" &
10644                            "'C'I'L access type", Arg1);
10645                      end if;
10646                   end if;
10647                end if;
10648
10649                Set_Is_Constructor (Def_Id);
10650                Set_Convention     (Def_Id, Convention);
10651                Set_Is_Imported    (Def_Id);
10652
10653                exit when From_Aspect_Specification (N);
10654                Hom_Id := Homonym (Hom_Id);
10655
10656                exit when No (Hom_Id) or else Scope (Hom_Id) /= Current_Scope;
10657             end loop;
10658          end Java_Constructor;
10659
10660          ----------------------
10661          -- Java_Interface --
10662          ----------------------
10663
10664          --  pragma Java_Interface ([Entity =>] LOCAL_NAME);
10665
10666          when Pragma_Java_Interface => Java_Interface : declare
10667             Arg : Node_Id;
10668             Typ : Entity_Id;
10669
10670          begin
10671             GNAT_Pragma;
10672             Check_Arg_Count (1);
10673             Check_Optional_Identifier (Arg1, Name_Entity);
10674             Check_Arg_Is_Local_Name (Arg1);
10675
10676             Arg := Get_Pragma_Arg (Arg1);
10677             Analyze (Arg);
10678
10679             if Etype (Arg) = Any_Type then
10680                return;
10681             end if;
10682
10683             if not Is_Entity_Name (Arg)
10684               or else not Is_Type (Entity (Arg))
10685             then
10686                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
10687             end if;
10688
10689             Typ := Underlying_Type (Entity (Arg));
10690
10691             --  For now simply check some of the semantic constraints on the
10692             --  type. This currently leaves out some restrictions on interface
10693             --  types, namely that the parent type must be java.lang.Object.Typ
10694             --  and that all primitives of the type should be declared
10695             --  abstract. ???
10696
10697             if not Is_Tagged_Type (Typ) or else not Is_Abstract_Type (Typ) then
10698                Error_Pragma_Arg ("pragma% requires an abstract "
10699                  & "tagged type", Arg1);
10700
10701             elsif not Has_Discriminants (Typ)
10702               or else Ekind (Etype (First_Discriminant (Typ)))
10703                         /= E_Anonymous_Access_Type
10704               or else
10705                 not Is_Class_Wide_Type
10706                       (Designated_Type (Etype (First_Discriminant (Typ))))
10707             then
10708                Error_Pragma_Arg
10709                  ("type must have a class-wide access discriminant", Arg1);
10710             end if;
10711          end Java_Interface;
10712
10713          ----------------
10714          -- Keep_Names --
10715          ----------------
10716
10717          --  pragma Keep_Names ([On => ] local_NAME);
10718
10719          when Pragma_Keep_Names => Keep_Names : declare
10720             Arg : Node_Id;
10721
10722          begin
10723             GNAT_Pragma;
10724             Check_Arg_Count (1);
10725             Check_Optional_Identifier (Arg1, Name_On);
10726             Check_Arg_Is_Local_Name (Arg1);
10727
10728             Arg := Get_Pragma_Arg (Arg1);
10729             Analyze (Arg);
10730
10731             if Etype (Arg) = Any_Type then
10732                return;
10733             end if;
10734
10735             if not Is_Entity_Name (Arg)
10736               or else Ekind (Entity (Arg)) /= E_Enumeration_Type
10737             then
10738                Error_Pragma_Arg
10739                  ("pragma% requires a local enumeration type", Arg1);
10740             end if;
10741
10742             Set_Discard_Names (Entity (Arg), False);
10743          end Keep_Names;
10744
10745          -------------
10746          -- License --
10747          -------------
10748
10749          --  pragma License (RESTRICTED | UNRESTRICTED | GPL | MODIFIED_GPL);
10750
10751          when Pragma_License =>
10752             GNAT_Pragma;
10753             Check_Arg_Count (1);
10754             Check_No_Identifiers;
10755             Check_Valid_Configuration_Pragma;
10756             Check_Arg_Is_Identifier (Arg1);
10757
10758             declare
10759                Sind : constant Source_File_Index :=
10760                         Source_Index (Current_Sem_Unit);
10761
10762             begin
10763                case Chars (Get_Pragma_Arg (Arg1)) is
10764                   when Name_GPL =>
10765                      Set_License (Sind, GPL);
10766
10767                   when Name_Modified_GPL =>
10768                      Set_License (Sind, Modified_GPL);
10769
10770                   when Name_Restricted =>
10771                      Set_License (Sind, Restricted);
10772
10773                   when Name_Unrestricted =>
10774                      Set_License (Sind, Unrestricted);
10775
10776                   when others =>
10777                      Error_Pragma_Arg ("invalid license name", Arg1);
10778                end case;
10779             end;
10780
10781          ---------------
10782          -- Link_With --
10783          ---------------
10784
10785          --  pragma Link_With (string_EXPRESSION {, string_EXPRESSION});
10786
10787          when Pragma_Link_With => Link_With : declare
10788             Arg : Node_Id;
10789
10790          begin
10791             GNAT_Pragma;
10792
10793             if Operating_Mode = Generate_Code
10794               and then In_Extended_Main_Source_Unit (N)
10795             then
10796                Check_At_Least_N_Arguments (1);
10797                Check_No_Identifiers;
10798                Check_Is_In_Decl_Part_Or_Package_Spec;
10799                Check_Arg_Is_Static_Expression (Arg1, Standard_String);
10800                Start_String;
10801
10802                Arg := Arg1;
10803                while Present (Arg) loop
10804                   Check_Arg_Is_Static_Expression (Arg, Standard_String);
10805
10806                   --  Store argument, converting sequences of spaces to a
10807                   --  single null character (this is one of the differences
10808                   --  in processing between Link_With and Linker_Options).
10809
10810                   Arg_Store : declare
10811                      C : constant Char_Code := Get_Char_Code (' ');
10812                      S : constant String_Id :=
10813                            Strval (Expr_Value_S (Get_Pragma_Arg (Arg)));
10814                      L : constant Nat := String_Length (S);
10815                      F : Nat := 1;
10816
10817                      procedure Skip_Spaces;
10818                      --  Advance F past any spaces
10819
10820                      -----------------
10821                      -- Skip_Spaces --
10822                      -----------------
10823
10824                      procedure Skip_Spaces is
10825                      begin
10826                         while F <= L and then Get_String_Char (S, F) = C loop
10827                            F := F + 1;
10828                         end loop;
10829                      end Skip_Spaces;
10830
10831                   --  Start of processing for Arg_Store
10832
10833                   begin
10834                      Skip_Spaces; -- skip leading spaces
10835
10836                      --  Loop through characters, changing any embedded
10837                      --  sequence of spaces to a single null character (this
10838                      --  is how Link_With/Linker_Options differ)
10839
10840                      while F <= L loop
10841                         if Get_String_Char (S, F) = C then
10842                            Skip_Spaces;
10843                            exit when F > L;
10844                            Store_String_Char (ASCII.NUL);
10845
10846                         else
10847                            Store_String_Char (Get_String_Char (S, F));
10848                            F := F + 1;
10849                         end if;
10850                      end loop;
10851                   end Arg_Store;
10852
10853                   Arg := Next (Arg);
10854
10855                   if Present (Arg) then
10856                      Store_String_Char (ASCII.NUL);
10857                   end if;
10858                end loop;
10859
10860                Store_Linker_Option_String (End_String);
10861             end if;
10862          end Link_With;
10863
10864          ------------------
10865          -- Linker_Alias --
10866          ------------------
10867
10868          --  pragma Linker_Alias (
10869          --      [Entity =>]  LOCAL_NAME
10870          --      [Target =>]  static_string_EXPRESSION);
10871
10872          when Pragma_Linker_Alias =>
10873             GNAT_Pragma;
10874             Check_Arg_Order ((Name_Entity, Name_Target));
10875             Check_Arg_Count (2);
10876             Check_Optional_Identifier (Arg1, Name_Entity);
10877             Check_Optional_Identifier (Arg2, Name_Target);
10878             Check_Arg_Is_Library_Level_Local_Name (Arg1);
10879             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10880
10881             --  The only processing required is to link this item on to the
10882             --  list of rep items for the given entity. This is accomplished
10883             --  by the call to Rep_Item_Too_Late (when no error is detected
10884             --  and False is returned).
10885
10886             if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
10887                return;
10888             else
10889                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10890             end if;
10891
10892          ------------------------
10893          -- Linker_Constructor --
10894          ------------------------
10895
10896          --  pragma Linker_Constructor (procedure_LOCAL_NAME);
10897
10898          --  Code is shared with Linker_Destructor
10899
10900          -----------------------
10901          -- Linker_Destructor --
10902          -----------------------
10903
10904          --  pragma Linker_Destructor (procedure_LOCAL_NAME);
10905
10906          when Pragma_Linker_Constructor |
10907               Pragma_Linker_Destructor =>
10908          Linker_Constructor : declare
10909             Arg1_X : Node_Id;
10910             Proc   : Entity_Id;
10911
10912          begin
10913             GNAT_Pragma;
10914             Check_Arg_Count (1);
10915             Check_No_Identifiers;
10916             Check_Arg_Is_Local_Name (Arg1);
10917             Arg1_X := Get_Pragma_Arg (Arg1);
10918             Analyze (Arg1_X);
10919             Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
10920
10921             if not Is_Library_Level_Entity (Proc) then
10922                Error_Pragma_Arg
10923                 ("argument for pragma% must be library level entity", Arg1);
10924             end if;
10925
10926             --  The only processing required is to link this item on to the
10927             --  list of rep items for the given entity. This is accomplished
10928             --  by the call to Rep_Item_Too_Late (when no error is detected
10929             --  and False is returned).
10930
10931             if Rep_Item_Too_Late (Proc, N) then
10932                return;
10933             else
10934                Set_Has_Gigi_Rep_Item (Proc);
10935             end if;
10936          end Linker_Constructor;
10937
10938          --------------------
10939          -- Linker_Options --
10940          --------------------
10941
10942          --  pragma Linker_Options (string_EXPRESSION {, string_EXPRESSION});
10943
10944          when Pragma_Linker_Options => Linker_Options : declare
10945             Arg : Node_Id;
10946
10947          begin
10948             Check_Ada_83_Warning;
10949             Check_No_Identifiers;
10950             Check_Arg_Count (1);
10951             Check_Is_In_Decl_Part_Or_Package_Spec;
10952             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
10953             Start_String (Strval (Expr_Value_S (Get_Pragma_Arg (Arg1))));
10954
10955             Arg := Arg2;
10956             while Present (Arg) loop
10957                Check_Arg_Is_Static_Expression (Arg, Standard_String);
10958                Store_String_Char (ASCII.NUL);
10959                Store_String_Chars
10960                  (Strval (Expr_Value_S (Get_Pragma_Arg (Arg))));
10961                Arg := Next (Arg);
10962             end loop;
10963
10964             if Operating_Mode = Generate_Code
10965               and then In_Extended_Main_Source_Unit (N)
10966             then
10967                Store_Linker_Option_String (End_String);
10968             end if;
10969          end Linker_Options;
10970
10971          --------------------
10972          -- Linker_Section --
10973          --------------------
10974
10975          --  pragma Linker_Section (
10976          --      [Entity  =>]  LOCAL_NAME
10977          --      [Section =>]  static_string_EXPRESSION);
10978
10979          when Pragma_Linker_Section =>
10980             GNAT_Pragma;
10981             Check_Arg_Order ((Name_Entity, Name_Section));
10982             Check_Arg_Count (2);
10983             Check_Optional_Identifier (Arg1, Name_Entity);
10984             Check_Optional_Identifier (Arg2, Name_Section);
10985             Check_Arg_Is_Library_Level_Local_Name (Arg1);
10986             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10987
10988             --  This pragma applies only to objects
10989
10990             if not Is_Object (Entity (Get_Pragma_Arg (Arg1))) then
10991                Error_Pragma_Arg ("pragma% applies only to objects", Arg1);
10992             end if;
10993
10994             --  The only processing required is to link this item on to the
10995             --  list of rep items for the given entity. This is accomplished
10996             --  by the call to Rep_Item_Too_Late (when no error is detected
10997             --  and False is returned).
10998
10999             if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
11000                return;
11001             else
11002                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
11003             end if;
11004
11005          ----------
11006          -- List --
11007          ----------
11008
11009          --  pragma List (On | Off)
11010
11011          --  There is nothing to do here, since we did all the processing for
11012          --  this pragma in Par.Prag (so that it works properly even in syntax
11013          --  only mode).
11014
11015          when Pragma_List =>
11016             null;
11017
11018          --------------------
11019          -- Locking_Policy --
11020          --------------------
11021
11022          --  pragma Locking_Policy (policy_IDENTIFIER);
11023
11024          when Pragma_Locking_Policy => declare
11025             subtype LP_Range is Name_Id
11026               range First_Locking_Policy_Name .. Last_Locking_Policy_Name;
11027             LP_Val : LP_Range;
11028             LP     : Character;
11029          begin
11030             Check_Ada_83_Warning;
11031             Check_Arg_Count (1);
11032             Check_No_Identifiers;
11033             Check_Arg_Is_Locking_Policy (Arg1);
11034             Check_Valid_Configuration_Pragma;
11035             LP_Val := Chars (Get_Pragma_Arg (Arg1));
11036
11037             case LP_Val is
11038                when Name_Ceiling_Locking            => LP := 'C';
11039                when Name_Inheritance_Locking        => LP := 'I';
11040                when Name_Concurrent_Readers_Locking => LP := 'R';
11041             end case;
11042
11043             if Locking_Policy /= ' '
11044               and then Locking_Policy /= LP
11045             then
11046                Error_Msg_Sloc := Locking_Policy_Sloc;
11047                Error_Pragma ("locking policy incompatible with policy#");
11048
11049             --  Set new policy, but always preserve System_Location since we
11050             --  like the error message with the run time name.
11051
11052             else
11053                Locking_Policy := LP;
11054
11055                if Locking_Policy_Sloc /= System_Location then
11056                   Locking_Policy_Sloc := Loc;
11057                end if;
11058             end if;
11059          end;
11060
11061          ----------------
11062          -- Long_Float --
11063          ----------------
11064
11065          --  pragma Long_Float (D_Float | G_Float);
11066
11067          when Pragma_Long_Float => Long_Float : declare
11068          begin
11069             GNAT_Pragma;
11070             Check_Valid_Configuration_Pragma;
11071             Check_Arg_Count (1);
11072             Check_No_Identifier (Arg1);
11073             Check_Arg_Is_One_Of (Arg1, Name_D_Float, Name_G_Float);
11074
11075             if not OpenVMS_On_Target then
11076                Error_Pragma ("?pragma% ignored (applies only to Open'V'M'S)");
11077             end if;
11078
11079             --  D_Float case
11080
11081             if Chars (Get_Pragma_Arg (Arg1)) = Name_D_Float then
11082                if Opt.Float_Format_Long = 'G' then
11083                   Error_Pragma_Arg
11084                     ("G_Float previously specified", Arg1);
11085
11086                elsif Current_Sem_Unit /= Main_Unit
11087                  and then Opt.Float_Format_Long /= 'D'
11088                then
11089                   Error_Pragma_Arg
11090                     ("main unit not compiled with pragma Long_Float (D_Float)",
11091                      "\pragma% must be used consistently for whole partition",
11092                      Arg1);
11093
11094                else
11095                   Opt.Float_Format_Long := 'D';
11096                end if;
11097
11098             --  G_Float case (this is the default, does not need overriding)
11099
11100             else
11101                if Opt.Float_Format_Long = 'D' then
11102                   Error_Pragma ("D_Float previously specified");
11103
11104                elsif Current_Sem_Unit /= Main_Unit
11105                  and then Opt.Float_Format_Long /= 'G'
11106                then
11107                   Error_Pragma_Arg
11108                     ("main unit not compiled with pragma Long_Float (G_Float)",
11109                      "\pragma% must be used consistently for whole partition",
11110                      Arg1);
11111
11112                else
11113                   Opt.Float_Format_Long := 'G';
11114                end if;
11115             end if;
11116
11117             Set_Standard_Fpt_Formats;
11118          end Long_Float;
11119
11120          -----------------------
11121          -- Machine_Attribute --
11122          -----------------------
11123
11124          --  pragma Machine_Attribute (
11125          --       [Entity         =>] LOCAL_NAME,
11126          --       [Attribute_Name =>] static_string_EXPRESSION
11127          --    [, [Info           =>] static_EXPRESSION] );
11128
11129          when Pragma_Machine_Attribute => Machine_Attribute : declare
11130             Def_Id : Entity_Id;
11131
11132          begin
11133             GNAT_Pragma;
11134             Check_Arg_Order ((Name_Entity, Name_Attribute_Name, Name_Info));
11135
11136             if Arg_Count = 3 then
11137                Check_Optional_Identifier (Arg3, Name_Info);
11138                Check_Arg_Is_Static_Expression (Arg3);
11139             else
11140                Check_Arg_Count (2);
11141             end if;
11142
11143             Check_Optional_Identifier (Arg1, Name_Entity);
11144             Check_Optional_Identifier (Arg2, Name_Attribute_Name);
11145             Check_Arg_Is_Local_Name (Arg1);
11146             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
11147             Def_Id := Entity (Get_Pragma_Arg (Arg1));
11148
11149             if Is_Access_Type (Def_Id) then
11150                Def_Id := Designated_Type (Def_Id);
11151             end if;
11152
11153             if Rep_Item_Too_Early (Def_Id, N) then
11154                return;
11155             end if;
11156
11157             Def_Id := Underlying_Type (Def_Id);
11158
11159             --  The only processing required is to link this item on to the
11160             --  list of rep items for the given entity. This is accomplished
11161             --  by the call to Rep_Item_Too_Late (when no error is detected
11162             --  and False is returned).
11163
11164             if Rep_Item_Too_Late (Def_Id, N) then
11165                return;
11166             else
11167                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
11168             end if;
11169          end Machine_Attribute;
11170
11171          ----------
11172          -- Main --
11173          ----------
11174
11175          --  pragma Main
11176          --   (MAIN_OPTION [, MAIN_OPTION]);
11177
11178          --  MAIN_OPTION ::=
11179          --    [STACK_SIZE              =>] static_integer_EXPRESSION
11180          --  | [TASK_STACK_SIZE_DEFAULT =>] static_integer_EXPRESSION
11181          --  | [TIME_SLICING_ENABLED    =>] static_boolean_EXPRESSION
11182
11183          when Pragma_Main => Main : declare
11184             Args  : Args_List (1 .. 3);
11185             Names : constant Name_List (1 .. 3) := (
11186                       Name_Stack_Size,
11187                       Name_Task_Stack_Size_Default,
11188                       Name_Time_Slicing_Enabled);
11189
11190             Nod : Node_Id;
11191
11192          begin
11193             GNAT_Pragma;
11194             Gather_Associations (Names, Args);
11195
11196             for J in 1 .. 2 loop
11197                if Present (Args (J)) then
11198                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
11199                end if;
11200             end loop;
11201
11202             if Present (Args (3)) then
11203                Check_Arg_Is_Static_Expression (Args (3), Standard_Boolean);
11204             end if;
11205
11206             Nod := Next (N);
11207             while Present (Nod) loop
11208                if Nkind (Nod) = N_Pragma
11209                  and then Pragma_Name (Nod) = Name_Main
11210                then
11211                   Error_Msg_Name_1 := Pname;
11212                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
11213                end if;
11214
11215                Next (Nod);
11216             end loop;
11217          end Main;
11218
11219          ------------------
11220          -- Main_Storage --
11221          ------------------
11222
11223          --  pragma Main_Storage
11224          --   (MAIN_STORAGE_OPTION [, MAIN_STORAGE_OPTION]);
11225
11226          --  MAIN_STORAGE_OPTION ::=
11227          --    [WORKING_STORAGE =>] static_SIMPLE_EXPRESSION
11228          --  | [TOP_GUARD =>] static_SIMPLE_EXPRESSION
11229
11230          when Pragma_Main_Storage => Main_Storage : declare
11231             Args  : Args_List (1 .. 2);
11232             Names : constant Name_List (1 .. 2) := (
11233                       Name_Working_Storage,
11234                       Name_Top_Guard);
11235
11236             Nod : Node_Id;
11237
11238          begin
11239             GNAT_Pragma;
11240             Gather_Associations (Names, Args);
11241
11242             for J in 1 .. 2 loop
11243                if Present (Args (J)) then
11244                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
11245                end if;
11246             end loop;
11247
11248             Check_In_Main_Program;
11249
11250             Nod := Next (N);
11251             while Present (Nod) loop
11252                if Nkind (Nod) = N_Pragma
11253                  and then Pragma_Name (Nod) = Name_Main_Storage
11254                then
11255                   Error_Msg_Name_1 := Pname;
11256                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
11257                end if;
11258
11259                Next (Nod);
11260             end loop;
11261          end Main_Storage;
11262
11263          -----------------
11264          -- Memory_Size --
11265          -----------------
11266
11267          --  pragma Memory_Size (NUMERIC_LITERAL)
11268
11269          when Pragma_Memory_Size =>
11270             GNAT_Pragma;
11271
11272             --  Memory size is simply ignored
11273
11274             Check_No_Identifiers;
11275             Check_Arg_Count (1);
11276             Check_Arg_Is_Integer_Literal (Arg1);
11277
11278          -------------
11279          -- No_Body --
11280          -------------
11281
11282          --  pragma No_Body;
11283
11284          --  The only correct use of this pragma is on its own in a file, in
11285          --  which case it is specially processed (see Gnat1drv.Check_Bad_Body
11286          --  and Frontend, which use Sinput.L.Source_File_Is_Pragma_No_Body to
11287          --  check for a file containing nothing but a No_Body pragma). If we
11288          --  attempt to process it during normal semantics processing, it means
11289          --  it was misplaced.
11290
11291          when Pragma_No_Body =>
11292             GNAT_Pragma;
11293             Pragma_Misplaced;
11294
11295          ---------------
11296          -- No_Return --
11297          ---------------
11298
11299          --  pragma No_Return (procedure_LOCAL_NAME {, procedure_Local_Name});
11300
11301          when Pragma_No_Return => No_Return : declare
11302             Id    : Node_Id;
11303             E     : Entity_Id;
11304             Found : Boolean;
11305             Arg   : Node_Id;
11306
11307          begin
11308             Ada_2005_Pragma;
11309             Check_At_Least_N_Arguments (1);
11310
11311             --  Loop through arguments of pragma
11312
11313             Arg := Arg1;
11314             while Present (Arg) loop
11315                Check_Arg_Is_Local_Name (Arg);
11316                Id := Get_Pragma_Arg (Arg);
11317                Analyze (Id);
11318
11319                if not Is_Entity_Name (Id) then
11320                   Error_Pragma_Arg ("entity name required", Arg);
11321                end if;
11322
11323                if Etype (Id) = Any_Type then
11324                   raise Pragma_Exit;
11325                end if;
11326
11327                --  Loop to find matching procedures
11328
11329                E := Entity (Id);
11330                Found := False;
11331                while Present (E)
11332                  and then Scope (E) = Current_Scope
11333                loop
11334                   if Ekind_In (E, E_Procedure, E_Generic_Procedure) then
11335                      Set_No_Return (E);
11336
11337                      --  Set flag on any alias as well
11338
11339                      if Is_Overloadable (E) and then Present (Alias (E)) then
11340                         Set_No_Return (Alias (E));
11341                      end if;
11342
11343                      Found := True;
11344                   end if;
11345
11346                   exit when From_Aspect_Specification (N);
11347                   E := Homonym (E);
11348                end loop;
11349
11350                if not Found then
11351                   Error_Pragma_Arg ("no procedure & found for pragma%", Arg);
11352                end if;
11353
11354                Next (Arg);
11355             end loop;
11356          end No_Return;
11357
11358          -----------------
11359          -- No_Run_Time --
11360          -----------------
11361
11362          --  pragma No_Run_Time;
11363
11364          --  Note: this pragma is retained for backwards compatibility. See
11365          --  body of Rtsfind for full details on its handling.
11366
11367          when Pragma_No_Run_Time =>
11368             GNAT_Pragma;
11369             Check_Valid_Configuration_Pragma;
11370             Check_Arg_Count (0);
11371
11372             No_Run_Time_Mode           := True;
11373             Configurable_Run_Time_Mode := True;
11374
11375             --  Set Duration to 32 bits if word size is 32
11376
11377             if Ttypes.System_Word_Size = 32 then
11378                Duration_32_Bits_On_Target := True;
11379             end if;
11380
11381             --  Set appropriate restrictions
11382
11383             Set_Restriction (No_Finalization, N);
11384             Set_Restriction (No_Exception_Handlers, N);
11385             Set_Restriction (Max_Tasks, N, 0);
11386             Set_Restriction (No_Tasking, N);
11387
11388          ------------------------
11389          -- No_Strict_Aliasing --
11390          ------------------------
11391
11392          --  pragma No_Strict_Aliasing [([Entity =>] type_LOCAL_NAME)];
11393
11394          when Pragma_No_Strict_Aliasing => No_Strict_Aliasing : declare
11395             E_Id : Entity_Id;
11396
11397          begin
11398             GNAT_Pragma;
11399             Check_At_Most_N_Arguments (1);
11400
11401             if Arg_Count = 0 then
11402                Check_Valid_Configuration_Pragma;
11403                Opt.No_Strict_Aliasing := True;
11404
11405             else
11406                Check_Optional_Identifier (Arg2, Name_Entity);
11407                Check_Arg_Is_Local_Name (Arg1);
11408                E_Id := Entity (Get_Pragma_Arg (Arg1));
11409
11410                if E_Id = Any_Type then
11411                   return;
11412                elsif No (E_Id) or else not Is_Access_Type (E_Id) then
11413                   Error_Pragma_Arg ("pragma% requires access type", Arg1);
11414                end if;
11415
11416                Set_No_Strict_Aliasing (Implementation_Base_Type (E_Id));
11417             end if;
11418          end No_Strict_Aliasing;
11419
11420          -----------------------
11421          -- Normalize_Scalars --
11422          -----------------------
11423
11424          --  pragma Normalize_Scalars;
11425
11426          when Pragma_Normalize_Scalars =>
11427             Check_Ada_83_Warning;
11428             Check_Arg_Count (0);
11429             Check_Valid_Configuration_Pragma;
11430
11431             --  Normalize_Scalars creates false positives in CodePeer, and
11432             --  incorrect negative results in Alfa mode, so ignore this pragma
11433             --  in these modes.
11434
11435             if not (CodePeer_Mode or Alfa_Mode) then
11436                Normalize_Scalars := True;
11437                Init_Or_Norm_Scalars := True;
11438             end if;
11439
11440          -----------------
11441          -- Obsolescent --
11442          -----------------
11443
11444          --  pragma Obsolescent;
11445
11446          --  pragma Obsolescent (
11447          --    [Message =>] static_string_EXPRESSION
11448          --  [,[Version =>] Ada_05]]);
11449
11450          --  pragma Obsolescent (
11451          --    [Entity  =>] NAME
11452          --  [,[Message =>] static_string_EXPRESSION
11453          --  [,[Version =>] Ada_05]] );
11454
11455          when Pragma_Obsolescent => Obsolescent : declare
11456             Ename : Node_Id;
11457             Decl  : Node_Id;
11458
11459             procedure Set_Obsolescent (E : Entity_Id);
11460             --  Given an entity Ent, mark it as obsolescent if appropriate
11461
11462             ---------------------
11463             -- Set_Obsolescent --
11464             ---------------------
11465
11466             procedure Set_Obsolescent (E : Entity_Id) is
11467                Active : Boolean;
11468                Ent    : Entity_Id;
11469                S      : String_Id;
11470
11471             begin
11472                Active := True;
11473                Ent    := E;
11474
11475                --  Entity name was given
11476
11477                if Present (Ename) then
11478
11479                   --  If entity name matches, we are fine. Save entity in
11480                   --  pragma argument, for ASIS use.
11481
11482                   if Chars (Ename) = Chars (Ent) then
11483                      Set_Entity (Ename, Ent);
11484                      Generate_Reference (Ent, Ename);
11485
11486                   --  If entity name does not match, only possibility is an
11487                   --  enumeration literal from an enumeration type declaration.
11488
11489                   elsif Ekind (Ent) /= E_Enumeration_Type then
11490                      Error_Pragma
11491                        ("pragma % entity name does not match declaration");
11492
11493                   else
11494                      Ent := First_Literal (E);
11495                      loop
11496                         if No (Ent) then
11497                            Error_Pragma
11498                              ("pragma % entity name does not match any " &
11499                               "enumeration literal");
11500
11501                         elsif Chars (Ent) = Chars (Ename) then
11502                            Set_Entity (Ename, Ent);
11503                            Generate_Reference (Ent, Ename);
11504                            exit;
11505
11506                         else
11507                            Ent := Next_Literal (Ent);
11508                         end if;
11509                      end loop;
11510                   end if;
11511                end if;
11512
11513                --  Ent points to entity to be marked
11514
11515                if Arg_Count >= 1 then
11516
11517                   --  Deal with static string argument
11518
11519                   Check_Arg_Is_Static_Expression (Arg1, Standard_String);
11520                   S := Strval (Get_Pragma_Arg (Arg1));
11521
11522                   for J in 1 .. String_Length (S) loop
11523                      if not In_Character_Range (Get_String_Char (S, J)) then
11524                         Error_Pragma_Arg
11525                           ("pragma% argument does not allow wide characters",
11526                            Arg1);
11527                      end if;
11528                   end loop;
11529
11530                   Obsolescent_Warnings.Append
11531                     ((Ent => Ent, Msg => Strval (Get_Pragma_Arg (Arg1))));
11532
11533                   --  Check for Ada_05 parameter
11534
11535                   if Arg_Count /= 1 then
11536                      Check_Arg_Count (2);
11537
11538                      declare
11539                         Argx : constant Node_Id := Get_Pragma_Arg (Arg2);
11540
11541                      begin
11542                         Check_Arg_Is_Identifier (Argx);
11543
11544                         if Chars (Argx) /= Name_Ada_05 then
11545                            Error_Msg_Name_2 := Name_Ada_05;
11546                            Error_Pragma_Arg
11547                              ("only allowed argument for pragma% is %", Argx);
11548                         end if;
11549
11550                         if Ada_Version_Explicit < Ada_2005
11551                           or else not Warn_On_Ada_2005_Compatibility
11552                         then
11553                            Active := False;
11554                         end if;
11555                      end;
11556                   end if;
11557                end if;
11558
11559                --  Set flag if pragma active
11560
11561                if Active then
11562                   Set_Is_Obsolescent (Ent);
11563                end if;
11564
11565                return;
11566             end Set_Obsolescent;
11567
11568          --  Start of processing for pragma Obsolescent
11569
11570          begin
11571             GNAT_Pragma;
11572
11573             Check_At_Most_N_Arguments (3);
11574
11575             --  See if first argument specifies an entity name
11576
11577             if Arg_Count >= 1
11578               and then
11579                 (Chars (Arg1) = Name_Entity
11580                    or else
11581                      Nkind_In (Get_Pragma_Arg (Arg1), N_Character_Literal,
11582                                                       N_Identifier,
11583                                                       N_Operator_Symbol))
11584             then
11585                Ename := Get_Pragma_Arg (Arg1);
11586
11587                --  Eliminate first argument, so we can share processing
11588
11589                Arg1 := Arg2;
11590                Arg2 := Arg3;
11591                Arg_Count := Arg_Count - 1;
11592
11593             --  No Entity name argument given
11594
11595             else
11596                Ename := Empty;
11597             end if;
11598
11599             if Arg_Count >= 1 then
11600                Check_Optional_Identifier (Arg1, Name_Message);
11601
11602                if Arg_Count = 2 then
11603                   Check_Optional_Identifier (Arg2, Name_Version);
11604                end if;
11605             end if;
11606
11607             --  Get immediately preceding declaration
11608
11609             Decl := Prev (N);
11610             while Present (Decl) and then Nkind (Decl) = N_Pragma loop
11611                Prev (Decl);
11612             end loop;
11613
11614             --  Cases where we do not follow anything other than another pragma
11615
11616             if No (Decl) then
11617
11618                --  First case: library level compilation unit declaration with
11619                --  the pragma immediately following the declaration.
11620
11621                if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
11622                   Set_Obsolescent
11623                     (Defining_Entity (Unit (Parent (Parent (N)))));
11624                   return;
11625
11626                --  Case 2: library unit placement for package
11627
11628                else
11629                   declare
11630                      Ent : constant Entity_Id := Find_Lib_Unit_Name;
11631                   begin
11632                      if Is_Package_Or_Generic_Package (Ent) then
11633                         Set_Obsolescent (Ent);
11634                         return;
11635                      end if;
11636                   end;
11637                end if;
11638
11639             --  Cases where we must follow a declaration
11640
11641             else
11642                if         Nkind (Decl) not in N_Declaration
11643                  and then Nkind (Decl) not in N_Later_Decl_Item
11644                  and then Nkind (Decl) not in N_Generic_Declaration
11645                  and then Nkind (Decl) not in N_Renaming_Declaration
11646                then
11647                   Error_Pragma
11648                     ("pragma% misplaced, "
11649                      & "must immediately follow a declaration");
11650
11651                else
11652                   Set_Obsolescent (Defining_Entity (Decl));
11653                   return;
11654                end if;
11655             end if;
11656          end Obsolescent;
11657
11658          --------------
11659          -- Optimize --
11660          --------------
11661
11662          --  pragma Optimize (Time | Space | Off);
11663
11664          --  The actual check for optimize is done in Gigi. Note that this
11665          --  pragma does not actually change the optimization setting, it
11666          --  simply checks that it is consistent with the pragma.
11667
11668          when Pragma_Optimize =>
11669             Check_No_Identifiers;
11670             Check_Arg_Count (1);
11671             Check_Arg_Is_One_Of (Arg1, Name_Time, Name_Space, Name_Off);
11672
11673          ------------------------
11674          -- Optimize_Alignment --
11675          ------------------------
11676
11677          --  pragma Optimize_Alignment (Time | Space | Off);
11678
11679          when Pragma_Optimize_Alignment => Optimize_Alignment : begin
11680             GNAT_Pragma;
11681             Check_No_Identifiers;
11682             Check_Arg_Count (1);
11683             Check_Valid_Configuration_Pragma;
11684
11685             declare
11686                Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
11687             begin
11688                case Nam is
11689                   when Name_Time =>
11690                      Opt.Optimize_Alignment := 'T';
11691                   when Name_Space =>
11692                      Opt.Optimize_Alignment := 'S';
11693                   when Name_Off =>
11694                      Opt.Optimize_Alignment := 'O';
11695                   when others =>
11696                      Error_Pragma_Arg ("invalid argument for pragma%", Arg1);
11697                end case;
11698             end;
11699
11700             --  Set indication that mode is set locally. If we are in fact in a
11701             --  configuration pragma file, this setting is harmless since the
11702             --  switch will get reset anyway at the start of each unit.
11703
11704             Optimize_Alignment_Local := True;
11705          end Optimize_Alignment;
11706
11707          -------------
11708          -- Ordered --
11709          -------------
11710
11711          --  pragma Ordered (first_enumeration_subtype_LOCAL_NAME);
11712
11713          when Pragma_Ordered => Ordered : declare
11714             Assoc   : constant Node_Id := Arg1;
11715             Type_Id : Node_Id;
11716             Typ     : Entity_Id;
11717
11718          begin
11719             GNAT_Pragma;
11720             Check_No_Identifiers;
11721             Check_Arg_Count (1);
11722             Check_Arg_Is_Local_Name (Arg1);
11723
11724             Type_Id := Get_Pragma_Arg (Assoc);
11725             Find_Type (Type_Id);
11726             Typ := Entity (Type_Id);
11727
11728             if Typ = Any_Type then
11729                return;
11730             else
11731                Typ := Underlying_Type (Typ);
11732             end if;
11733
11734             if not Is_Enumeration_Type (Typ) then
11735                Error_Pragma ("pragma% must specify enumeration type");
11736             end if;
11737
11738             Check_First_Subtype (Arg1);
11739             Set_Has_Pragma_Ordered (Base_Type (Typ));
11740          end Ordered;
11741
11742          ----------
11743          -- Pack --
11744          ----------
11745
11746          --  pragma Pack (first_subtype_LOCAL_NAME);
11747
11748          when Pragma_Pack => Pack : declare
11749             Assoc   : constant Node_Id := Arg1;
11750             Type_Id : Node_Id;
11751             Typ     : Entity_Id;
11752             Ctyp    : Entity_Id;
11753             Ignore  : Boolean := False;
11754
11755          begin
11756             Check_No_Identifiers;
11757             Check_Arg_Count (1);
11758             Check_Arg_Is_Local_Name (Arg1);
11759
11760             Type_Id := Get_Pragma_Arg (Assoc);
11761             Find_Type (Type_Id);
11762             Typ := Entity (Type_Id);
11763
11764             if Typ = Any_Type
11765               or else Rep_Item_Too_Early (Typ, N)
11766             then
11767                return;
11768             else
11769                Typ := Underlying_Type (Typ);
11770             end if;
11771
11772             if not Is_Array_Type (Typ) and then not Is_Record_Type (Typ) then
11773                Error_Pragma ("pragma% must specify array or record type");
11774             end if;
11775
11776             Check_First_Subtype (Arg1);
11777             Check_Duplicate_Pragma (Typ);
11778
11779             --  Array type
11780
11781             if Is_Array_Type (Typ) then
11782                Ctyp := Component_Type (Typ);
11783
11784                --  Ignore pack that does nothing
11785
11786                if Known_Static_Esize (Ctyp)
11787                  and then Known_Static_RM_Size (Ctyp)
11788                  and then Esize (Ctyp) = RM_Size (Ctyp)
11789                  and then Addressable (Esize (Ctyp))
11790                then
11791                   Ignore := True;
11792                end if;
11793
11794                --  Process OK pragma Pack. Note that if there is a separate
11795                --  component clause present, the Pack will be cancelled. This
11796                --  processing is in Freeze.
11797
11798                if not Rep_Item_Too_Late (Typ, N) then
11799
11800                   --  In the context of static code analysis, we do not need
11801                   --  complex front-end expansions related to pragma Pack,
11802                   --  so disable handling of pragma Pack in these cases.
11803
11804                   if CodePeer_Mode or Alfa_Mode then
11805                      null;
11806
11807                   --  Don't attempt any packing for VM targets. We possibly
11808                   --  could deal with some cases of array bit-packing, but we
11809                   --  don't bother, since this is not a typical kind of
11810                   --  representation in the VM context anyway (and would not
11811                   --  for example work nicely with the debugger).
11812
11813                   elsif VM_Target /= No_VM then
11814                      if not GNAT_Mode then
11815                         Error_Pragma
11816                           ("?pragma% ignored in this configuration");
11817                      end if;
11818
11819                   --  Normal case where we do the pack action
11820
11821                   else
11822                      if not Ignore then
11823                         Set_Is_Packed            (Base_Type (Typ));
11824                         Set_Has_Non_Standard_Rep (Base_Type (Typ));
11825                      end if;
11826
11827                      Set_Has_Pragma_Pack (Base_Type (Typ));
11828                   end if;
11829                end if;
11830
11831             --  For record types, the pack is always effective
11832
11833             else pragma Assert (Is_Record_Type (Typ));
11834                if not Rep_Item_Too_Late (Typ, N) then
11835
11836                   --  Ignore pack request with warning in VM mode (skip warning
11837                   --  if we are compiling GNAT run time library).
11838
11839                   if VM_Target /= No_VM then
11840                      if not GNAT_Mode then
11841                         Error_Pragma
11842                           ("?pragma% ignored in this configuration");
11843                      end if;
11844
11845                   --  Normal case of pack request active
11846
11847                   else
11848                      Set_Is_Packed            (Base_Type (Typ));
11849                      Set_Has_Pragma_Pack      (Base_Type (Typ));
11850                      Set_Has_Non_Standard_Rep (Base_Type (Typ));
11851                   end if;
11852                end if;
11853             end if;
11854          end Pack;
11855
11856          ----------
11857          -- Page --
11858          ----------
11859
11860          --  pragma Page;
11861
11862          --  There is nothing to do here, since we did all the processing for
11863          --  this pragma in Par.Prag (so that it works properly even in syntax
11864          --  only mode).
11865
11866          when Pragma_Page =>
11867             null;
11868
11869          -------------
11870          -- Passive --
11871          -------------
11872
11873          --  pragma Passive [(PASSIVE_FORM)];
11874
11875          --  PASSIVE_FORM ::= Semaphore | No
11876
11877          when Pragma_Passive =>
11878             GNAT_Pragma;
11879
11880             if Nkind (Parent (N)) /= N_Task_Definition then
11881                Error_Pragma ("pragma% must be within task definition");
11882             end if;
11883
11884             if Arg_Count /= 0 then
11885                Check_Arg_Count (1);
11886                Check_Arg_Is_One_Of (Arg1, Name_Semaphore, Name_No);
11887             end if;
11888
11889          ----------------------------------
11890          -- Preelaborable_Initialization --
11891          ----------------------------------
11892
11893          --  pragma Preelaborable_Initialization (DIRECT_NAME);
11894
11895          when Pragma_Preelaborable_Initialization => Preelab_Init : declare
11896             Ent : Entity_Id;
11897
11898          begin
11899             Ada_2005_Pragma;
11900             Check_Arg_Count (1);
11901             Check_No_Identifiers;
11902             Check_Arg_Is_Identifier (Arg1);
11903             Check_Arg_Is_Local_Name (Arg1);
11904             Check_First_Subtype (Arg1);
11905             Ent := Entity (Get_Pragma_Arg (Arg1));
11906
11907             if not (Is_Private_Type (Ent)
11908                       or else
11909                     Is_Protected_Type (Ent)
11910                       or else
11911                     (Is_Generic_Type (Ent) and then Is_Derived_Type (Ent)))
11912             then
11913                Error_Pragma_Arg
11914                  ("pragma % can only be applied to private, formal derived or "
11915                   & "protected type",
11916                   Arg1);
11917             end if;
11918
11919             --  Give an error if the pragma is applied to a protected type that
11920             --  does not qualify (due to having entries, or due to components
11921             --  that do not qualify).
11922
11923             if Is_Protected_Type (Ent)
11924               and then not Has_Preelaborable_Initialization (Ent)
11925             then
11926                Error_Msg_N
11927                  ("protected type & does not have preelaborable " &
11928                   "initialization", Ent);
11929
11930             --  Otherwise mark the type as definitely having preelaborable
11931             --  initialization.
11932
11933             else
11934                Set_Known_To_Have_Preelab_Init (Ent);
11935             end if;
11936
11937             if Has_Pragma_Preelab_Init (Ent)
11938               and then Warn_On_Redundant_Constructs
11939             then
11940                Error_Pragma ("?duplicate pragma%!");
11941             else
11942                Set_Has_Pragma_Preelab_Init (Ent);
11943             end if;
11944          end Preelab_Init;
11945
11946          --------------------
11947          -- Persistent_BSS --
11948          --------------------
11949
11950          --  pragma Persistent_BSS [(object_NAME)];
11951
11952          when Pragma_Persistent_BSS => Persistent_BSS :  declare
11953             Decl : Node_Id;
11954             Ent  : Entity_Id;
11955             Prag : Node_Id;
11956
11957          begin
11958             GNAT_Pragma;
11959             Check_At_Most_N_Arguments (1);
11960
11961             --  Case of application to specific object (one argument)
11962
11963             if Arg_Count = 1 then
11964                Check_Arg_Is_Library_Level_Local_Name (Arg1);
11965
11966                if not Is_Entity_Name (Get_Pragma_Arg (Arg1))
11967                  or else not
11968                   Ekind_In (Entity (Get_Pragma_Arg (Arg1)), E_Variable,
11969                                                             E_Constant)
11970                then
11971                   Error_Pragma_Arg ("pragma% only applies to objects", Arg1);
11972                end if;
11973
11974                Ent := Entity (Get_Pragma_Arg (Arg1));
11975                Decl := Parent (Ent);
11976
11977                if Rep_Item_Too_Late (Ent, N) then
11978                   return;
11979                end if;
11980
11981                if Present (Expression (Decl)) then
11982                   Error_Pragma_Arg
11983                     ("object for pragma% cannot have initialization", Arg1);
11984                end if;
11985
11986                if not Is_Potentially_Persistent_Type (Etype (Ent)) then
11987                   Error_Pragma_Arg
11988                     ("object type for pragma% is not potentially persistent",
11989                      Arg1);
11990                end if;
11991
11992                Check_Duplicate_Pragma (Ent);
11993
11994                Prag :=
11995                  Make_Linker_Section_Pragma
11996                    (Ent, Sloc (N), ".persistent.bss");
11997                Insert_After (N, Prag);
11998                Analyze (Prag);
11999
12000             --  Case of use as configuration pragma with no arguments
12001
12002             else
12003                Check_Valid_Configuration_Pragma;
12004                Persistent_BSS_Mode := True;
12005             end if;
12006          end Persistent_BSS;
12007
12008          -------------
12009          -- Polling --
12010          -------------
12011
12012          --  pragma Polling (ON | OFF);
12013
12014          when Pragma_Polling =>
12015             GNAT_Pragma;
12016             Check_Arg_Count (1);
12017             Check_No_Identifiers;
12018             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
12019             Polling_Required := (Chars (Get_Pragma_Arg (Arg1)) = Name_On);
12020
12021          -------------------
12022          -- Postcondition --
12023          -------------------
12024
12025          --  pragma Postcondition ([Check   =>] Boolean_EXPRESSION
12026          --                      [,[Message =>] String_EXPRESSION]);
12027
12028          when Pragma_Postcondition => Postcondition : declare
12029             In_Body : Boolean;
12030             pragma Warnings (Off, In_Body);
12031
12032          begin
12033             GNAT_Pragma;
12034             Check_At_Least_N_Arguments (1);
12035             Check_At_Most_N_Arguments (2);
12036             Check_Optional_Identifier (Arg1, Name_Check);
12037
12038             --  All we need to do here is call the common check procedure,
12039             --  the remainder of the processing is found in Sem_Ch6/Sem_Ch7.
12040
12041             Check_Precondition_Postcondition (In_Body);
12042          end Postcondition;
12043
12044          ------------------
12045          -- Precondition --
12046          ------------------
12047
12048          --  pragma Precondition ([Check   =>] Boolean_EXPRESSION
12049          --                     [,[Message =>] String_EXPRESSION]);
12050
12051          when Pragma_Precondition => Precondition : declare
12052             In_Body : Boolean;
12053
12054          begin
12055             GNAT_Pragma;
12056             Check_At_Least_N_Arguments (1);
12057             Check_At_Most_N_Arguments (2);
12058             Check_Optional_Identifier (Arg1, Name_Check);
12059             Check_Precondition_Postcondition (In_Body);
12060
12061             --  If in spec, nothing more to do. If in body, then we convert the
12062             --  pragma to pragma Check (Precondition, cond [, msg]). Note we do
12063             --  this whether or not precondition checks are enabled. That works
12064             --  fine since pragma Check will do this check, and will also
12065             --  analyze the condition itself in the proper context.
12066
12067             if In_Body then
12068                Rewrite (N,
12069                  Make_Pragma (Loc,
12070                    Chars => Name_Check,
12071                    Pragma_Argument_Associations => New_List (
12072                      Make_Pragma_Argument_Association (Loc,
12073                        Expression => Make_Identifier (Loc, Name_Precondition)),
12074
12075                      Make_Pragma_Argument_Association (Sloc (Arg1),
12076                        Expression => Relocate_Node (Get_Pragma_Arg (Arg1))))));
12077
12078                if Arg_Count = 2 then
12079                   Append_To (Pragma_Argument_Associations (N),
12080                     Make_Pragma_Argument_Association (Sloc (Arg2),
12081                       Expression => Relocate_Node (Get_Pragma_Arg (Arg2))));
12082                end if;
12083
12084                Analyze (N);
12085             end if;
12086          end Precondition;
12087
12088          ---------------
12089          -- Predicate --
12090          ---------------
12091
12092          --  pragma Predicate
12093          --    ([Entity =>] type_LOCAL_NAME,
12094          --     [Check  =>] EXPRESSION);
12095
12096          when Pragma_Predicate => Predicate : declare
12097             Type_Id : Node_Id;
12098             Typ     : Entity_Id;
12099
12100             Discard : Boolean;
12101             pragma Unreferenced (Discard);
12102
12103          begin
12104             GNAT_Pragma;
12105             Check_Arg_Count (2);
12106             Check_Optional_Identifier (Arg1, Name_Entity);
12107             Check_Optional_Identifier (Arg2, Name_Check);
12108
12109             Check_Arg_Is_Local_Name (Arg1);
12110
12111             Type_Id := Get_Pragma_Arg (Arg1);
12112             Find_Type (Type_Id);
12113             Typ := Entity (Type_Id);
12114
12115             if Typ = Any_Type then
12116                return;
12117             end if;
12118
12119             --  The remaining processing is simply to link the pragma on to
12120             --  the rep item chain, for processing when the type is frozen.
12121             --  This is accomplished by a call to Rep_Item_Too_Late. We also
12122             --  mark the type as having predicates.
12123
12124             Set_Has_Predicates (Typ);
12125             Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
12126          end Predicate;
12127
12128          ------------------
12129          -- Preelaborate --
12130          ------------------
12131
12132          --  pragma Preelaborate [(library_unit_NAME)];
12133
12134          --  Set the flag Is_Preelaborated of program unit name entity
12135
12136          when Pragma_Preelaborate => Preelaborate : declare
12137             Pa  : constant Node_Id   := Parent (N);
12138             Pk  : constant Node_Kind := Nkind (Pa);
12139             Ent : Entity_Id;
12140
12141          begin
12142             Check_Ada_83_Warning;
12143             Check_Valid_Library_Unit_Pragma;
12144
12145             if Nkind (N) = N_Null_Statement then
12146                return;
12147             end if;
12148
12149             Ent := Find_Lib_Unit_Name;
12150             Check_Duplicate_Pragma (Ent);
12151
12152             --  This filters out pragmas inside generic parent then
12153             --  show up inside instantiation
12154
12155             if Present (Ent)
12156               and then not (Pk = N_Package_Specification
12157                              and then Present (Generic_Parent (Pa)))
12158             then
12159                if not Debug_Flag_U then
12160                   Set_Is_Preelaborated (Ent);
12161                   Set_Suppress_Elaboration_Warnings (Ent);
12162                end if;
12163             end if;
12164          end Preelaborate;
12165
12166          ---------------------
12167          -- Preelaborate_05 --
12168          ---------------------
12169
12170          --  pragma Preelaborate_05 [(library_unit_NAME)];
12171
12172          --  This pragma is useable only in GNAT_Mode, where it is used like
12173          --  pragma Preelaborate but it is only effective in Ada 2005 mode
12174          --  (otherwise it is ignored). This is used to implement AI-362 which
12175          --  recategorizes some run-time packages in Ada 2005 mode.
12176
12177          when Pragma_Preelaborate_05 => Preelaborate_05 : declare
12178             Ent : Entity_Id;
12179
12180          begin
12181             GNAT_Pragma;
12182             Check_Valid_Library_Unit_Pragma;
12183
12184             if not GNAT_Mode then
12185                Error_Pragma ("pragma% only available in GNAT mode");
12186             end if;
12187
12188             if Nkind (N) = N_Null_Statement then
12189                return;
12190             end if;
12191
12192             --  This is one of the few cases where we need to test the value of
12193             --  Ada_Version_Explicit rather than Ada_Version (which is always
12194             --  set to Ada_2012 in a predefined unit), we need to know the
12195             --  explicit version set to know if this pragma is active.
12196
12197             if Ada_Version_Explicit >= Ada_2005 then
12198                Ent := Find_Lib_Unit_Name;
12199                Set_Is_Preelaborated (Ent);
12200                Set_Suppress_Elaboration_Warnings (Ent);
12201             end if;
12202          end Preelaborate_05;
12203
12204          --------------
12205          -- Priority --
12206          --------------
12207
12208          --  pragma Priority (EXPRESSION);
12209
12210          when Pragma_Priority => Priority : declare
12211             P   : constant Node_Id := Parent (N);
12212             Arg : Node_Id;
12213
12214          begin
12215             Check_No_Identifiers;
12216             Check_Arg_Count (1);
12217
12218             --  Subprogram case
12219
12220             if Nkind (P) = N_Subprogram_Body then
12221                Check_In_Main_Program;
12222
12223                Arg := Get_Pragma_Arg (Arg1);
12224                Analyze_And_Resolve (Arg, Standard_Integer);
12225
12226                --  Must be static
12227
12228                if not Is_Static_Expression (Arg) then
12229                   Flag_Non_Static_Expr
12230                     ("main subprogram priority is not static!", Arg);
12231                   raise Pragma_Exit;
12232
12233                --  If constraint error, then we already signalled an error
12234
12235                elsif Raises_Constraint_Error (Arg) then
12236                   null;
12237
12238                --  Otherwise check in range
12239
12240                else
12241                   declare
12242                      Val : constant Uint := Expr_Value (Arg);
12243
12244                   begin
12245                      if Val < 0
12246                        or else Val > Expr_Value (Expression
12247                                        (Parent (RTE (RE_Max_Priority))))
12248                      then
12249                         Error_Pragma_Arg
12250                           ("main subprogram priority is out of range", Arg1);
12251                      end if;
12252                   end;
12253                end if;
12254
12255                Set_Main_Priority
12256                     (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
12257
12258                --  Load an arbitrary entity from System.Tasking to make sure
12259                --  this package is implicitly with'ed, since we need to have
12260                --  the tasking run-time active for the pragma Priority to have
12261                --  any effect.
12262
12263                declare
12264                   Discard : Entity_Id;
12265                   pragma Warnings (Off, Discard);
12266                begin
12267                   Discard := RTE (RE_Task_List);
12268                end;
12269
12270             --  Task or Protected, must be of type Integer
12271
12272             elsif Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
12273                Arg := Get_Pragma_Arg (Arg1);
12274
12275                --  The expression must be analyzed in the special manner
12276                --  described in "Handling of Default and Per-Object
12277                --  Expressions" in sem.ads.
12278
12279                Preanalyze_Spec_Expression (Arg, Standard_Integer);
12280
12281                if not Is_Static_Expression (Arg) then
12282                   Check_Restriction (Static_Priorities, Arg);
12283                end if;
12284
12285             --  Anything else is incorrect
12286
12287             else
12288                Pragma_Misplaced;
12289             end if;
12290
12291             if Has_Pragma_Priority (P) then
12292                Error_Pragma ("duplicate pragma% not allowed");
12293             else
12294                Set_Has_Pragma_Priority (P, True);
12295
12296                if Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
12297                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
12298                   --  exp_ch9 should use this ???
12299                end if;
12300             end if;
12301          end Priority;
12302
12303          -----------------------------------
12304          -- Priority_Specific_Dispatching --
12305          -----------------------------------
12306
12307          --  pragma Priority_Specific_Dispatching (
12308          --    policy_IDENTIFIER,
12309          --    first_priority_EXPRESSION,
12310          --    last_priority_EXPRESSION);
12311
12312          when Pragma_Priority_Specific_Dispatching =>
12313          Priority_Specific_Dispatching : declare
12314             Prio_Id : constant Entity_Id := RTE (RE_Any_Priority);
12315             --  This is the entity System.Any_Priority;
12316
12317             DP          : Character;
12318             Lower_Bound : Node_Id;
12319             Upper_Bound : Node_Id;
12320             Lower_Val   : Uint;
12321             Upper_Val   : Uint;
12322
12323          begin
12324             Ada_2005_Pragma;
12325             Check_Arg_Count (3);
12326             Check_No_Identifiers;
12327             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
12328             Check_Valid_Configuration_Pragma;
12329             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
12330             DP := Fold_Upper (Name_Buffer (1));
12331
12332             Lower_Bound := Get_Pragma_Arg (Arg2);
12333             Check_Arg_Is_Static_Expression (Lower_Bound, Standard_Integer);
12334             Lower_Val := Expr_Value (Lower_Bound);
12335
12336             Upper_Bound := Get_Pragma_Arg (Arg3);
12337             Check_Arg_Is_Static_Expression (Upper_Bound, Standard_Integer);
12338             Upper_Val := Expr_Value (Upper_Bound);
12339
12340             --  It is not allowed to use Task_Dispatching_Policy and
12341             --  Priority_Specific_Dispatching in the same partition.
12342
12343             if Task_Dispatching_Policy /= ' ' then
12344                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
12345                Error_Pragma
12346                  ("pragma% incompatible with Task_Dispatching_Policy#");
12347
12348             --  Check lower bound in range
12349
12350             elsif Lower_Val < Expr_Value (Type_Low_Bound (Prio_Id))
12351                     or else
12352                   Lower_Val > Expr_Value (Type_High_Bound (Prio_Id))
12353             then
12354                Error_Pragma_Arg
12355                  ("first_priority is out of range", Arg2);
12356
12357             --  Check upper bound in range
12358
12359             elsif Upper_Val < Expr_Value (Type_Low_Bound (Prio_Id))
12360                     or else
12361                   Upper_Val > Expr_Value (Type_High_Bound (Prio_Id))
12362             then
12363                Error_Pragma_Arg
12364                  ("last_priority is out of range", Arg3);
12365
12366             --  Check that the priority range is valid
12367
12368             elsif Lower_Val > Upper_Val then
12369                Error_Pragma
12370                  ("last_priority_expression must be greater than" &
12371                   " or equal to first_priority_expression");
12372
12373             --  Store the new policy, but always preserve System_Location since
12374             --  we like the error message with the run-time name.
12375
12376             else
12377                --  Check overlapping in the priority ranges specified in other
12378                --  Priority_Specific_Dispatching pragmas within the same
12379                --  partition. We can only check those we know about!
12380
12381                for J in
12382                   Specific_Dispatching.First .. Specific_Dispatching.Last
12383                loop
12384                   if Specific_Dispatching.Table (J).First_Priority in
12385                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
12386                   or else Specific_Dispatching.Table (J).Last_Priority in
12387                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
12388                   then
12389                      Error_Msg_Sloc :=
12390                        Specific_Dispatching.Table (J).Pragma_Loc;
12391                         Error_Pragma
12392                           ("priority range overlaps with "
12393                            & "Priority_Specific_Dispatching#");
12394                   end if;
12395                end loop;
12396
12397                --  The use of Priority_Specific_Dispatching is incompatible
12398                --  with Task_Dispatching_Policy.
12399
12400                if Task_Dispatching_Policy /= ' ' then
12401                   Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
12402                      Error_Pragma
12403                        ("Priority_Specific_Dispatching incompatible "
12404                         & "with Task_Dispatching_Policy#");
12405                end if;
12406
12407                --  The use of Priority_Specific_Dispatching forces ceiling
12408                --  locking policy.
12409
12410                if Locking_Policy /= ' ' and then Locking_Policy /= 'C' then
12411                   Error_Msg_Sloc := Locking_Policy_Sloc;
12412                      Error_Pragma
12413                        ("Priority_Specific_Dispatching incompatible "
12414                         & "with Locking_Policy#");
12415
12416                --  Set the Ceiling_Locking policy, but preserve System_Location
12417                --  since we like the error message with the run time name.
12418
12419                else
12420                   Locking_Policy := 'C';
12421
12422                   if Locking_Policy_Sloc /= System_Location then
12423                      Locking_Policy_Sloc := Loc;
12424                   end if;
12425                end if;
12426
12427                --  Add entry in the table
12428
12429                Specific_Dispatching.Append
12430                     ((Dispatching_Policy => DP,
12431                       First_Priority     => UI_To_Int (Lower_Val),
12432                       Last_Priority      => UI_To_Int (Upper_Val),
12433                       Pragma_Loc         => Loc));
12434             end if;
12435          end Priority_Specific_Dispatching;
12436
12437          -------------
12438          -- Profile --
12439          -------------
12440
12441          --  pragma Profile (profile_IDENTIFIER);
12442
12443          --  profile_IDENTIFIER => Restricted | Ravenscar
12444
12445          when Pragma_Profile =>
12446             Ada_2005_Pragma;
12447             Check_Arg_Count (1);
12448             Check_Valid_Configuration_Pragma;
12449             Check_No_Identifiers;
12450
12451             declare
12452                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
12453
12454             begin
12455                if Chars (Argx) = Name_Ravenscar then
12456                   Set_Ravenscar_Profile (N);
12457
12458                elsif Chars (Argx) = Name_Restricted then
12459                   Set_Profile_Restrictions
12460                     (Restricted,
12461                      N, Warn => Treat_Restrictions_As_Warnings);
12462
12463                elsif Chars (Argx) = Name_No_Implementation_Extensions then
12464                   Set_Profile_Restrictions
12465                     (No_Implementation_Extensions,
12466                      N, Warn => Treat_Restrictions_As_Warnings);
12467
12468                else
12469                   Error_Pragma_Arg ("& is not a valid profile", Argx);
12470                end if;
12471             end;
12472
12473          ----------------------
12474          -- Profile_Warnings --
12475          ----------------------
12476
12477          --  pragma Profile_Warnings (profile_IDENTIFIER);
12478
12479          --  profile_IDENTIFIER => Restricted | Ravenscar
12480
12481          when Pragma_Profile_Warnings =>
12482             GNAT_Pragma;
12483             Check_Arg_Count (1);
12484             Check_Valid_Configuration_Pragma;
12485             Check_No_Identifiers;
12486
12487             declare
12488                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
12489
12490             begin
12491                if Chars (Argx) = Name_Ravenscar then
12492                   Set_Profile_Restrictions (Ravenscar, N, Warn => True);
12493
12494                elsif Chars (Argx) = Name_Restricted then
12495                   Set_Profile_Restrictions (Restricted, N, Warn => True);
12496
12497                elsif Chars (Argx) = Name_No_Implementation_Extensions then
12498                   Set_Profile_Restrictions
12499                     (No_Implementation_Extensions, N, Warn => True);
12500
12501                else
12502                   Error_Pragma_Arg ("& is not a valid profile", Argx);
12503                end if;
12504             end;
12505
12506          --------------------------
12507          -- Propagate_Exceptions --
12508          --------------------------
12509
12510          --  pragma Propagate_Exceptions;
12511
12512          --  Note: this pragma is obsolete and has no effect
12513
12514          when Pragma_Propagate_Exceptions =>
12515             GNAT_Pragma;
12516             Check_Arg_Count (0);
12517
12518             if In_Extended_Main_Source_Unit (N) then
12519                Propagate_Exceptions := True;
12520             end if;
12521
12522          ------------------
12523          -- Psect_Object --
12524          ------------------
12525
12526          --  pragma Psect_Object (
12527          --        [Internal =>] LOCAL_NAME,
12528          --     [, [External =>] EXTERNAL_SYMBOL]
12529          --     [, [Size     =>] EXTERNAL_SYMBOL]);
12530
12531          when Pragma_Psect_Object | Pragma_Common_Object =>
12532          Psect_Object : declare
12533             Args  : Args_List (1 .. 3);
12534             Names : constant Name_List (1 .. 3) := (
12535                       Name_Internal,
12536                       Name_External,
12537                       Name_Size);
12538
12539             Internal : Node_Id renames Args (1);
12540             External : Node_Id renames Args (2);
12541             Size     : Node_Id renames Args (3);
12542
12543             Def_Id : Entity_Id;
12544
12545             procedure Check_Too_Long (Arg : Node_Id);
12546             --  Posts message if the argument is an identifier with more
12547             --  than 31 characters, or a string literal with more than
12548             --  31 characters, and we are operating under VMS
12549
12550             --------------------
12551             -- Check_Too_Long --
12552             --------------------
12553
12554             procedure Check_Too_Long (Arg : Node_Id) is
12555                X : constant Node_Id := Original_Node (Arg);
12556
12557             begin
12558                if not Nkind_In (X, N_String_Literal, N_Identifier) then
12559                   Error_Pragma_Arg
12560                     ("inappropriate argument for pragma %", Arg);
12561                end if;
12562
12563                if OpenVMS_On_Target then
12564                   if (Nkind (X) = N_String_Literal
12565                        and then String_Length (Strval (X)) > 31)
12566                     or else
12567                      (Nkind (X) = N_Identifier
12568                        and then Length_Of_Name (Chars (X)) > 31)
12569                   then
12570                      Error_Pragma_Arg
12571                        ("argument for pragma % is longer than 31 characters",
12572                         Arg);
12573                   end if;
12574                end if;
12575             end Check_Too_Long;
12576
12577          --  Start of processing for Common_Object/Psect_Object
12578
12579          begin
12580             GNAT_Pragma;
12581             Gather_Associations (Names, Args);
12582             Process_Extended_Import_Export_Internal_Arg (Internal);
12583
12584             Def_Id := Entity (Internal);
12585
12586             if not Ekind_In (Def_Id, E_Constant, E_Variable) then
12587                Error_Pragma_Arg
12588                  ("pragma% must designate an object", Internal);
12589             end if;
12590
12591             Check_Too_Long (Internal);
12592
12593             if Is_Imported (Def_Id) or else Is_Exported (Def_Id) then
12594                Error_Pragma_Arg
12595                  ("cannot use pragma% for imported/exported object",
12596                   Internal);
12597             end if;
12598
12599             if Is_Concurrent_Type (Etype (Internal)) then
12600                Error_Pragma_Arg
12601                  ("cannot specify pragma % for task/protected object",
12602                   Internal);
12603             end if;
12604
12605             if Has_Rep_Pragma (Def_Id, Name_Common_Object)
12606                  or else
12607                Has_Rep_Pragma (Def_Id, Name_Psect_Object)
12608             then
12609                Error_Msg_N ("?duplicate Common/Psect_Object pragma", N);
12610             end if;
12611
12612             if Ekind (Def_Id) = E_Constant then
12613                Error_Pragma_Arg
12614                  ("cannot specify pragma % for a constant", Internal);
12615             end if;
12616
12617             if Is_Record_Type (Etype (Internal)) then
12618                declare
12619                   Ent  : Entity_Id;
12620                   Decl : Entity_Id;
12621
12622                begin
12623                   Ent := First_Entity (Etype (Internal));
12624                   while Present (Ent) loop
12625                      Decl := Declaration_Node (Ent);
12626
12627                      if Ekind (Ent) = E_Component
12628                        and then Nkind (Decl) = N_Component_Declaration
12629                        and then Present (Expression (Decl))
12630                        and then Warn_On_Export_Import
12631                      then
12632                         Error_Msg_N
12633                           ("?object for pragma % has defaults", Internal);
12634                         exit;
12635
12636                      else
12637                         Next_Entity (Ent);
12638                      end if;
12639                   end loop;
12640                end;
12641             end if;
12642
12643             if Present (Size) then
12644                Check_Too_Long (Size);
12645             end if;
12646
12647             if Present (External) then
12648                Check_Arg_Is_External_Name (External);
12649                Check_Too_Long (External);
12650             end if;
12651
12652             --  If all error tests pass, link pragma on to the rep item chain
12653
12654             Record_Rep_Item (Def_Id, N);
12655          end Psect_Object;
12656
12657          ----------
12658          -- Pure --
12659          ----------
12660
12661          --  pragma Pure [(library_unit_NAME)];
12662
12663          when Pragma_Pure => Pure : declare
12664             Ent : Entity_Id;
12665
12666          begin
12667             Check_Ada_83_Warning;
12668             Check_Valid_Library_Unit_Pragma;
12669
12670             if Nkind (N) = N_Null_Statement then
12671                return;
12672             end if;
12673
12674             Ent := Find_Lib_Unit_Name;
12675             Set_Is_Pure (Ent);
12676             Set_Has_Pragma_Pure (Ent);
12677             Set_Suppress_Elaboration_Warnings (Ent);
12678          end Pure;
12679
12680          -------------
12681          -- Pure_05 --
12682          -------------
12683
12684          --  pragma Pure_05 [(library_unit_NAME)];
12685
12686          --  This pragma is useable only in GNAT_Mode, where it is used like
12687          --  pragma Pure but it is only effective in Ada 2005 mode (otherwise
12688          --  it is ignored). It may be used after a pragma Preelaborate, in
12689          --  which case it overrides the effect of the pragma Preelaborate.
12690          --  This is used to implement AI-362 which recategorizes some run-time
12691          --  packages in Ada 2005 mode.
12692
12693          when Pragma_Pure_05 => Pure_05 : declare
12694             Ent : Entity_Id;
12695
12696          begin
12697             GNAT_Pragma;
12698             Check_Valid_Library_Unit_Pragma;
12699
12700             if not GNAT_Mode then
12701                Error_Pragma ("pragma% only available in GNAT mode");
12702             end if;
12703
12704             if Nkind (N) = N_Null_Statement then
12705                return;
12706             end if;
12707
12708             --  This is one of the few cases where we need to test the value of
12709             --  Ada_Version_Explicit rather than Ada_Version (which is always
12710             --  set to Ada_2012 in a predefined unit), we need to know the
12711             --  explicit version set to know if this pragma is active.
12712
12713             if Ada_Version_Explicit >= Ada_2005 then
12714                Ent := Find_Lib_Unit_Name;
12715                Set_Is_Preelaborated (Ent, False);
12716                Set_Is_Pure (Ent);
12717                Set_Suppress_Elaboration_Warnings (Ent);
12718             end if;
12719          end Pure_05;
12720
12721          -------------
12722          -- Pure_12 --
12723          -------------
12724
12725          --  pragma Pure_12 [(library_unit_NAME)];
12726
12727          --  This pragma is useable only in GNAT_Mode, where it is used like
12728          --  pragma Pure but it is only effective in Ada 2012 mode (otherwise
12729          --  it is ignored). It may be used after a pragma Preelaborate, in
12730          --  which case it overrides the effect of the pragma Preelaborate.
12731          --  This is used to implement AI05-0212 which recategorizes some
12732          --  run-time packages in Ada 2012 mode.
12733
12734          when Pragma_Pure_12 => Pure_12 : declare
12735             Ent : Entity_Id;
12736
12737          begin
12738             GNAT_Pragma;
12739             Check_Valid_Library_Unit_Pragma;
12740
12741             if not GNAT_Mode then
12742                Error_Pragma ("pragma% only available in GNAT mode");
12743             end if;
12744
12745             if Nkind (N) = N_Null_Statement then
12746                return;
12747             end if;
12748
12749             --  This is one of the few cases where we need to test the value of
12750             --  Ada_Version_Explicit rather than Ada_Version (which is always
12751             --  set to Ada_2012 in a predefined unit), we need to know the
12752             --  explicit version set to know if this pragma is active.
12753
12754             if Ada_Version_Explicit >= Ada_2012 then
12755                Ent := Find_Lib_Unit_Name;
12756                Set_Is_Preelaborated (Ent, False);
12757                Set_Is_Pure (Ent);
12758                Set_Suppress_Elaboration_Warnings (Ent);
12759             end if;
12760          end Pure_12;
12761
12762          -------------------
12763          -- Pure_Function --
12764          -------------------
12765
12766          --  pragma Pure_Function ([Entity =>] function_LOCAL_NAME);
12767
12768          when Pragma_Pure_Function => Pure_Function : declare
12769             E_Id      : Node_Id;
12770             E         : Entity_Id;
12771             Def_Id    : Entity_Id;
12772             Effective : Boolean := False;
12773
12774          begin
12775             GNAT_Pragma;
12776             Check_Arg_Count (1);
12777             Check_Optional_Identifier (Arg1, Name_Entity);
12778             Check_Arg_Is_Local_Name (Arg1);
12779             E_Id := Get_Pragma_Arg (Arg1);
12780
12781             if Error_Posted (E_Id) then
12782                return;
12783             end if;
12784
12785             --  Loop through homonyms (overloadings) of referenced entity
12786
12787             E := Entity (E_Id);
12788
12789             if Present (E) then
12790                loop
12791                   Def_Id := Get_Base_Subprogram (E);
12792
12793                   if not Ekind_In (Def_Id, E_Function,
12794                                            E_Generic_Function,
12795                                            E_Operator)
12796                   then
12797                      Error_Pragma_Arg
12798                        ("pragma% requires a function name", Arg1);
12799                   end if;
12800
12801                   Set_Is_Pure (Def_Id);
12802
12803                   if not Has_Pragma_Pure_Function (Def_Id) then
12804                      Set_Has_Pragma_Pure_Function (Def_Id);
12805                      Effective := True;
12806                   end if;
12807
12808                   exit when From_Aspect_Specification (N);
12809                   E := Homonym (E);
12810                   exit when No (E) or else Scope (E) /= Current_Scope;
12811                end loop;
12812
12813                if not Effective
12814                  and then Warn_On_Redundant_Constructs
12815                then
12816                   Error_Msg_NE
12817                     ("pragma Pure_Function on& is redundant?",
12818                      N, Entity (E_Id));
12819                end if;
12820             end if;
12821          end Pure_Function;
12822
12823          --------------------
12824          -- Queuing_Policy --
12825          --------------------
12826
12827          --  pragma Queuing_Policy (policy_IDENTIFIER);
12828
12829          when Pragma_Queuing_Policy => declare
12830             QP : Character;
12831
12832          begin
12833             Check_Ada_83_Warning;
12834             Check_Arg_Count (1);
12835             Check_No_Identifiers;
12836             Check_Arg_Is_Queuing_Policy (Arg1);
12837             Check_Valid_Configuration_Pragma;
12838             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
12839             QP := Fold_Upper (Name_Buffer (1));
12840
12841             if Queuing_Policy /= ' '
12842               and then Queuing_Policy /= QP
12843             then
12844                Error_Msg_Sloc := Queuing_Policy_Sloc;
12845                Error_Pragma ("queuing policy incompatible with policy#");
12846
12847             --  Set new policy, but always preserve System_Location since we
12848             --  like the error message with the run time name.
12849
12850             else
12851                Queuing_Policy := QP;
12852
12853                if Queuing_Policy_Sloc /= System_Location then
12854                   Queuing_Policy_Sloc := Loc;
12855                end if;
12856             end if;
12857          end;
12858
12859          -----------------------
12860          -- Relative_Deadline --
12861          -----------------------
12862
12863          --  pragma Relative_Deadline (time_span_EXPRESSION);
12864
12865          when Pragma_Relative_Deadline => Relative_Deadline : declare
12866             P   : constant Node_Id := Parent (N);
12867             Arg : Node_Id;
12868
12869          begin
12870             Ada_2005_Pragma;
12871             Check_No_Identifiers;
12872             Check_Arg_Count (1);
12873
12874             Arg := Get_Pragma_Arg (Arg1);
12875
12876             --  The expression must be analyzed in the special manner described
12877             --  in "Handling of Default and Per-Object Expressions" in sem.ads.
12878
12879             Preanalyze_Spec_Expression (Arg, RTE (RE_Time_Span));
12880
12881             --  Subprogram case
12882
12883             if Nkind (P) = N_Subprogram_Body then
12884                Check_In_Main_Program;
12885
12886             --  Tasks
12887
12888             elsif Nkind (P) = N_Task_Definition then
12889                null;
12890
12891             --  Anything else is incorrect
12892
12893             else
12894                Pragma_Misplaced;
12895             end if;
12896
12897             if Has_Relative_Deadline_Pragma (P) then
12898                Error_Pragma ("duplicate pragma% not allowed");
12899             else
12900                Set_Has_Relative_Deadline_Pragma (P, True);
12901
12902                if Nkind (P) = N_Task_Definition then
12903                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
12904                end if;
12905             end if;
12906          end Relative_Deadline;
12907
12908          ------------------------
12909          -- Remote_Access_Type --
12910          ------------------------
12911
12912          --  pragma Remote_Access_Type ([Entity =>] formal_type_LOCAL_NAME);
12913
12914          when Pragma_Remote_Access_Type => Remote_Access_Type : declare
12915             E : Entity_Id;
12916
12917          begin
12918             GNAT_Pragma;
12919             Check_Arg_Count (1);
12920             Check_Optional_Identifier (Arg1, Name_Entity);
12921             Check_Arg_Is_Local_Name (Arg1);
12922
12923             E := Entity (Get_Pragma_Arg (Arg1));
12924
12925             if Nkind (Parent (E)) = N_Formal_Type_Declaration
12926               and then Ekind (E) = E_General_Access_Type
12927               and then Is_Class_Wide_Type (Directly_Designated_Type (E))
12928               and then Scope (Root_Type (Directly_Designated_Type (E)))
12929                          = Scope (E)
12930               and then Is_Valid_Remote_Object_Type
12931                          (Root_Type (Directly_Designated_Type (E)))
12932             then
12933                Set_Is_Remote_Types (E);
12934
12935             else
12936                Error_Pragma_Arg
12937                  ("pragma% applies only to formal access to classwide types",
12938                   Arg1);
12939             end if;
12940          end Remote_Access_Type;
12941
12942          ---------------------------
12943          -- Remote_Call_Interface --
12944          ---------------------------
12945
12946          --  pragma Remote_Call_Interface [(library_unit_NAME)];
12947
12948          when Pragma_Remote_Call_Interface => Remote_Call_Interface : declare
12949             Cunit_Node : Node_Id;
12950             Cunit_Ent  : Entity_Id;
12951             K          : Node_Kind;
12952
12953          begin
12954             Check_Ada_83_Warning;
12955             Check_Valid_Library_Unit_Pragma;
12956
12957             if Nkind (N) = N_Null_Statement then
12958                return;
12959             end if;
12960
12961             Cunit_Node := Cunit (Current_Sem_Unit);
12962             K          := Nkind (Unit (Cunit_Node));
12963             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12964
12965             if K = N_Package_Declaration
12966               or else K = N_Generic_Package_Declaration
12967               or else K = N_Subprogram_Declaration
12968               or else K = N_Generic_Subprogram_Declaration
12969               or else (K = N_Subprogram_Body
12970                          and then Acts_As_Spec (Unit (Cunit_Node)))
12971             then
12972                null;
12973             else
12974                Error_Pragma (
12975                  "pragma% must apply to package or subprogram declaration");
12976             end if;
12977
12978             Set_Is_Remote_Call_Interface (Cunit_Ent);
12979          end Remote_Call_Interface;
12980
12981          ------------------
12982          -- Remote_Types --
12983          ------------------
12984
12985          --  pragma Remote_Types [(library_unit_NAME)];
12986
12987          when Pragma_Remote_Types => Remote_Types : declare
12988             Cunit_Node : Node_Id;
12989             Cunit_Ent  : Entity_Id;
12990
12991          begin
12992             Check_Ada_83_Warning;
12993             Check_Valid_Library_Unit_Pragma;
12994
12995             if Nkind (N) = N_Null_Statement then
12996                return;
12997             end if;
12998
12999             Cunit_Node := Cunit (Current_Sem_Unit);
13000             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
13001
13002             if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
13003                                                 N_Generic_Package_Declaration)
13004             then
13005                Error_Pragma
13006                  ("pragma% can only apply to a package declaration");
13007             end if;
13008
13009             Set_Is_Remote_Types (Cunit_Ent);
13010          end Remote_Types;
13011
13012          ---------------
13013          -- Ravenscar --
13014          ---------------
13015
13016          --  pragma Ravenscar;
13017
13018          when Pragma_Ravenscar =>
13019             GNAT_Pragma;
13020             Check_Arg_Count (0);
13021             Check_Valid_Configuration_Pragma;
13022             Set_Ravenscar_Profile (N);
13023
13024             if Warn_On_Obsolescent_Feature then
13025                Error_Msg_N ("pragma Ravenscar is an obsolescent feature?", N);
13026                Error_Msg_N ("|use pragma Profile (Ravenscar) instead", N);
13027             end if;
13028
13029          -------------------------
13030          -- Restricted_Run_Time --
13031          -------------------------
13032
13033          --  pragma Restricted_Run_Time;
13034
13035          when Pragma_Restricted_Run_Time =>
13036             GNAT_Pragma;
13037             Check_Arg_Count (0);
13038             Check_Valid_Configuration_Pragma;
13039             Set_Profile_Restrictions
13040               (Restricted, N, Warn => Treat_Restrictions_As_Warnings);
13041
13042             if Warn_On_Obsolescent_Feature then
13043                Error_Msg_N
13044                  ("pragma Restricted_Run_Time is an obsolescent feature?", N);
13045                Error_Msg_N ("|use pragma Profile (Restricted) instead", N);
13046             end if;
13047
13048          ------------------
13049          -- Restrictions --
13050          ------------------
13051
13052          --  pragma Restrictions (RESTRICTION {, RESTRICTION});
13053
13054          --  RESTRICTION ::=
13055          --    restriction_IDENTIFIER
13056          --  | restriction_parameter_IDENTIFIER => EXPRESSION
13057
13058          when Pragma_Restrictions =>
13059             Process_Restrictions_Or_Restriction_Warnings
13060               (Warn => Treat_Restrictions_As_Warnings);
13061
13062          --------------------------
13063          -- Restriction_Warnings --
13064          --------------------------
13065
13066          --  pragma Restriction_Warnings (RESTRICTION {, RESTRICTION});
13067
13068          --  RESTRICTION ::=
13069          --    restriction_IDENTIFIER
13070          --  | restriction_parameter_IDENTIFIER => EXPRESSION
13071
13072          when Pragma_Restriction_Warnings =>
13073             GNAT_Pragma;
13074             Process_Restrictions_Or_Restriction_Warnings (Warn => True);
13075
13076          ----------------
13077          -- Reviewable --
13078          ----------------
13079
13080          --  pragma Reviewable;
13081
13082          when Pragma_Reviewable =>
13083             Check_Ada_83_Warning;
13084             Check_Arg_Count (0);
13085
13086             --  Call dummy debugging function rv. This is done to assist front
13087             --  end debugging. By placing a Reviewable pragma in the source
13088             --  program, a breakpoint on rv catches this place in the source,
13089             --  allowing convenient stepping to the point of interest.
13090
13091             rv;
13092
13093          --------------------------
13094          -- Short_Circuit_And_Or --
13095          --------------------------
13096
13097          when Pragma_Short_Circuit_And_Or =>
13098             GNAT_Pragma;
13099             Check_Arg_Count (0);
13100             Check_Valid_Configuration_Pragma;
13101             Short_Circuit_And_Or := True;
13102
13103          -------------------
13104          -- Share_Generic --
13105          -------------------
13106
13107          --  pragma Share_Generic (NAME {, NAME});
13108
13109          when Pragma_Share_Generic =>
13110             GNAT_Pragma;
13111             Process_Generic_List;
13112
13113          ------------
13114          -- Shared --
13115          ------------
13116
13117          --  pragma Shared (LOCAL_NAME);
13118
13119          when Pragma_Shared =>
13120             GNAT_Pragma;
13121             Process_Atomic_Shared_Volatile;
13122
13123          --------------------
13124          -- Shared_Passive --
13125          --------------------
13126
13127          --  pragma Shared_Passive [(library_unit_NAME)];
13128
13129          --  Set the flag Is_Shared_Passive of program unit name entity
13130
13131          when Pragma_Shared_Passive => Shared_Passive : declare
13132             Cunit_Node : Node_Id;
13133             Cunit_Ent  : Entity_Id;
13134
13135          begin
13136             Check_Ada_83_Warning;
13137             Check_Valid_Library_Unit_Pragma;
13138
13139             if Nkind (N) = N_Null_Statement then
13140                return;
13141             end if;
13142
13143             Cunit_Node := Cunit (Current_Sem_Unit);
13144             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
13145
13146             if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
13147                                                 N_Generic_Package_Declaration)
13148             then
13149                Error_Pragma
13150                  ("pragma% can only apply to a package declaration");
13151             end if;
13152
13153             Set_Is_Shared_Passive (Cunit_Ent);
13154          end Shared_Passive;
13155
13156          -----------------------
13157          -- Short_Descriptors --
13158          -----------------------
13159
13160          --  pragma Short_Descriptors;
13161
13162          when Pragma_Short_Descriptors =>
13163             GNAT_Pragma;
13164             Check_Arg_Count (0);
13165             Check_Valid_Configuration_Pragma;
13166             Short_Descriptors := True;
13167
13168          ------------------------------
13169          -- Simple_Storage_Pool_Type --
13170          ------------------------------
13171
13172          --  pragma Simple_Storage_Pool_Type (type_LOCAL_NAME);
13173
13174          when Pragma_Simple_Storage_Pool_Type =>
13175          Simple_Storage_Pool_Type : declare
13176             Type_Id : Node_Id;
13177             Typ     : Entity_Id;
13178
13179          begin
13180             GNAT_Pragma;
13181             Check_Arg_Count (1);
13182             Check_Arg_Is_Library_Level_Local_Name (Arg1);
13183
13184             Type_Id := Get_Pragma_Arg (Arg1);
13185             Find_Type (Type_Id);
13186             Typ := Entity (Type_Id);
13187
13188             if Typ = Any_Type then
13189                return;
13190             end if;
13191
13192             --  We require the pragma to apply to a type declared in a package
13193             --  declaration, but not (immediately) within a package body.
13194
13195             if Ekind (Current_Scope) /= E_Package
13196               or else In_Package_Body (Current_Scope)
13197             then
13198                Error_Pragma
13199                  ("pragma% can only apply to type declared immediately " &
13200                   "within a package declaration");
13201             end if;
13202
13203             --  A simple storage pool type must be an immutably limited record
13204             --  or private type. If the pragma is given for a private type,
13205             --  the full type is similarly restricted (which is checked later
13206             --  in Freeze_Entity).
13207
13208             if Is_Record_Type (Typ)
13209               and then not Is_Immutably_Limited_Type (Typ)
13210             then
13211                Error_Pragma
13212                  ("pragma% can only apply to explicitly limited record type");
13213
13214             elsif Is_Private_Type (Typ) and then not Is_Limited_Type (Typ) then
13215                Error_Pragma
13216                  ("pragma% can only apply to a private type that is limited");
13217
13218             elsif not Is_Record_Type (Typ)
13219               and then not Is_Private_Type (Typ)
13220             then
13221                Error_Pragma
13222                  ("pragma% can only apply to limited record or private type");
13223             end if;
13224
13225             Record_Rep_Item (Typ, N);
13226          end Simple_Storage_Pool_Type;
13227
13228          ----------------------
13229          -- Source_File_Name --
13230          ----------------------
13231
13232          --  There are five forms for this pragma:
13233
13234          --  pragma Source_File_Name (
13235          --    [UNIT_NAME      =>] unit_NAME,
13236          --     BODY_FILE_NAME =>  STRING_LITERAL
13237          --    [, [INDEX =>] INTEGER_LITERAL]);
13238
13239          --  pragma Source_File_Name (
13240          --    [UNIT_NAME      =>] unit_NAME,
13241          --     SPEC_FILE_NAME =>  STRING_LITERAL
13242          --    [, [INDEX =>] INTEGER_LITERAL]);
13243
13244          --  pragma Source_File_Name (
13245          --     BODY_FILE_NAME  => STRING_LITERAL
13246          --  [, DOT_REPLACEMENT => STRING_LITERAL]
13247          --  [, CASING          => CASING_SPEC]);
13248
13249          --  pragma Source_File_Name (
13250          --     SPEC_FILE_NAME  => STRING_LITERAL
13251          --  [, DOT_REPLACEMENT => STRING_LITERAL]
13252          --  [, CASING          => CASING_SPEC]);
13253
13254          --  pragma Source_File_Name (
13255          --     SUBUNIT_FILE_NAME  => STRING_LITERAL
13256          --  [, DOT_REPLACEMENT    => STRING_LITERAL]
13257          --  [, CASING             => CASING_SPEC]);
13258
13259          --  CASING_SPEC ::= Uppercase | Lowercase | Mixedcase
13260
13261          --  Pragma Source_File_Name_Project (SFNP) is equivalent to pragma
13262          --  Source_File_Name (SFN), however their usage is exclusive: SFN can
13263          --  only be used when no project file is used, while SFNP can only be
13264          --  used when a project file is used.
13265
13266          --  No processing here. Processing was completed during parsing, since
13267          --  we need to have file names set as early as possible. Units are
13268          --  loaded well before semantic processing starts.
13269
13270          --  The only processing we defer to this point is the check for
13271          --  correct placement.
13272
13273          when Pragma_Source_File_Name =>
13274             GNAT_Pragma;
13275             Check_Valid_Configuration_Pragma;
13276
13277          ------------------------------
13278          -- Source_File_Name_Project --
13279          ------------------------------
13280
13281          --  See Source_File_Name for syntax
13282
13283          --  No processing here. Processing was completed during parsing, since
13284          --  we need to have file names set as early as possible. Units are
13285          --  loaded well before semantic processing starts.
13286
13287          --  The only processing we defer to this point is the check for
13288          --  correct placement.
13289
13290          when Pragma_Source_File_Name_Project =>
13291             GNAT_Pragma;
13292             Check_Valid_Configuration_Pragma;
13293
13294             --  Check that a pragma Source_File_Name_Project is used only in a
13295             --  configuration pragmas file.
13296
13297             --  Pragmas Source_File_Name_Project should only be generated by
13298             --  the Project Manager in configuration pragmas files.
13299
13300             --  This is really an ugly test. It seems to depend on some
13301             --  accidental and undocumented property. At the very least it
13302             --  needs to be documented, but it would be better to have a
13303             --  clean way of testing if we are in a configuration file???
13304
13305             if Present (Parent (N)) then
13306                Error_Pragma
13307                  ("pragma% can only appear in a configuration pragmas file");
13308             end if;
13309
13310          ----------------------
13311          -- Source_Reference --
13312          ----------------------
13313
13314          --  pragma Source_Reference (INTEGER_LITERAL [, STRING_LITERAL]);
13315
13316          --  Nothing to do, all processing completed in Par.Prag, since we need
13317          --  the information for possible parser messages that are output.
13318
13319          when Pragma_Source_Reference =>
13320             GNAT_Pragma;
13321
13322          --------------------------------
13323          -- Static_Elaboration_Desired --
13324          --------------------------------
13325
13326          --  pragma Static_Elaboration_Desired (DIRECT_NAME);
13327
13328          when Pragma_Static_Elaboration_Desired =>
13329             GNAT_Pragma;
13330             Check_At_Most_N_Arguments (1);
13331
13332             if Is_Compilation_Unit (Current_Scope)
13333               and then Ekind (Current_Scope) = E_Package
13334             then
13335                Set_Static_Elaboration_Desired (Current_Scope, True);
13336             else
13337                Error_Pragma ("pragma% must apply to a library-level package");
13338             end if;
13339
13340          ------------------
13341          -- Storage_Size --
13342          ------------------
13343
13344          --  pragma Storage_Size (EXPRESSION);
13345
13346          when Pragma_Storage_Size => Storage_Size : declare
13347             P   : constant Node_Id := Parent (N);
13348             Arg : Node_Id;
13349
13350          begin
13351             Check_No_Identifiers;
13352             Check_Arg_Count (1);
13353
13354             --  The expression must be analyzed in the special manner described
13355             --  in "Handling of Default Expressions" in sem.ads.
13356
13357             Arg := Get_Pragma_Arg (Arg1);
13358             Preanalyze_Spec_Expression (Arg, Any_Integer);
13359
13360             if not Is_Static_Expression (Arg) then
13361                Check_Restriction (Static_Storage_Size, Arg);
13362             end if;
13363
13364             if Nkind (P) /= N_Task_Definition then
13365                Pragma_Misplaced;
13366                return;
13367
13368             else
13369                if Has_Storage_Size_Pragma (P) then
13370                   Error_Pragma ("duplicate pragma% not allowed");
13371                else
13372                   Set_Has_Storage_Size_Pragma (P, True);
13373                end if;
13374
13375                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
13376                --  ???  exp_ch9 should use this!
13377             end if;
13378          end Storage_Size;
13379
13380          ------------------
13381          -- Storage_Unit --
13382          ------------------
13383
13384          --  pragma Storage_Unit (NUMERIC_LITERAL);
13385
13386          --  Only permitted argument is System'Storage_Unit value
13387
13388          when Pragma_Storage_Unit =>
13389             Check_No_Identifiers;
13390             Check_Arg_Count (1);
13391             Check_Arg_Is_Integer_Literal (Arg1);
13392
13393             if Intval (Get_Pragma_Arg (Arg1)) /=
13394               UI_From_Int (Ttypes.System_Storage_Unit)
13395             then
13396                Error_Msg_Uint_1 := UI_From_Int (Ttypes.System_Storage_Unit);
13397                Error_Pragma_Arg
13398                  ("the only allowed argument for pragma% is ^", Arg1);
13399             end if;
13400
13401          --------------------
13402          -- Stream_Convert --
13403          --------------------
13404
13405          --  pragma Stream_Convert (
13406          --    [Entity =>] type_LOCAL_NAME,
13407          --    [Read   =>] function_NAME,
13408          --    [Write  =>] function NAME);
13409
13410          when Pragma_Stream_Convert => Stream_Convert : declare
13411
13412             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id);
13413             --  Check that the given argument is the name of a local function
13414             --  of one argument that is not overloaded earlier in the current
13415             --  local scope. A check is also made that the argument is a
13416             --  function with one parameter.
13417
13418             --------------------------------------
13419             -- Check_OK_Stream_Convert_Function --
13420             --------------------------------------
13421
13422             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id) is
13423                Ent : Entity_Id;
13424
13425             begin
13426                Check_Arg_Is_Local_Name (Arg);
13427                Ent := Entity (Get_Pragma_Arg (Arg));
13428
13429                if Has_Homonym (Ent) then
13430                   Error_Pragma_Arg
13431                     ("argument for pragma% may not be overloaded", Arg);
13432                end if;
13433
13434                if Ekind (Ent) /= E_Function
13435                  or else No (First_Formal (Ent))
13436                  or else Present (Next_Formal (First_Formal (Ent)))
13437                then
13438                   Error_Pragma_Arg
13439                     ("argument for pragma% must be" &
13440                      " function of one argument", Arg);
13441                end if;
13442             end Check_OK_Stream_Convert_Function;
13443
13444          --  Start of processing for Stream_Convert
13445
13446          begin
13447             GNAT_Pragma;
13448             Check_Arg_Order ((Name_Entity, Name_Read, Name_Write));
13449             Check_Arg_Count (3);
13450             Check_Optional_Identifier (Arg1, Name_Entity);
13451             Check_Optional_Identifier (Arg2, Name_Read);
13452             Check_Optional_Identifier (Arg3, Name_Write);
13453             Check_Arg_Is_Local_Name (Arg1);
13454             Check_OK_Stream_Convert_Function (Arg2);
13455             Check_OK_Stream_Convert_Function (Arg3);
13456
13457             declare
13458                Typ   : constant Entity_Id :=
13459                          Underlying_Type (Entity (Get_Pragma_Arg (Arg1)));
13460                Read  : constant Entity_Id := Entity (Get_Pragma_Arg (Arg2));
13461                Write : constant Entity_Id := Entity (Get_Pragma_Arg (Arg3));
13462
13463             begin
13464                Check_First_Subtype (Arg1);
13465
13466                --  Check for too early or too late. Note that we don't enforce
13467                --  the rule about primitive operations in this case, since, as
13468                --  is the case for explicit stream attributes themselves, these
13469                --  restrictions are not appropriate. Note that the chaining of
13470                --  the pragma by Rep_Item_Too_Late is actually the critical
13471                --  processing done for this pragma.
13472
13473                if Rep_Item_Too_Early (Typ, N)
13474                     or else
13475                   Rep_Item_Too_Late (Typ, N, FOnly => True)
13476                then
13477                   return;
13478                end if;
13479
13480                --  Return if previous error
13481
13482                if Etype (Typ) = Any_Type
13483                     or else
13484                   Etype (Read) = Any_Type
13485                     or else
13486                   Etype (Write) = Any_Type
13487                then
13488                   return;
13489                end if;
13490
13491                --  Error checks
13492
13493                if Underlying_Type (Etype (Read)) /= Typ then
13494                   Error_Pragma_Arg
13495                     ("incorrect return type for function&", Arg2);
13496                end if;
13497
13498                if Underlying_Type (Etype (First_Formal (Write))) /= Typ then
13499                   Error_Pragma_Arg
13500                     ("incorrect parameter type for function&", Arg3);
13501                end if;
13502
13503                if Underlying_Type (Etype (First_Formal (Read))) /=
13504                   Underlying_Type (Etype (Write))
13505                then
13506                   Error_Pragma_Arg
13507                     ("result type of & does not match Read parameter type",
13508                      Arg3);
13509                end if;
13510             end;
13511          end Stream_Convert;
13512
13513          -------------------------
13514          -- Style_Checks (GNAT) --
13515          -------------------------
13516
13517          --  pragma Style_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
13518
13519          --  This is processed by the parser since some of the style checks
13520          --  take place during source scanning and parsing. This means that
13521          --  we don't need to issue error messages here.
13522
13523          when Pragma_Style_Checks => Style_Checks : declare
13524             A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
13525             S  : String_Id;
13526             C  : Char_Code;
13527
13528          begin
13529             GNAT_Pragma;
13530             Check_No_Identifiers;
13531
13532             --  Two argument form
13533
13534             if Arg_Count = 2 then
13535                Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
13536
13537                declare
13538                   E_Id : Node_Id;
13539                   E    : Entity_Id;
13540
13541                begin
13542                   E_Id := Get_Pragma_Arg (Arg2);
13543                   Analyze (E_Id);
13544
13545                   if not Is_Entity_Name (E_Id) then
13546                      Error_Pragma_Arg
13547                        ("second argument of pragma% must be entity name",
13548                         Arg2);
13549                   end if;
13550
13551                   E := Entity (E_Id);
13552
13553                   if E = Any_Id then
13554                      return;
13555                   else
13556                      loop
13557                         Set_Suppress_Style_Checks (E,
13558                           (Chars (Get_Pragma_Arg (Arg1)) = Name_Off));
13559                         exit when No (Homonym (E));
13560                         E := Homonym (E);
13561                      end loop;
13562                   end if;
13563                end;
13564
13565             --  One argument form
13566
13567             else
13568                Check_Arg_Count (1);
13569
13570                if Nkind (A) = N_String_Literal then
13571                   S   := Strval (A);
13572
13573                   declare
13574                      Slen    : constant Natural := Natural (String_Length (S));
13575                      Options : String (1 .. Slen);
13576                      J       : Natural;
13577
13578                   begin
13579                      J := 1;
13580                      loop
13581                         C := Get_String_Char (S, Int (J));
13582                         exit when not In_Character_Range (C);
13583                         Options (J) := Get_Character (C);
13584
13585                         --  If at end of string, set options. As per discussion
13586                         --  above, no need to check for errors, since we issued
13587                         --  them in the parser.
13588
13589                         if J = Slen then
13590                            Set_Style_Check_Options (Options);
13591                            exit;
13592                         end if;
13593
13594                         J := J + 1;
13595                      end loop;
13596                   end;
13597
13598                elsif Nkind (A) = N_Identifier then
13599                   if Chars (A) = Name_All_Checks then
13600                      if GNAT_Mode then
13601                         Set_GNAT_Style_Check_Options;
13602                      else
13603                         Set_Default_Style_Check_Options;
13604                      end if;
13605
13606                   elsif Chars (A) = Name_On then
13607                      Style_Check := True;
13608
13609                   elsif Chars (A) = Name_Off then
13610                      Style_Check := False;
13611                   end if;
13612                end if;
13613             end if;
13614          end Style_Checks;
13615
13616          --------------
13617          -- Subtitle --
13618          --------------
13619
13620          --  pragma Subtitle ([Subtitle =>] STRING_LITERAL);
13621
13622          when Pragma_Subtitle =>
13623             GNAT_Pragma;
13624             Check_Arg_Count (1);
13625             Check_Optional_Identifier (Arg1, Name_Subtitle);
13626             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
13627             Store_Note (N);
13628
13629          --------------
13630          -- Suppress --
13631          --------------
13632
13633          --  pragma Suppress (IDENTIFIER [, [On =>] NAME]);
13634
13635          when Pragma_Suppress =>
13636             Process_Suppress_Unsuppress (True);
13637
13638          ------------------
13639          -- Suppress_All --
13640          ------------------
13641
13642          --  pragma Suppress_All;
13643
13644          --  The only check made here is that the pragma has no arguments.
13645          --  There are no placement rules, and the processing required (setting
13646          --  the Has_Pragma_Suppress_All flag in the compilation unit node was
13647          --  taken care of by the parser). Process_Compilation_Unit_Pragmas
13648          --  then creates and inserts a pragma Suppress (All_Checks).
13649
13650          when Pragma_Suppress_All =>
13651             GNAT_Pragma;
13652             Check_Arg_Count (0);
13653
13654          -------------------------
13655          -- Suppress_Debug_Info --
13656          -------------------------
13657
13658          --  pragma Suppress_Debug_Info ([Entity =>] LOCAL_NAME);
13659
13660          when Pragma_Suppress_Debug_Info =>
13661             GNAT_Pragma;
13662             Check_Arg_Count (1);
13663             Check_Optional_Identifier (Arg1, Name_Entity);
13664             Check_Arg_Is_Local_Name (Arg1);
13665             Set_Debug_Info_Off (Entity (Get_Pragma_Arg (Arg1)));
13666
13667          ----------------------------------
13668          -- Suppress_Exception_Locations --
13669          ----------------------------------
13670
13671          --  pragma Suppress_Exception_Locations;
13672
13673          when Pragma_Suppress_Exception_Locations =>
13674             GNAT_Pragma;
13675             Check_Arg_Count (0);
13676             Check_Valid_Configuration_Pragma;
13677             Exception_Locations_Suppressed := True;
13678
13679          -----------------------------
13680          -- Suppress_Initialization --
13681          -----------------------------
13682
13683          --  pragma Suppress_Initialization ([Entity =>] type_Name);
13684
13685          when Pragma_Suppress_Initialization => Suppress_Init : declare
13686             E_Id : Node_Id;
13687             E    : Entity_Id;
13688
13689          begin
13690             GNAT_Pragma;
13691             Check_Arg_Count (1);
13692             Check_Optional_Identifier (Arg1, Name_Entity);
13693             Check_Arg_Is_Local_Name (Arg1);
13694
13695             E_Id := Get_Pragma_Arg (Arg1);
13696
13697             if Etype (E_Id) = Any_Type then
13698                return;
13699             end if;
13700
13701             E := Entity (E_Id);
13702
13703             if not Is_Type (E) then
13704                Error_Pragma_Arg ("pragma% requires type or subtype", Arg1);
13705             end if;
13706
13707             if Rep_Item_Too_Early (E, N)
13708                  or else
13709                Rep_Item_Too_Late (E, N, FOnly => True)
13710             then
13711                return;
13712             end if;
13713
13714             --  For incomplete/private type, set flag on full view
13715
13716             if Is_Incomplete_Or_Private_Type (E) then
13717                if No (Full_View (Base_Type (E))) then
13718                   Error_Pragma_Arg
13719                     ("argument of pragma% cannot be an incomplete type", Arg1);
13720                else
13721                   Set_Suppress_Initialization (Full_View (Base_Type (E)));
13722                end if;
13723
13724             --  For first subtype, set flag on base type
13725
13726             elsif Is_First_Subtype (E) then
13727                Set_Suppress_Initialization (Base_Type (E));
13728
13729             --  For other than first subtype, set flag on subtype itself
13730
13731             else
13732                Set_Suppress_Initialization (E);
13733             end if;
13734          end Suppress_Init;
13735
13736          -----------------
13737          -- System_Name --
13738          -----------------
13739
13740          --  pragma System_Name (DIRECT_NAME);
13741
13742          --  Syntax check: one argument, which must be the identifier GNAT or
13743          --  the identifier GCC, no other identifiers are acceptable.
13744
13745          when Pragma_System_Name =>
13746             GNAT_Pragma;
13747             Check_No_Identifiers;
13748             Check_Arg_Count (1);
13749             Check_Arg_Is_One_Of (Arg1, Name_Gcc, Name_Gnat);
13750
13751          -----------------------------
13752          -- Task_Dispatching_Policy --
13753          -----------------------------
13754
13755          --  pragma Task_Dispatching_Policy (policy_IDENTIFIER);
13756
13757          when Pragma_Task_Dispatching_Policy => declare
13758             DP : Character;
13759
13760          begin
13761             Check_Ada_83_Warning;
13762             Check_Arg_Count (1);
13763             Check_No_Identifiers;
13764             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
13765             Check_Valid_Configuration_Pragma;
13766             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
13767             DP := Fold_Upper (Name_Buffer (1));
13768
13769             if Task_Dispatching_Policy /= ' '
13770               and then Task_Dispatching_Policy /= DP
13771             then
13772                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
13773                Error_Pragma
13774                  ("task dispatching policy incompatible with policy#");
13775
13776             --  Set new policy, but always preserve System_Location since we
13777             --  like the error message with the run time name.
13778
13779             else
13780                Task_Dispatching_Policy := DP;
13781
13782                if Task_Dispatching_Policy_Sloc /= System_Location then
13783                   Task_Dispatching_Policy_Sloc := Loc;
13784                end if;
13785             end if;
13786          end;
13787
13788          ---------------
13789          -- Task_Info --
13790          ---------------
13791
13792          --  pragma Task_Info (EXPRESSION);
13793
13794          when Pragma_Task_Info => Task_Info : declare
13795             P : constant Node_Id := Parent (N);
13796
13797          begin
13798             GNAT_Pragma;
13799
13800             if Nkind (P) /= N_Task_Definition then
13801                Error_Pragma ("pragma% must appear in task definition");
13802             end if;
13803
13804             Check_No_Identifiers;
13805             Check_Arg_Count (1);
13806
13807             Analyze_And_Resolve
13808               (Get_Pragma_Arg (Arg1), RTE (RE_Task_Info_Type));
13809
13810             if Etype (Get_Pragma_Arg (Arg1)) = Any_Type then
13811                return;
13812             end if;
13813
13814             if Has_Task_Info_Pragma (P) then
13815                Error_Pragma ("duplicate pragma% not allowed");
13816             else
13817                Set_Has_Task_Info_Pragma (P, True);
13818             end if;
13819          end Task_Info;
13820
13821          ---------------
13822          -- Task_Name --
13823          ---------------
13824
13825          --  pragma Task_Name (string_EXPRESSION);
13826
13827          when Pragma_Task_Name => Task_Name : declare
13828             P   : constant Node_Id := Parent (N);
13829             Arg : Node_Id;
13830
13831          begin
13832             Check_No_Identifiers;
13833             Check_Arg_Count (1);
13834
13835             Arg := Get_Pragma_Arg (Arg1);
13836
13837             --  The expression is used in the call to Create_Task, and must be
13838             --  expanded there, not in the context of the current spec. It must
13839             --  however be analyzed to capture global references, in case it
13840             --  appears in a generic context.
13841
13842             Preanalyze_And_Resolve (Arg, Standard_String);
13843
13844             if Nkind (P) /= N_Task_Definition then
13845                Pragma_Misplaced;
13846             end if;
13847
13848             if Has_Task_Name_Pragma (P) then
13849                Error_Pragma ("duplicate pragma% not allowed");
13850             else
13851                Set_Has_Task_Name_Pragma (P, True);
13852                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
13853             end if;
13854          end Task_Name;
13855
13856          ------------------
13857          -- Task_Storage --
13858          ------------------
13859
13860          --  pragma Task_Storage (
13861          --     [Task_Type =>] LOCAL_NAME,
13862          --     [Top_Guard =>] static_integer_EXPRESSION);
13863
13864          when Pragma_Task_Storage => Task_Storage : declare
13865             Args  : Args_List (1 .. 2);
13866             Names : constant Name_List (1 .. 2) := (
13867                       Name_Task_Type,
13868                       Name_Top_Guard);
13869
13870             Task_Type : Node_Id renames Args (1);
13871             Top_Guard : Node_Id renames Args (2);
13872
13873             Ent : Entity_Id;
13874
13875          begin
13876             GNAT_Pragma;
13877             Gather_Associations (Names, Args);
13878
13879             if No (Task_Type) then
13880                Error_Pragma
13881                  ("missing task_type argument for pragma%");
13882             end if;
13883
13884             Check_Arg_Is_Local_Name (Task_Type);
13885
13886             Ent := Entity (Task_Type);
13887
13888             if not Is_Task_Type (Ent) then
13889                Error_Pragma_Arg
13890                  ("argument for pragma% must be task type", Task_Type);
13891             end if;
13892
13893             if No (Top_Guard) then
13894                Error_Pragma_Arg
13895                  ("pragma% takes two arguments", Task_Type);
13896             else
13897                Check_Arg_Is_Static_Expression (Top_Guard, Any_Integer);
13898             end if;
13899
13900             Check_First_Subtype (Task_Type);
13901
13902             if Rep_Item_Too_Late (Ent, N) then
13903                raise Pragma_Exit;
13904             end if;
13905          end Task_Storage;
13906
13907          ---------------
13908          -- Test_Case --
13909          ---------------
13910
13911          --  pragma Test_Case ([Name     =>] Static_String_EXPRESSION
13912          --                   ,[Mode     =>] MODE_TYPE
13913          --                  [, Requires =>  Boolean_EXPRESSION]
13914          --                  [, Ensures  =>  Boolean_EXPRESSION]);
13915
13916          --  MODE_TYPE ::= Nominal | Robustness
13917
13918          when Pragma_Test_Case => Test_Case : declare
13919          begin
13920             GNAT_Pragma;
13921             Check_At_Least_N_Arguments (2);
13922             Check_At_Most_N_Arguments (4);
13923             Check_Arg_Order
13924                  ((Name_Name, Name_Mode, Name_Requires, Name_Ensures));
13925
13926             Check_Optional_Identifier (Arg1, Name_Name);
13927             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
13928
13929             --  In ASIS mode, for a pragma generated from a source aspect, also
13930             --  analyze the original aspect expression.
13931
13932             if ASIS_Mode
13933               and then Present (Corresponding_Aspect (N))
13934             then
13935                Check_Expr_Is_Static_Expression
13936                  (Original_Node (Get_Pragma_Arg (Arg1)), Standard_String);
13937             end if;
13938
13939             Check_Optional_Identifier (Arg2, Name_Mode);
13940             Check_Arg_Is_One_Of (Arg2, Name_Nominal, Name_Robustness);
13941
13942             if Arg_Count = 4 then
13943                Check_Identifier (Arg3, Name_Requires);
13944                Check_Identifier (Arg4, Name_Ensures);
13945
13946             elsif Arg_Count = 3 then
13947                Check_Identifier_Is_One_Of (Arg3, Name_Requires, Name_Ensures);
13948             end if;
13949
13950             Check_Test_Case;
13951          end Test_Case;
13952
13953          --------------------------
13954          -- Thread_Local_Storage --
13955          --------------------------
13956
13957          --  pragma Thread_Local_Storage ([Entity =>] LOCAL_NAME);
13958
13959          when Pragma_Thread_Local_Storage => Thread_Local_Storage : declare
13960             Id : Node_Id;
13961             E  : Entity_Id;
13962
13963          begin
13964             GNAT_Pragma;
13965             Check_Arg_Count (1);
13966             Check_Optional_Identifier (Arg1, Name_Entity);
13967             Check_Arg_Is_Library_Level_Local_Name (Arg1);
13968
13969             Id := Get_Pragma_Arg (Arg1);
13970             Analyze (Id);
13971
13972             if not Is_Entity_Name (Id)
13973               or else Ekind (Entity (Id)) /= E_Variable
13974             then
13975                Error_Pragma_Arg ("local variable name required", Arg1);
13976             end if;
13977
13978             E := Entity (Id);
13979
13980             if Rep_Item_Too_Early (E, N)
13981               or else Rep_Item_Too_Late (E, N)
13982             then
13983                raise Pragma_Exit;
13984             end if;
13985
13986             Set_Has_Pragma_Thread_Local_Storage (E);
13987             Set_Has_Gigi_Rep_Item (E);
13988          end Thread_Local_Storage;
13989
13990          ----------------
13991          -- Time_Slice --
13992          ----------------
13993
13994          --  pragma Time_Slice (static_duration_EXPRESSION);
13995
13996          when Pragma_Time_Slice => Time_Slice : declare
13997             Val : Ureal;
13998             Nod : Node_Id;
13999
14000          begin
14001             GNAT_Pragma;
14002             Check_Arg_Count (1);
14003             Check_No_Identifiers;
14004             Check_In_Main_Program;
14005             Check_Arg_Is_Static_Expression (Arg1, Standard_Duration);
14006
14007             if not Error_Posted (Arg1) then
14008                Nod := Next (N);
14009                while Present (Nod) loop
14010                   if Nkind (Nod) = N_Pragma
14011                     and then Pragma_Name (Nod) = Name_Time_Slice
14012                   then
14013                      Error_Msg_Name_1 := Pname;
14014                      Error_Msg_N ("duplicate pragma% not permitted", Nod);
14015                   end if;
14016
14017                   Next (Nod);
14018                end loop;
14019             end if;
14020
14021             --  Process only if in main unit
14022
14023             if Get_Source_Unit (Loc) = Main_Unit then
14024                Opt.Time_Slice_Set := True;
14025                Val := Expr_Value_R (Get_Pragma_Arg (Arg1));
14026
14027                if Val <= Ureal_0 then
14028                   Opt.Time_Slice_Value := 0;
14029
14030                elsif Val > UR_From_Uint (UI_From_Int (1000)) then
14031                   Opt.Time_Slice_Value := 1_000_000_000;
14032
14033                else
14034                   Opt.Time_Slice_Value :=
14035                     UI_To_Int (UR_To_Uint (Val * UI_From_Int (1_000_000)));
14036                end if;
14037             end if;
14038          end Time_Slice;
14039
14040          -----------
14041          -- Title --
14042          -----------
14043
14044          --  pragma Title (TITLING_OPTION [, TITLING OPTION]);
14045
14046          --   TITLING_OPTION ::=
14047          --     [Title =>] STRING_LITERAL
14048          --   | [Subtitle =>] STRING_LITERAL
14049
14050          when Pragma_Title => Title : declare
14051             Args  : Args_List (1 .. 2);
14052             Names : constant Name_List (1 .. 2) := (
14053                       Name_Title,
14054                       Name_Subtitle);
14055
14056          begin
14057             GNAT_Pragma;
14058             Gather_Associations (Names, Args);
14059             Store_Note (N);
14060
14061             for J in 1 .. 2 loop
14062                if Present (Args (J)) then
14063                   Check_Arg_Is_Static_Expression (Args (J), Standard_String);
14064                end if;
14065             end loop;
14066          end Title;
14067
14068          ---------------------
14069          -- Unchecked_Union --
14070          ---------------------
14071
14072          --  pragma Unchecked_Union (first_subtype_LOCAL_NAME)
14073
14074          when Pragma_Unchecked_Union => Unchecked_Union : declare
14075             Assoc   : constant Node_Id := Arg1;
14076             Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
14077             Typ     : Entity_Id;
14078             Discr   : Entity_Id;
14079             Tdef    : Node_Id;
14080             Clist   : Node_Id;
14081             Vpart   : Node_Id;
14082             Comp    : Node_Id;
14083             Variant : Node_Id;
14084
14085          begin
14086             Ada_2005_Pragma;
14087             Check_No_Identifiers;
14088             Check_Arg_Count (1);
14089             Check_Arg_Is_Local_Name (Arg1);
14090
14091             Find_Type (Type_Id);
14092             Typ := Entity (Type_Id);
14093
14094             if Typ = Any_Type
14095               or else Rep_Item_Too_Early (Typ, N)
14096             then
14097                return;
14098             else
14099                Typ := Underlying_Type (Typ);
14100             end if;
14101
14102             if Rep_Item_Too_Late (Typ, N) then
14103                return;
14104             end if;
14105
14106             Check_First_Subtype (Arg1);
14107
14108             --  Note remaining cases are references to a type in the current
14109             --  declarative part. If we find an error, we post the error on
14110             --  the relevant type declaration at an appropriate point.
14111
14112             if not Is_Record_Type (Typ) then
14113                Error_Msg_N ("Unchecked_Union must be record type", Typ);
14114                return;
14115
14116             elsif Is_Tagged_Type (Typ) then
14117                Error_Msg_N ("Unchecked_Union must not be tagged", Typ);
14118                return;
14119
14120             elsif not Has_Discriminants (Typ) then
14121                Error_Msg_N
14122                 ("Unchecked_Union must have one discriminant", Typ);
14123                return;
14124
14125             --  Note: in previous versions of GNAT we used to check for limited
14126             --  types and give an error, but in fact the standard does allow
14127             --  Unchecked_Union on limited types, so this check was removed.
14128
14129             --  Proceed with basic error checks completed
14130
14131             else
14132                Discr := First_Discriminant (Typ);
14133                while Present (Discr) loop
14134                   if No (Discriminant_Default_Value (Discr)) then
14135                      Error_Msg_N
14136                        ("Unchecked_Union discriminant must have default value",
14137                         Discr);
14138                   end if;
14139
14140                   Next_Discriminant (Discr);
14141                end loop;
14142
14143                Tdef  := Type_Definition (Declaration_Node (Typ));
14144                Clist := Component_List (Tdef);
14145
14146                Comp := First (Component_Items (Clist));
14147                while Present (Comp) loop
14148                   Check_Component (Comp, Typ);
14149                   Next (Comp);
14150                end loop;
14151
14152                if No (Clist) or else No (Variant_Part (Clist)) then
14153                   Error_Msg_N
14154                     ("Unchecked_Union must have variant part",
14155                      Tdef);
14156                   return;
14157                end if;
14158
14159                Vpart := Variant_Part (Clist);
14160
14161                Variant := First (Variants (Vpart));
14162                while Present (Variant) loop
14163                   Check_Variant (Variant, Typ);
14164                   Next (Variant);
14165                end loop;
14166             end if;
14167
14168             Set_Is_Unchecked_Union  (Typ);
14169             Set_Convention (Typ, Convention_C);
14170             Set_Has_Unchecked_Union (Base_Type (Typ));
14171             Set_Is_Unchecked_Union  (Base_Type (Typ));
14172          end Unchecked_Union;
14173
14174          ------------------------
14175          -- Unimplemented_Unit --
14176          ------------------------
14177
14178          --  pragma Unimplemented_Unit;
14179
14180          --  Note: this only gives an error if we are generating code, or if
14181          --  we are in a generic library unit (where the pragma appears in the
14182          --  body, not in the spec).
14183
14184          when Pragma_Unimplemented_Unit => Unimplemented_Unit : declare
14185             Cunitent : constant Entity_Id :=
14186                          Cunit_Entity (Get_Source_Unit (Loc));
14187             Ent_Kind : constant Entity_Kind :=
14188                          Ekind (Cunitent);
14189
14190          begin
14191             GNAT_Pragma;
14192             Check_Arg_Count (0);
14193
14194             if Operating_Mode = Generate_Code
14195               or else Ent_Kind = E_Generic_Function
14196               or else Ent_Kind = E_Generic_Procedure
14197               or else Ent_Kind = E_Generic_Package
14198             then
14199                Get_Name_String (Chars (Cunitent));
14200                Set_Casing (Mixed_Case);
14201                Write_Str (Name_Buffer (1 .. Name_Len));
14202                Write_Str (" is not supported in this configuration");
14203                Write_Eol;
14204                raise Unrecoverable_Error;
14205             end if;
14206          end Unimplemented_Unit;
14207
14208          ------------------------
14209          -- Universal_Aliasing --
14210          ------------------------
14211
14212          --  pragma Universal_Aliasing [([Entity =>] type_LOCAL_NAME)];
14213
14214          when Pragma_Universal_Aliasing => Universal_Alias : declare
14215             E_Id : Entity_Id;
14216
14217          begin
14218             GNAT_Pragma;
14219             Check_Arg_Count (1);
14220             Check_Optional_Identifier (Arg2, Name_Entity);
14221             Check_Arg_Is_Local_Name (Arg1);
14222             E_Id := Entity (Get_Pragma_Arg (Arg1));
14223
14224             if E_Id = Any_Type then
14225                return;
14226             elsif No (E_Id) or else not Is_Type (E_Id) then
14227                Error_Pragma_Arg ("pragma% requires type", Arg1);
14228             end if;
14229
14230             Set_Universal_Aliasing (Implementation_Base_Type (E_Id));
14231          end Universal_Alias;
14232
14233          --------------------
14234          -- Universal_Data --
14235          --------------------
14236
14237          --  pragma Universal_Data [(library_unit_NAME)];
14238
14239          when Pragma_Universal_Data =>
14240             GNAT_Pragma;
14241
14242             --  If this is a configuration pragma, then set the universal
14243             --  addressing option, otherwise confirm that the pragma satisfies
14244             --  the requirements of library unit pragma placement and leave it
14245             --  to the GNAAMP back end to detect the pragma (avoids transitive
14246             --  setting of the option due to withed units).
14247
14248             if Is_Configuration_Pragma then
14249                Universal_Addressing_On_AAMP := True;
14250             else
14251                Check_Valid_Library_Unit_Pragma;
14252             end if;
14253
14254             if not AAMP_On_Target then
14255                Error_Pragma ("?pragma% ignored (applies only to AAMP)");
14256             end if;
14257
14258          ----------------
14259          -- Unmodified --
14260          ----------------
14261
14262          --  pragma Unmodified (local_Name {, local_Name});
14263
14264          when Pragma_Unmodified => Unmodified : declare
14265             Arg_Node : Node_Id;
14266             Arg_Expr : Node_Id;
14267             Arg_Ent  : Entity_Id;
14268
14269          begin
14270             GNAT_Pragma;
14271             Check_At_Least_N_Arguments (1);
14272
14273             --  Loop through arguments
14274
14275             Arg_Node := Arg1;
14276             while Present (Arg_Node) loop
14277                Check_No_Identifier (Arg_Node);
14278
14279                --  Note: the analyze call done by Check_Arg_Is_Local_Name will
14280                --  in fact generate reference, so that the entity will have a
14281                --  reference, which will inhibit any warnings about it not
14282                --  being referenced, and also properly show up in the ali file
14283                --  as a reference. But this reference is recorded before the
14284                --  Has_Pragma_Unreferenced flag is set, so that no warning is
14285                --  generated for this reference.
14286
14287                Check_Arg_Is_Local_Name (Arg_Node);
14288                Arg_Expr := Get_Pragma_Arg (Arg_Node);
14289
14290                if Is_Entity_Name (Arg_Expr) then
14291                   Arg_Ent := Entity (Arg_Expr);
14292
14293                   if not Is_Assignable (Arg_Ent) then
14294                      Error_Pragma_Arg
14295                        ("pragma% can only be applied to a variable",
14296                         Arg_Expr);
14297                   else
14298                      Set_Has_Pragma_Unmodified (Arg_Ent);
14299                   end if;
14300                end if;
14301
14302                Next (Arg_Node);
14303             end loop;
14304          end Unmodified;
14305
14306          ------------------
14307          -- Unreferenced --
14308          ------------------
14309
14310          --  pragma Unreferenced (local_Name {, local_Name});
14311
14312          --    or when used in a context clause:
14313
14314          --  pragma Unreferenced (library_unit_NAME {, library_unit_NAME}
14315
14316          when Pragma_Unreferenced => Unreferenced : declare
14317             Arg_Node : Node_Id;
14318             Arg_Expr : Node_Id;
14319             Arg_Ent  : Entity_Id;
14320             Citem    : Node_Id;
14321
14322          begin
14323             GNAT_Pragma;
14324             Check_At_Least_N_Arguments (1);
14325
14326             --  Check case of appearing within context clause
14327
14328             if Is_In_Context_Clause then
14329
14330                --  The arguments must all be units mentioned in a with clause
14331                --  in the same context clause. Note we already checked (in
14332                --  Par.Prag) that the arguments are either identifiers or
14333                --  selected components.
14334
14335                Arg_Node := Arg1;
14336                while Present (Arg_Node) loop
14337                   Citem := First (List_Containing (N));
14338                   while Citem /= N loop
14339                      if Nkind (Citem) = N_With_Clause
14340                        and then
14341                          Same_Name (Name (Citem), Get_Pragma_Arg (Arg_Node))
14342                      then
14343                         Set_Has_Pragma_Unreferenced
14344                           (Cunit_Entity
14345                              (Get_Source_Unit
14346                                 (Library_Unit (Citem))));
14347                         Set_Unit_Name
14348                           (Get_Pragma_Arg (Arg_Node), Name (Citem));
14349                         exit;
14350                      end if;
14351
14352                      Next (Citem);
14353                   end loop;
14354
14355                   if Citem = N then
14356                      Error_Pragma_Arg
14357                        ("argument of pragma% is not withed unit", Arg_Node);
14358                   end if;
14359
14360                   Next (Arg_Node);
14361                end loop;
14362
14363             --  Case of not in list of context items
14364
14365             else
14366                Arg_Node := Arg1;
14367                while Present (Arg_Node) loop
14368                   Check_No_Identifier (Arg_Node);
14369
14370                   --  Note: the analyze call done by Check_Arg_Is_Local_Name
14371                   --  will in fact generate reference, so that the entity will
14372                   --  have a reference, which will inhibit any warnings about
14373                   --  it not being referenced, and also properly show up in the
14374                   --  ali file as a reference. But this reference is recorded
14375                   --  before the Has_Pragma_Unreferenced flag is set, so that
14376                   --  no warning is generated for this reference.
14377
14378                   Check_Arg_Is_Local_Name (Arg_Node);
14379                   Arg_Expr := Get_Pragma_Arg (Arg_Node);
14380
14381                   if Is_Entity_Name (Arg_Expr) then
14382                      Arg_Ent := Entity (Arg_Expr);
14383
14384                      --  If the entity is overloaded, the pragma applies to the
14385                      --  most recent overloading, as documented. In this case,
14386                      --  name resolution does not generate a reference, so it
14387                      --  must be done here explicitly.
14388
14389                      if Is_Overloaded (Arg_Expr) then
14390                         Generate_Reference (Arg_Ent, N);
14391                      end if;
14392
14393                      Set_Has_Pragma_Unreferenced (Arg_Ent);
14394                   end if;
14395
14396                   Next (Arg_Node);
14397                end loop;
14398             end if;
14399          end Unreferenced;
14400
14401          --------------------------
14402          -- Unreferenced_Objects --
14403          --------------------------
14404
14405          --  pragma Unreferenced_Objects (local_Name {, local_Name});
14406
14407          when Pragma_Unreferenced_Objects => Unreferenced_Objects : declare
14408             Arg_Node : Node_Id;
14409             Arg_Expr : Node_Id;
14410
14411          begin
14412             GNAT_Pragma;
14413             Check_At_Least_N_Arguments (1);
14414
14415             Arg_Node := Arg1;
14416             while Present (Arg_Node) loop
14417                Check_No_Identifier (Arg_Node);
14418                Check_Arg_Is_Local_Name (Arg_Node);
14419                Arg_Expr := Get_Pragma_Arg (Arg_Node);
14420
14421                if not Is_Entity_Name (Arg_Expr)
14422                  or else not Is_Type (Entity (Arg_Expr))
14423                then
14424                   Error_Pragma_Arg
14425                     ("argument for pragma% must be type or subtype", Arg_Node);
14426                end if;
14427
14428                Set_Has_Pragma_Unreferenced_Objects (Entity (Arg_Expr));
14429                Next (Arg_Node);
14430             end loop;
14431          end Unreferenced_Objects;
14432
14433          ------------------------------
14434          -- Unreserve_All_Interrupts --
14435          ------------------------------
14436
14437          --  pragma Unreserve_All_Interrupts;
14438
14439          when Pragma_Unreserve_All_Interrupts =>
14440             GNAT_Pragma;
14441             Check_Arg_Count (0);
14442
14443             if In_Extended_Main_Code_Unit (Main_Unit_Entity) then
14444                Unreserve_All_Interrupts := True;
14445             end if;
14446
14447          ----------------
14448          -- Unsuppress --
14449          ----------------
14450
14451          --  pragma Unsuppress (IDENTIFIER [, [On =>] NAME]);
14452
14453          when Pragma_Unsuppress =>
14454             Ada_2005_Pragma;
14455             Process_Suppress_Unsuppress (False);
14456
14457          -------------------
14458          -- Use_VADS_Size --
14459          -------------------
14460
14461          --  pragma Use_VADS_Size;
14462
14463          when Pragma_Use_VADS_Size =>
14464             GNAT_Pragma;
14465             Check_Arg_Count (0);
14466             Check_Valid_Configuration_Pragma;
14467             Use_VADS_Size := True;
14468
14469          ---------------------
14470          -- Validity_Checks --
14471          ---------------------
14472
14473          --  pragma Validity_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
14474
14475          when Pragma_Validity_Checks => Validity_Checks : declare
14476             A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
14477             S  : String_Id;
14478             C  : Char_Code;
14479
14480          begin
14481             GNAT_Pragma;
14482             Check_Arg_Count (1);
14483             Check_No_Identifiers;
14484
14485             if Nkind (A) = N_String_Literal then
14486                S   := Strval (A);
14487
14488                declare
14489                   Slen    : constant Natural := Natural (String_Length (S));
14490                   Options : String (1 .. Slen);
14491                   J       : Natural;
14492
14493                begin
14494                   J := 1;
14495                   loop
14496                      C := Get_String_Char (S, Int (J));
14497                      exit when not In_Character_Range (C);
14498                      Options (J) := Get_Character (C);
14499
14500                      if J = Slen then
14501                         Set_Validity_Check_Options (Options);
14502                         exit;
14503                      else
14504                         J := J + 1;
14505                      end if;
14506                   end loop;
14507                end;
14508
14509             elsif Nkind (A) = N_Identifier then
14510                if Chars (A) = Name_All_Checks then
14511                   Set_Validity_Check_Options ("a");
14512                elsif Chars (A) = Name_On then
14513                   Validity_Checks_On := True;
14514                elsif Chars (A) = Name_Off then
14515                   Validity_Checks_On := False;
14516                end if;
14517             end if;
14518          end Validity_Checks;
14519
14520          --------------
14521          -- Volatile --
14522          --------------
14523
14524          --  pragma Volatile (LOCAL_NAME);
14525
14526          when Pragma_Volatile =>
14527             Process_Atomic_Shared_Volatile;
14528
14529          -------------------------
14530          -- Volatile_Components --
14531          -------------------------
14532
14533          --  pragma Volatile_Components (array_LOCAL_NAME);
14534
14535          --  Volatile is handled by the same circuit as Atomic_Components
14536
14537          --------------
14538          -- Warnings --
14539          --------------
14540
14541          --  pragma Warnings (On | Off);
14542          --  pragma Warnings (On | Off, LOCAL_NAME);
14543          --  pragma Warnings (static_string_EXPRESSION);
14544          --  pragma Warnings (On | Off, STRING_LITERAL);
14545
14546          when Pragma_Warnings => Warnings : begin
14547             GNAT_Pragma;
14548             Check_At_Least_N_Arguments (1);
14549             Check_No_Identifiers;
14550
14551             --  If debug flag -gnatd.i is set, pragma is ignored
14552
14553             if Debug_Flag_Dot_I then
14554                return;
14555             end if;
14556
14557             --  Process various forms of the pragma
14558
14559             declare
14560                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
14561
14562             begin
14563                --  One argument case
14564
14565                if Arg_Count = 1 then
14566
14567                   --  On/Off one argument case was processed by parser
14568
14569                   if Nkind (Argx) = N_Identifier
14570                     and then
14571                       (Chars (Argx) = Name_On
14572                          or else
14573                        Chars (Argx) = Name_Off)
14574                   then
14575                      null;
14576
14577                   --  One argument case must be ON/OFF or static string expr
14578
14579                   elsif not Is_Static_String_Expression (Arg1) then
14580                      Error_Pragma_Arg
14581                        ("argument of pragma% must be On/Off or " &
14582                         "static string expression", Arg1);
14583
14584                   --  One argument string expression case
14585
14586                   else
14587                      declare
14588                         Lit : constant Node_Id   := Expr_Value_S (Argx);
14589                         Str : constant String_Id := Strval (Lit);
14590                         Len : constant Nat       := String_Length (Str);
14591                         C   : Char_Code;
14592                         J   : Nat;
14593                         OK  : Boolean;
14594                         Chr : Character;
14595
14596                      begin
14597                         J := 1;
14598                         while J <= Len loop
14599                            C := Get_String_Char (Str, J);
14600                            OK := In_Character_Range (C);
14601
14602                            if OK then
14603                               Chr := Get_Character (C);
14604
14605                               --  Dot case
14606
14607                               if J < Len and then Chr = '.' then
14608                                  J := J + 1;
14609                                  C := Get_String_Char (Str, J);
14610                                  Chr := Get_Character (C);
14611
14612                                  if not Set_Dot_Warning_Switch (Chr) then
14613                                     Error_Pragma_Arg
14614                                       ("invalid warning switch character " &
14615                                        '.' & Chr, Arg1);
14616                                  end if;
14617
14618                               --  Non-Dot case
14619
14620                               else
14621                                  OK := Set_Warning_Switch (Chr);
14622                               end if;
14623                            end if;
14624
14625                            if not OK then
14626                               Error_Pragma_Arg
14627                                 ("invalid warning switch character " & Chr,
14628                                  Arg1);
14629                            end if;
14630
14631                            J := J + 1;
14632                         end loop;
14633                      end;
14634                   end if;
14635
14636                --  Two or more arguments (must be two)
14637
14638                else
14639                   Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
14640                   Check_At_Most_N_Arguments (2);
14641
14642                   declare
14643                      E_Id : Node_Id;
14644                      E    : Entity_Id;
14645                      Err  : Boolean;
14646
14647                   begin
14648                      E_Id := Get_Pragma_Arg (Arg2);
14649                      Analyze (E_Id);
14650
14651                      --  In the expansion of an inlined body, a reference to
14652                      --  the formal may be wrapped in a conversion if the
14653                      --  actual is a conversion. Retrieve the real entity name.
14654
14655                      if (In_Instance_Body or In_Inlined_Body)
14656                        and then Nkind (E_Id) = N_Unchecked_Type_Conversion
14657                      then
14658                         E_Id := Expression (E_Id);
14659                      end if;
14660
14661                      --  Entity name case
14662
14663                      if Is_Entity_Name (E_Id) then
14664                         E := Entity (E_Id);
14665
14666                         if E = Any_Id then
14667                            return;
14668                         else
14669                            loop
14670                               Set_Warnings_Off
14671                                 (E, (Chars (Get_Pragma_Arg (Arg1)) =
14672                                                               Name_Off));
14673
14674                               if Chars (Get_Pragma_Arg (Arg1)) = Name_Off
14675                                 and then Warn_On_Warnings_Off
14676                               then
14677                                  Warnings_Off_Pragmas.Append ((N, E));
14678                               end if;
14679
14680                               if Is_Enumeration_Type (E) then
14681                                  declare
14682                                     Lit : Entity_Id;
14683                                  begin
14684                                     Lit := First_Literal (E);
14685                                     while Present (Lit) loop
14686                                        Set_Warnings_Off (Lit);
14687                                        Next_Literal (Lit);
14688                                     end loop;
14689                                  end;
14690                               end if;
14691
14692                               exit when No (Homonym (E));
14693                               E := Homonym (E);
14694                            end loop;
14695                         end if;
14696
14697                      --  Error if not entity or static string literal case
14698
14699                      elsif not Is_Static_String_Expression (Arg2) then
14700                         Error_Pragma_Arg
14701                           ("second argument of pragma% must be entity " &
14702                            "name or static string expression", Arg2);
14703
14704                      --  String literal case
14705
14706                      else
14707                         String_To_Name_Buffer
14708                           (Strval (Expr_Value_S (Get_Pragma_Arg (Arg2))));
14709
14710                         --  Note on configuration pragma case: If this is a
14711                         --  configuration pragma, then for an OFF pragma, we
14712                         --  just set Config True in the call, which is all
14713                         --  that needs to be done. For the case of ON, this
14714                         --  is normally an error, unless it is canceling the
14715                         --  effect of a previous OFF pragma in the same file.
14716                         --  In any other case, an error will be signalled (ON
14717                         --  with no matching OFF).
14718
14719                         --  Note: We set Used if we are inside a generic to
14720                         --  disable the test that the non-config case actually
14721                         --  cancels a warning. That's because we can't be sure
14722                         --  there isn't an instantiation in some other unit
14723                         --  where a warning is suppressed.
14724
14725                         --  We could do a little better here by checking if the
14726                         --  generic unit we are inside is public, but for now
14727                         --  we don't bother with that refinement.
14728
14729                         if Chars (Argx) = Name_Off then
14730                            Set_Specific_Warning_Off
14731                              (Loc, Name_Buffer (1 .. Name_Len),
14732                               Config => Is_Configuration_Pragma,
14733                               Used   => Inside_A_Generic or else In_Instance);
14734
14735                         elsif Chars (Argx) = Name_On then
14736                            Set_Specific_Warning_On
14737                              (Loc, Name_Buffer (1 .. Name_Len), Err);
14738
14739                            if Err then
14740                               Error_Msg
14741                                 ("?pragma Warnings On with no " &
14742                                  "matching Warnings Off",
14743                                  Loc);
14744                            end if;
14745                         end if;
14746                      end if;
14747                   end;
14748                end if;
14749             end;
14750          end Warnings;
14751
14752          -------------------
14753          -- Weak_External --
14754          -------------------
14755
14756          --  pragma Weak_External ([Entity =>] LOCAL_NAME);
14757
14758          when Pragma_Weak_External => Weak_External : declare
14759             Ent : Entity_Id;
14760
14761          begin
14762             GNAT_Pragma;
14763             Check_Arg_Count (1);
14764             Check_Optional_Identifier (Arg1, Name_Entity);
14765             Check_Arg_Is_Library_Level_Local_Name (Arg1);
14766             Ent := Entity (Get_Pragma_Arg (Arg1));
14767
14768             if Rep_Item_Too_Early (Ent, N) then
14769                return;
14770             else
14771                Ent := Underlying_Type (Ent);
14772             end if;
14773
14774             --  The only processing required is to link this item on to the
14775             --  list of rep items for the given entity. This is accomplished
14776             --  by the call to Rep_Item_Too_Late (when no error is detected
14777             --  and False is returned).
14778
14779             if Rep_Item_Too_Late (Ent, N) then
14780                return;
14781             else
14782                Set_Has_Gigi_Rep_Item (Ent);
14783             end if;
14784          end Weak_External;
14785
14786          -----------------------------
14787          -- Wide_Character_Encoding --
14788          -----------------------------
14789
14790          --  pragma Wide_Character_Encoding (IDENTIFIER);
14791
14792          when Pragma_Wide_Character_Encoding =>
14793             GNAT_Pragma;
14794
14795             --  Nothing to do, handled in parser. Note that we do not enforce
14796             --  configuration pragma placement, this pragma can appear at any
14797             --  place in the source, allowing mixed encodings within a single
14798             --  source program.
14799
14800             null;
14801
14802          --------------------
14803          -- Unknown_Pragma --
14804          --------------------
14805
14806          --  Should be impossible, since the case of an unknown pragma is
14807          --  separately processed before the case statement is entered.
14808
14809          when Unknown_Pragma =>
14810             raise Program_Error;
14811       end case;
14812
14813       --  AI05-0144: detect dangerous order dependence. Disabled for now,
14814       --  until AI is formally approved.
14815
14816       --  Check_Order_Dependence;
14817
14818    exception
14819       when Pragma_Exit => null;
14820    end Analyze_Pragma;
14821
14822    -----------------------------
14823    -- Analyze_TC_In_Decl_Part --
14824    -----------------------------
14825
14826    procedure Analyze_TC_In_Decl_Part (N : Node_Id; S : Entity_Id) is
14827    begin
14828       --  Install formals and push subprogram spec onto scope stack so that we
14829       --  can see the formals from the pragma.
14830
14831       Install_Formals (S);
14832       Push_Scope (S);
14833
14834       --  Preanalyze the boolean expressions, we treat these as spec
14835       --  expressions (i.e. similar to a default expression).
14836
14837       Preanalyze_TC_Args (N,
14838                           Get_Requires_From_Test_Case_Pragma (N),
14839                           Get_Ensures_From_Test_Case_Pragma (N));
14840
14841       --  Remove the subprogram from the scope stack now that the pre-analysis
14842       --  of the expressions in the test-case is done.
14843
14844       End_Scope;
14845    end Analyze_TC_In_Decl_Part;
14846
14847    --------------------
14848    -- Check_Disabled --
14849    --------------------
14850
14851    function Check_Disabled (Nam : Name_Id) return Boolean is
14852       PP : Node_Id;
14853
14854    begin
14855       --  Loop through entries in check policy list
14856
14857       PP := Opt.Check_Policy_List;
14858       loop
14859          --  If there are no specific entries that matched, then nothing is
14860          --  disabled, so return False.
14861
14862          if No (PP) then
14863             return False;
14864
14865          --  Here we have an entry see if it matches
14866
14867          else
14868             declare
14869                PPA : constant List_Id := Pragma_Argument_Associations (PP);
14870             begin
14871                if Nam = Chars (Get_Pragma_Arg (First (PPA))) then
14872                   return Chars (Get_Pragma_Arg (Last (PPA))) = Name_Disable;
14873                else
14874                   PP := Next_Pragma (PP);
14875                end if;
14876             end;
14877          end if;
14878       end loop;
14879    end Check_Disabled;
14880
14881    -------------------
14882    -- Check_Enabled --
14883    -------------------
14884
14885    function Check_Enabled (Nam : Name_Id) return Boolean is
14886       PP : Node_Id;
14887
14888    begin
14889       --  Loop through entries in check policy list
14890
14891       PP := Opt.Check_Policy_List;
14892       loop
14893          --  If there are no specific entries that matched, then we let the
14894          --  setting of assertions govern. Note that this provides the needed
14895          --  compatibility with the RM for the cases of assertion, invariant,
14896          --  precondition, predicate, and postcondition.
14897
14898          if No (PP) then
14899             return Assertions_Enabled;
14900
14901          --  Here we have an entry see if it matches
14902
14903          else
14904             declare
14905                PPA : constant List_Id := Pragma_Argument_Associations (PP);
14906
14907             begin
14908                if Nam = Chars (Get_Pragma_Arg (First (PPA))) then
14909                   case (Chars (Get_Pragma_Arg (Last (PPA)))) is
14910                      when Name_On | Name_Check =>
14911                         return True;
14912                      when Name_Off | Name_Ignore =>
14913                         return False;
14914                      when others =>
14915                         raise Program_Error;
14916                   end case;
14917
14918                else
14919                   PP := Next_Pragma (PP);
14920                end if;
14921             end;
14922          end if;
14923       end loop;
14924    end Check_Enabled;
14925
14926    ---------------------------------
14927    -- Delay_Config_Pragma_Analyze --
14928    ---------------------------------
14929
14930    function Delay_Config_Pragma_Analyze (N : Node_Id) return Boolean is
14931    begin
14932       return Pragma_Name (N) = Name_Interrupt_State
14933                or else
14934              Pragma_Name (N) = Name_Priority_Specific_Dispatching;
14935    end Delay_Config_Pragma_Analyze;
14936
14937    -------------------------
14938    -- Get_Base_Subprogram --
14939    -------------------------
14940
14941    function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id is
14942       Result : Entity_Id;
14943
14944    begin
14945       --  Follow subprogram renaming chain
14946
14947       Result := Def_Id;
14948
14949       if Is_Subprogram (Result)
14950         and then
14951           Nkind (Parent (Declaration_Node (Result))) =
14952                                          N_Subprogram_Renaming_Declaration
14953         and then Present (Alias (Result))
14954       then
14955          Result := Alias (Result);
14956       end if;
14957
14958       return Result;
14959    end Get_Base_Subprogram;
14960
14961    ----------------
14962    -- Initialize --
14963    ----------------
14964
14965    procedure Initialize is
14966    begin
14967       Externals.Init;
14968    end Initialize;
14969
14970    -----------------------------
14971    -- Is_Config_Static_String --
14972    -----------------------------
14973
14974    function Is_Config_Static_String (Arg : Node_Id) return Boolean is
14975
14976       function Add_Config_Static_String (Arg : Node_Id) return Boolean;
14977       --  This is an internal recursive function that is just like the outer
14978       --  function except that it adds the string to the name buffer rather
14979       --  than placing the string in the name buffer.
14980
14981       ------------------------------
14982       -- Add_Config_Static_String --
14983       ------------------------------
14984
14985       function Add_Config_Static_String (Arg : Node_Id) return Boolean is
14986          N : Node_Id;
14987          C : Char_Code;
14988
14989       begin
14990          N := Arg;
14991
14992          if Nkind (N) = N_Op_Concat then
14993             if Add_Config_Static_String (Left_Opnd (N)) then
14994                N := Right_Opnd (N);
14995             else
14996                return False;
14997             end if;
14998          end if;
14999
15000          if Nkind (N) /= N_String_Literal then
15001             Error_Msg_N ("string literal expected for pragma argument", N);
15002             return False;
15003
15004          else
15005             for J in 1 .. String_Length (Strval (N)) loop
15006                C := Get_String_Char (Strval (N), J);
15007
15008                if not In_Character_Range (C) then
15009                   Error_Msg
15010                     ("string literal contains invalid wide character",
15011                      Sloc (N) + 1 + Source_Ptr (J));
15012                   return False;
15013                end if;
15014
15015                Add_Char_To_Name_Buffer (Get_Character (C));
15016             end loop;
15017          end if;
15018
15019          return True;
15020       end Add_Config_Static_String;
15021
15022    --  Start of processing for Is_Config_Static_String
15023
15024    begin
15025
15026       Name_Len := 0;
15027       return Add_Config_Static_String (Arg);
15028    end Is_Config_Static_String;
15029
15030    -----------------------------------------
15031    -- Is_Non_Significant_Pragma_Reference --
15032    -----------------------------------------
15033
15034    --  This function makes use of the following static table which indicates
15035    --  whether appearance of some name in a given pragma is to be considered
15036    --  as a reference for the purposes of warnings about unreferenced objects.
15037
15038    --  -1  indicates that references in any argument position are significant
15039    --  0   indicates that appearance in any argument is not significant
15040    --  +n  indicates that appearance as argument n is significant, but all
15041    --      other arguments are not significant
15042    --  99  special processing required (e.g. for pragma Check)
15043
15044    Sig_Flags : constant array (Pragma_Id) of Int :=
15045      (Pragma_AST_Entry                      => -1,
15046       Pragma_Abort_Defer                    => -1,
15047       Pragma_Ada_83                         => -1,
15048       Pragma_Ada_95                         => -1,
15049       Pragma_Ada_05                         => -1,
15050       Pragma_Ada_2005                       => -1,
15051       Pragma_Ada_12                         => -1,
15052       Pragma_Ada_2012                       => -1,
15053       Pragma_All_Calls_Remote               => -1,
15054       Pragma_Annotate                       => -1,
15055       Pragma_Assert                         => -1,
15056       Pragma_Assertion_Policy               =>  0,
15057       Pragma_Assume_No_Invalid_Values       =>  0,
15058       Pragma_Asynchronous                   => -1,
15059       Pragma_Atomic                         =>  0,
15060       Pragma_Atomic_Components              =>  0,
15061       Pragma_Attach_Handler                 => -1,
15062       Pragma_Check                          => 99,
15063       Pragma_Check_Name                     =>  0,
15064       Pragma_Check_Policy                   =>  0,
15065       Pragma_CIL_Constructor                => -1,
15066       Pragma_CPP_Class                      =>  0,
15067       Pragma_CPP_Constructor                =>  0,
15068       Pragma_CPP_Virtual                    =>  0,
15069       Pragma_CPP_Vtable                     =>  0,
15070       Pragma_CPU                            => -1,
15071       Pragma_C_Pass_By_Copy                 =>  0,
15072       Pragma_Comment                        =>  0,
15073       Pragma_Common_Object                  => -1,
15074       Pragma_Compile_Time_Error             => -1,
15075       Pragma_Compile_Time_Warning           => -1,
15076       Pragma_Compiler_Unit                  =>  0,
15077       Pragma_Complete_Representation        =>  0,
15078       Pragma_Complex_Representation         =>  0,
15079       Pragma_Component_Alignment            => -1,
15080       Pragma_Controlled                     =>  0,
15081       Pragma_Convention                     =>  0,
15082       Pragma_Convention_Identifier          =>  0,
15083       Pragma_Debug                          => -1,
15084       Pragma_Debug_Policy                   =>  0,
15085       Pragma_Detect_Blocking                => -1,
15086       Pragma_Default_Storage_Pool           => -1,
15087       Pragma_Disable_Atomic_Synchronization => -1,
15088       Pragma_Discard_Names                  =>  0,
15089       Pragma_Dispatching_Domain             => -1,
15090       Pragma_Elaborate                      => -1,
15091       Pragma_Elaborate_All                  => -1,
15092       Pragma_Elaborate_Body                 => -1,
15093       Pragma_Elaboration_Checks             => -1,
15094       Pragma_Eliminate                      => -1,
15095       Pragma_Enable_Atomic_Synchronization  => -1,
15096       Pragma_Export                         => -1,
15097       Pragma_Export_Exception               => -1,
15098       Pragma_Export_Function                => -1,
15099       Pragma_Export_Object                  => -1,
15100       Pragma_Export_Procedure               => -1,
15101       Pragma_Export_Value                   => -1,
15102       Pragma_Export_Valued_Procedure        => -1,
15103       Pragma_Extend_System                  => -1,
15104       Pragma_Extensions_Allowed             => -1,
15105       Pragma_External                       => -1,
15106       Pragma_Favor_Top_Level                => -1,
15107       Pragma_External_Name_Casing           => -1,
15108       Pragma_Fast_Math                      => -1,
15109       Pragma_Finalize_Storage_Only          =>  0,
15110       Pragma_Float_Representation           =>  0,
15111       Pragma_Ident                          => -1,
15112       Pragma_Implementation_Defined         => -1,
15113       Pragma_Implemented                    => -1,
15114       Pragma_Implicit_Packing               =>  0,
15115       Pragma_Import                         => +2,
15116       Pragma_Import_Exception               =>  0,
15117       Pragma_Import_Function                =>  0,
15118       Pragma_Import_Object                  =>  0,
15119       Pragma_Import_Procedure               =>  0,
15120       Pragma_Import_Valued_Procedure        =>  0,
15121       Pragma_Independent                    =>  0,
15122       Pragma_Independent_Components         =>  0,
15123       Pragma_Initialize_Scalars             => -1,
15124       Pragma_Inline                         =>  0,
15125       Pragma_Inline_Always                  =>  0,
15126       Pragma_Inline_Generic                 =>  0,
15127       Pragma_Inspection_Point               => -1,
15128       Pragma_Interface                      => +2,
15129       Pragma_Interface_Name                 => +2,
15130       Pragma_Interrupt_Handler              => -1,
15131       Pragma_Interrupt_Priority             => -1,
15132       Pragma_Interrupt_State                => -1,
15133       Pragma_Invariant                      => -1,
15134       Pragma_Java_Constructor               => -1,
15135       Pragma_Java_Interface                 => -1,
15136       Pragma_Keep_Names                     =>  0,
15137       Pragma_License                        => -1,
15138       Pragma_Link_With                      => -1,
15139       Pragma_Linker_Alias                   => -1,
15140       Pragma_Linker_Constructor             => -1,
15141       Pragma_Linker_Destructor              => -1,
15142       Pragma_Linker_Options                 => -1,
15143       Pragma_Linker_Section                 => -1,
15144       Pragma_List                           => -1,
15145       Pragma_Locking_Policy                 => -1,
15146       Pragma_Long_Float                     => -1,
15147       Pragma_Machine_Attribute              => -1,
15148       Pragma_Main                           => -1,
15149       Pragma_Main_Storage                   => -1,
15150       Pragma_Memory_Size                    => -1,
15151       Pragma_No_Return                      =>  0,
15152       Pragma_No_Body                        =>  0,
15153       Pragma_No_Run_Time                    => -1,
15154       Pragma_No_Strict_Aliasing             => -1,
15155       Pragma_Normalize_Scalars              => -1,
15156       Pragma_Obsolescent                    =>  0,
15157       Pragma_Optimize                       => -1,
15158       Pragma_Optimize_Alignment             => -1,
15159       Pragma_Ordered                        =>  0,
15160       Pragma_Pack                           =>  0,
15161       Pragma_Page                           => -1,
15162       Pragma_Passive                        => -1,
15163       Pragma_Preelaborable_Initialization   => -1,
15164       Pragma_Polling                        => -1,
15165       Pragma_Persistent_BSS                 =>  0,
15166       Pragma_Postcondition                  => -1,
15167       Pragma_Precondition                   => -1,
15168       Pragma_Predicate                      => -1,
15169       Pragma_Preelaborate                   => -1,
15170       Pragma_Preelaborate_05                => -1,
15171       Pragma_Priority                       => -1,
15172       Pragma_Priority_Specific_Dispatching  => -1,
15173       Pragma_Profile                        =>  0,
15174       Pragma_Profile_Warnings               =>  0,
15175       Pragma_Propagate_Exceptions           => -1,
15176       Pragma_Psect_Object                   => -1,
15177       Pragma_Pure                           => -1,
15178       Pragma_Pure_05                        => -1,
15179       Pragma_Pure_12                        => -1,
15180       Pragma_Pure_Function                  => -1,
15181       Pragma_Queuing_Policy                 => -1,
15182       Pragma_Ravenscar                      => -1,
15183       Pragma_Relative_Deadline              => -1,
15184       Pragma_Remote_Access_Type             => -1,
15185       Pragma_Remote_Call_Interface          => -1,
15186       Pragma_Remote_Types                   => -1,
15187       Pragma_Restricted_Run_Time            => -1,
15188       Pragma_Restriction_Warnings           => -1,
15189       Pragma_Restrictions                   => -1,
15190       Pragma_Reviewable                     => -1,
15191       Pragma_Short_Circuit_And_Or           => -1,
15192       Pragma_Share_Generic                  => -1,
15193       Pragma_Shared                         => -1,
15194       Pragma_Shared_Passive                 => -1,
15195       Pragma_Short_Descriptors              =>  0,
15196       Pragma_Simple_Storage_Pool_Type       =>  0,
15197       Pragma_Source_File_Name               => -1,
15198       Pragma_Source_File_Name_Project       => -1,
15199       Pragma_Source_Reference               => -1,
15200       Pragma_Storage_Size                   => -1,
15201       Pragma_Storage_Unit                   => -1,
15202       Pragma_Static_Elaboration_Desired     => -1,
15203       Pragma_Stream_Convert                 => -1,
15204       Pragma_Style_Checks                   => -1,
15205       Pragma_Subtitle                       => -1,
15206       Pragma_Suppress                       =>  0,
15207       Pragma_Suppress_Exception_Locations   =>  0,
15208       Pragma_Suppress_All                   => -1,
15209       Pragma_Suppress_Debug_Info            =>  0,
15210       Pragma_Suppress_Initialization        =>  0,
15211       Pragma_System_Name                    => -1,
15212       Pragma_Task_Dispatching_Policy        => -1,
15213       Pragma_Task_Info                      => -1,
15214       Pragma_Task_Name                      => -1,
15215       Pragma_Task_Storage                   =>  0,
15216       Pragma_Test_Case                      => -1,
15217       Pragma_Thread_Local_Storage           =>  0,
15218       Pragma_Time_Slice                     => -1,
15219       Pragma_Title                          => -1,
15220       Pragma_Unchecked_Union                =>  0,
15221       Pragma_Unimplemented_Unit             => -1,
15222       Pragma_Universal_Aliasing             => -1,
15223       Pragma_Universal_Data                 => -1,
15224       Pragma_Unmodified                     => -1,
15225       Pragma_Unreferenced                   => -1,
15226       Pragma_Unreferenced_Objects           => -1,
15227       Pragma_Unreserve_All_Interrupts       => -1,
15228       Pragma_Unsuppress                     =>  0,
15229       Pragma_Use_VADS_Size                  => -1,
15230       Pragma_Validity_Checks                => -1,
15231       Pragma_Volatile                       =>  0,
15232       Pragma_Volatile_Components            =>  0,
15233       Pragma_Warnings                       => -1,
15234       Pragma_Weak_External                  => -1,
15235       Pragma_Wide_Character_Encoding        =>  0,
15236       Unknown_Pragma                        =>  0);
15237
15238    function Is_Non_Significant_Pragma_Reference (N : Node_Id) return Boolean is
15239       Id : Pragma_Id;
15240       P  : Node_Id;
15241       C  : Int;
15242       A  : Node_Id;
15243
15244    begin
15245       P := Parent (N);
15246
15247       if Nkind (P) /= N_Pragma_Argument_Association then
15248          return False;
15249
15250       else
15251          Id := Get_Pragma_Id (Parent (P));
15252          C := Sig_Flags (Id);
15253
15254          case C is
15255             when -1 =>
15256                return False;
15257
15258             when 0 =>
15259                return True;
15260
15261             when 99 =>
15262                case Id is
15263
15264                   --  For pragma Check, the first argument is not significant,
15265                   --  the second and the third (if present) arguments are
15266                   --  significant.
15267
15268                   when Pragma_Check =>
15269                      return
15270                        P = First (Pragma_Argument_Associations (Parent (P)));
15271
15272                   when others =>
15273                      raise Program_Error;
15274                end case;
15275
15276             when others =>
15277                A := First (Pragma_Argument_Associations (Parent (P)));
15278                for J in 1 .. C - 1 loop
15279                   if No (A) then
15280                      return False;
15281                   end if;
15282
15283                   Next (A);
15284                end loop;
15285
15286                return A = P; -- is this wrong way round ???
15287          end case;
15288       end if;
15289    end Is_Non_Significant_Pragma_Reference;
15290
15291    ------------------------------
15292    -- Is_Pragma_String_Literal --
15293    ------------------------------
15294
15295    --  This function returns true if the corresponding pragma argument is a
15296    --  static string expression. These are the only cases in which string
15297    --  literals can appear as pragma arguments. We also allow a string literal
15298    --  as the first argument to pragma Assert (although it will of course
15299    --  always generate a type error).
15300
15301    function Is_Pragma_String_Literal (Par : Node_Id) return Boolean is
15302       Pragn : constant Node_Id := Parent (Par);
15303       Assoc : constant List_Id := Pragma_Argument_Associations (Pragn);
15304       Pname : constant Name_Id := Pragma_Name (Pragn);
15305       Argn  : Natural;
15306       N     : Node_Id;
15307
15308    begin
15309       Argn := 1;
15310       N := First (Assoc);
15311       loop
15312          exit when N = Par;
15313          Argn := Argn + 1;
15314          Next (N);
15315       end loop;
15316
15317       if Pname = Name_Assert then
15318          return True;
15319
15320       elsif Pname = Name_Export then
15321          return Argn > 2;
15322
15323       elsif Pname = Name_Ident then
15324          return Argn = 1;
15325
15326       elsif Pname = Name_Import then
15327          return Argn > 2;
15328
15329       elsif Pname = Name_Interface_Name then
15330          return Argn > 1;
15331
15332       elsif Pname = Name_Linker_Alias then
15333          return Argn = 2;
15334
15335       elsif Pname = Name_Linker_Section then
15336          return Argn = 2;
15337
15338       elsif Pname = Name_Machine_Attribute then
15339          return Argn = 2;
15340
15341       elsif Pname = Name_Source_File_Name then
15342          return True;
15343
15344       elsif Pname = Name_Source_Reference then
15345          return Argn = 2;
15346
15347       elsif Pname = Name_Title then
15348          return True;
15349
15350       elsif Pname = Name_Subtitle then
15351          return True;
15352
15353       else
15354          return False;
15355       end if;
15356    end Is_Pragma_String_Literal;
15357
15358    -----------------------------------------
15359    -- Make_Aspect_For_PPC_In_Gen_Sub_Decl --
15360    -----------------------------------------
15361
15362    procedure Make_Aspect_For_PPC_In_Gen_Sub_Decl (Decl : Node_Id) is
15363       Aspects : constant List_Id := New_List;
15364       Loc     : constant Source_Ptr := Sloc (Decl);
15365       Or_Decl : constant Node_Id := Original_Node (Decl);
15366
15367       Original_Aspects : List_Id;
15368       --  To capture global references, a copy of the created aspects must be
15369       --  inserted in the original tree.
15370
15371       Prag         : Node_Id;
15372       Prag_Arg_Ass : Node_Id;
15373       Prag_Id      : Pragma_Id;
15374
15375    begin
15376       --  Check for any PPC pragmas that appear within Decl
15377
15378       Prag := Next (Decl);
15379       while Nkind (Prag) = N_Pragma loop
15380          Prag_Id := Get_Pragma_Id (Chars (Pragma_Identifier (Prag)));
15381
15382          case Prag_Id is
15383             when Pragma_Postcondition | Pragma_Precondition =>
15384                Prag_Arg_Ass := First (Pragma_Argument_Associations (Prag));
15385
15386                --  Make an aspect from any PPC pragma
15387
15388                Append_To (Aspects,
15389                  Make_Aspect_Specification (Loc,
15390                    Identifier =>
15391                      Make_Identifier (Loc, Chars (Pragma_Identifier (Prag))),
15392                    Expression =>
15393                      Copy_Separate_Tree (Expression (Prag_Arg_Ass))));
15394
15395                --  Generate the analysis information in the pragma expression
15396                --  and then set the pragma node analyzed to avoid any further
15397                --  analysis.
15398
15399                Analyze (Expression (Prag_Arg_Ass));
15400                Set_Analyzed (Prag, True);
15401
15402             when others => null;
15403          end case;
15404
15405          Next (Prag);
15406       end loop;
15407
15408       --  Set all new aspects into the generic declaration node
15409
15410       if Is_Non_Empty_List (Aspects) then
15411
15412          --  Create the list of aspects to be inserted in the original tree
15413
15414          Original_Aspects := Copy_Separate_List (Aspects);
15415
15416          --  Check if Decl already has aspects
15417
15418          --  Attach the new lists of aspects to both the generic copy and the
15419          --  original tree.
15420
15421          if Has_Aspects (Decl) then
15422             Append_List (Aspects, Aspect_Specifications (Decl));
15423             Append_List (Original_Aspects, Aspect_Specifications (Or_Decl));
15424
15425          else
15426             Set_Parent (Aspects, Decl);
15427             Set_Aspect_Specifications (Decl, Aspects);
15428             Set_Parent (Original_Aspects, Or_Decl);
15429             Set_Aspect_Specifications (Or_Decl, Original_Aspects);
15430          end if;
15431       end if;
15432    end Make_Aspect_For_PPC_In_Gen_Sub_Decl;
15433
15434    ------------------------
15435    -- Preanalyze_TC_Args --
15436    ------------------------
15437
15438    procedure Preanalyze_TC_Args (N, Arg_Req, Arg_Ens : Node_Id) is
15439    begin
15440       --  Preanalyze the boolean expressions, we treat these as spec
15441       --  expressions (i.e. similar to a default expression).
15442
15443       if Present (Arg_Req) then
15444          Preanalyze_Spec_Expression
15445            (Get_Pragma_Arg (Arg_Req), Standard_Boolean);
15446
15447          --  In ASIS mode, for a pragma generated from a source aspect, also
15448          --  analyze the original aspect expression.
15449
15450          if ASIS_Mode and then Present (Corresponding_Aspect (N)) then
15451             Preanalyze_Spec_Expression
15452               (Original_Node (Get_Pragma_Arg (Arg_Req)), Standard_Boolean);
15453          end if;
15454       end if;
15455
15456       if Present (Arg_Ens) then
15457          Preanalyze_Spec_Expression
15458            (Get_Pragma_Arg (Arg_Ens), Standard_Boolean);
15459
15460          --  In ASIS mode, for a pragma generated from a source aspect, also
15461          --  analyze the original aspect expression.
15462
15463          if ASIS_Mode and then Present (Corresponding_Aspect (N)) then
15464             Preanalyze_Spec_Expression
15465               (Original_Node (Get_Pragma_Arg (Arg_Ens)), Standard_Boolean);
15466          end if;
15467       end if;
15468    end Preanalyze_TC_Args;
15469
15470    --------------------------------------
15471    -- Process_Compilation_Unit_Pragmas --
15472    --------------------------------------
15473
15474    procedure Process_Compilation_Unit_Pragmas (N : Node_Id) is
15475    begin
15476       --  A special check for pragma Suppress_All, a very strange DEC pragma,
15477       --  strange because it comes at the end of the unit. Rational has the
15478       --  same name for a pragma, but treats it as a program unit pragma, In
15479       --  GNAT we just decide to allow it anywhere at all. If it appeared then
15480       --  the flag Has_Pragma_Suppress_All was set on the compilation unit
15481       --  node, and we insert a pragma Suppress (All_Checks) at the start of
15482       --  the context clause to ensure the correct processing.
15483
15484       if Has_Pragma_Suppress_All (N) then
15485          Prepend_To (Context_Items (N),
15486            Make_Pragma (Sloc (N),
15487              Chars                        => Name_Suppress,
15488              Pragma_Argument_Associations => New_List (
15489                Make_Pragma_Argument_Association (Sloc (N),
15490                  Expression => Make_Identifier (Sloc (N), Name_All_Checks)))));
15491       end if;
15492
15493       --  Nothing else to do at the current time!
15494
15495    end Process_Compilation_Unit_Pragmas;
15496
15497    --------
15498    -- rv --
15499    --------
15500
15501    procedure rv is
15502    begin
15503       null;
15504    end rv;
15505
15506    --------------------------------
15507    -- Set_Encoded_Interface_Name --
15508    --------------------------------
15509
15510    procedure Set_Encoded_Interface_Name (E : Entity_Id; S : Node_Id) is
15511       Str : constant String_Id := Strval (S);
15512       Len : constant Int       := String_Length (Str);
15513       CC  : Char_Code;
15514       C   : Character;
15515       J   : Int;
15516
15517       Hex : constant array (0 .. 15) of Character := "0123456789abcdef";
15518
15519       procedure Encode;
15520       --  Stores encoded value of character code CC. The encoding we use an
15521       --  underscore followed by four lower case hex digits.
15522
15523       ------------
15524       -- Encode --
15525       ------------
15526
15527       procedure Encode is
15528       begin
15529          Store_String_Char (Get_Char_Code ('_'));
15530          Store_String_Char
15531            (Get_Char_Code (Hex (Integer (CC / 2 ** 12))));
15532          Store_String_Char
15533            (Get_Char_Code (Hex (Integer (CC / 2 ** 8 and 16#0F#))));
15534          Store_String_Char
15535            (Get_Char_Code (Hex (Integer (CC / 2 ** 4 and 16#0F#))));
15536          Store_String_Char
15537            (Get_Char_Code (Hex (Integer (CC and 16#0F#))));
15538       end Encode;
15539
15540    --  Start of processing for Set_Encoded_Interface_Name
15541
15542    begin
15543       --  If first character is asterisk, this is a link name, and we leave it
15544       --  completely unmodified. We also ignore null strings (the latter case
15545       --  happens only in error cases) and no encoding should occur for Java or
15546       --  AAMP interface names.
15547
15548       if Len = 0
15549         or else Get_String_Char (Str, 1) = Get_Char_Code ('*')
15550         or else VM_Target /= No_VM
15551         or else AAMP_On_Target
15552       then
15553          Set_Interface_Name (E, S);
15554
15555       else
15556          J := 1;
15557          loop
15558             CC := Get_String_Char (Str, J);
15559
15560             exit when not In_Character_Range (CC);
15561
15562             C := Get_Character (CC);
15563
15564             exit when C /= '_' and then C /= '$'
15565               and then C not in '0' .. '9'
15566               and then C not in 'a' .. 'z'
15567               and then C not in 'A' .. 'Z';
15568
15569             if J = Len then
15570                Set_Interface_Name (E, S);
15571                return;
15572
15573             else
15574                J := J + 1;
15575             end if;
15576          end loop;
15577
15578          --  Here we need to encode. The encoding we use as follows:
15579          --     three underscores  + four hex digits (lower case)
15580
15581          Start_String;
15582
15583          for J in 1 .. String_Length (Str) loop
15584             CC := Get_String_Char (Str, J);
15585
15586             if not In_Character_Range (CC) then
15587                Encode;
15588             else
15589                C := Get_Character (CC);
15590
15591                if C = '_' or else C = '$'
15592                  or else C in '0' .. '9'
15593                  or else C in 'a' .. 'z'
15594                  or else C in 'A' .. 'Z'
15595                then
15596                   Store_String_Char (CC);
15597                else
15598                   Encode;
15599                end if;
15600             end if;
15601          end loop;
15602
15603          Set_Interface_Name (E,
15604            Make_String_Literal (Sloc (S),
15605              Strval => End_String));
15606       end if;
15607    end Set_Encoded_Interface_Name;
15608
15609    -------------------
15610    -- Set_Unit_Name --
15611    -------------------
15612
15613    procedure Set_Unit_Name (N : Node_Id; With_Item : Node_Id) is
15614       Pref : Node_Id;
15615       Scop : Entity_Id;
15616
15617    begin
15618       if Nkind (N) = N_Identifier
15619         and then Nkind (With_Item) = N_Identifier
15620       then
15621          Set_Entity (N, Entity (With_Item));
15622
15623       elsif Nkind (N) = N_Selected_Component then
15624          Change_Selected_Component_To_Expanded_Name (N);
15625          Set_Entity (N, Entity (With_Item));
15626          Set_Entity (Selector_Name (N), Entity (N));
15627
15628          Pref := Prefix (N);
15629          Scop := Scope (Entity (N));
15630          while Nkind (Pref) = N_Selected_Component loop
15631             Change_Selected_Component_To_Expanded_Name (Pref);
15632             Set_Entity (Selector_Name (Pref), Scop);
15633             Set_Entity (Pref, Scop);
15634             Pref := Prefix (Pref);
15635             Scop := Scope (Scop);
15636          end loop;
15637
15638          Set_Entity (Pref, Scop);
15639       end if;
15640    end Set_Unit_Name;
15641
15642 end Sem_Prag;