OSDN Git Service

2012-01-30 Robert Dewar <dewar@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_prag.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                             S E M _ P R A G                              --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-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          declare
282             T   : constant Entity_Id := Find_Dispatching_Type (S);
283
284             ACW : Entity_Id := Empty;
285             --  Access to T'class, created if there is a controlling formal
286             --  that is an access parameter.
287
288             function Get_ACW return Entity_Id;
289             --  If the expression has a reference to an controlling access
290             --  parameter, create an access to T'class for the necessary
291             --  conversions if one does not exist.
292
293             function Process (N : Node_Id) return Traverse_Result;
294             --  ARM 6.1.1: Within the expression for a Pre'Class or Post'Class
295             --  aspect for a primitive subprogram of a tagged type T, a name
296             --  that denotes a formal parameter of type T is interpreted as
297             --  having type T'Class. Similarly, a name that denotes a formal
298             --  accessparameter of type access-to-T is interpreted as having
299             --  type access-to-T'Class. This ensures the expression is well-
300             --  defined for a primitive subprogram of a type descended from T.
301
302             -------------
303             -- Get_ACW --
304             -------------
305
306             function Get_ACW return Entity_Id is
307                Loc  : constant Source_Ptr := Sloc (N);
308                Decl : Node_Id;
309
310             begin
311                if No (ACW) then
312                   Decl := Make_Full_Type_Declaration (Loc,
313                     Defining_Identifier => Make_Temporary (Loc, 'T'),
314                     Type_Definition =>
315                        Make_Access_To_Object_Definition (Loc,
316                        Subtype_Indication =>
317                          New_Occurrence_Of (Class_Wide_Type (T), Loc),
318                        All_Present => True));
319
320                   Insert_Before (Unit_Declaration_Node (S), Decl);
321                   Analyze (Decl);
322                   ACW := Defining_Identifier (Decl);
323                   Freeze_Before (Unit_Declaration_Node (S), ACW);
324                end if;
325
326                return ACW;
327             end Get_ACW;
328
329             -------------
330             -- Process --
331             -------------
332
333             function Process (N : Node_Id) return Traverse_Result is
334                Loc : constant Source_Ptr := Sloc (N);
335                Typ : Entity_Id;
336
337             begin
338                if Is_Entity_Name (N)
339                  and then Is_Formal (Entity (N))
340                  and then Nkind (Parent (N)) /= N_Type_Conversion
341                then
342                   if Etype (Entity (N)) = T then
343                      Typ := Class_Wide_Type (T);
344
345                   elsif Is_Access_Type (Etype (Entity (N)))
346                     and then Designated_Type (Etype (Entity (N))) = T
347                   then
348                      Typ := Get_ACW;
349                   else
350                      Typ := Empty;
351                   end if;
352
353                   if Present (Typ) then
354                      Rewrite (N,
355                        Make_Type_Conversion (Loc,
356                          Subtype_Mark =>
357                            New_Occurrence_Of (Typ, Loc),
358                          Expression  => New_Occurrence_Of (Entity (N), Loc)));
359                      Set_Etype (N, Typ);
360                   end if;
361                end if;
362
363                return OK;
364             end Process;
365
366             procedure Replace_Type is new Traverse_Proc (Process);
367
368          begin
369             Replace_Type (Get_Pragma_Arg (Arg1));
370          end;
371       end if;
372
373       --  Remove the subprogram from the scope stack now that the pre-analysis
374       --  of the precondition/postcondition is done.
375
376       End_Scope;
377    end Analyze_PPC_In_Decl_Part;
378
379    --------------------
380    -- Analyze_Pragma --
381    --------------------
382
383    procedure Analyze_Pragma (N : Node_Id) is
384       Loc     : constant Source_Ptr := Sloc (N);
385       Prag_Id : Pragma_Id;
386
387       Pname : Name_Id;
388       --  Name of the source pragma, or name of the corresponding aspect for
389       --  pragmas which originate in a source aspect. In the latter case, the
390       --  name may be different from the pragma name.
391
392       Pragma_Exit : exception;
393       --  This exception is used to exit pragma processing completely. It is
394       --  used when an error is detected, and no further processing is
395       --  required. It is also used if an earlier error has left the tree in
396       --  a state where the pragma should not be processed.
397
398       Arg_Count : Nat;
399       --  Number of pragma argument associations
400
401       Arg1 : Node_Id;
402       Arg2 : Node_Id;
403       Arg3 : Node_Id;
404       Arg4 : Node_Id;
405       --  First four pragma arguments (pragma argument association nodes, or
406       --  Empty if the corresponding argument does not exist).
407
408       type Name_List is array (Natural range <>) of Name_Id;
409       type Args_List is array (Natural range <>) of Node_Id;
410       --  Types used for arguments to Check_Arg_Order and Gather_Associations
411
412       procedure Ada_2005_Pragma;
413       --  Called for pragmas defined in Ada 2005, that are not in Ada 95. In
414       --  Ada 95 mode, these are implementation defined pragmas, so should be
415       --  caught by the No_Implementation_Pragmas restriction.
416
417       procedure Ada_2012_Pragma;
418       --  Called for pragmas defined in Ada 2012, that are not in Ada 95 or 05.
419       --  In Ada 95 or 05 mode, these are implementation defined pragmas, so
420       --  should be caught by the No_Implementation_Pragmas restriction.
421
422       procedure Check_Ada_83_Warning;
423       --  Issues a warning message for the current pragma if operating in Ada
424       --  83 mode (used for language pragmas that are not a standard part of
425       --  Ada 83). This procedure does not raise Error_Pragma. Also notes use
426       --  of 95 pragma.
427
428       procedure Check_Arg_Count (Required : Nat);
429       --  Check argument count for pragma is equal to given parameter. If not,
430       --  then issue an error message and raise Pragma_Exit.
431
432       --  Note: all routines whose name is Check_Arg_Is_xxx take an argument
433       --  Arg which can either be a pragma argument association, in which case
434       --  the check is applied to the expression of the association or an
435       --  expression directly.
436
437       procedure Check_Arg_Is_External_Name (Arg : Node_Id);
438       --  Check that an argument has the right form for an EXTERNAL_NAME
439       --  parameter of an extended import/export pragma. The rule is that the
440       --  name must be an identifier or string literal (in Ada 83 mode) or a
441       --  static string expression (in Ada 95 mode).
442
443       procedure Check_Arg_Is_Identifier (Arg : Node_Id);
444       --  Check the specified argument Arg to make sure that it is an
445       --  identifier. If not give error and raise Pragma_Exit.
446
447       procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id);
448       --  Check the specified argument Arg to make sure that it is an integer
449       --  literal. If not give error and raise Pragma_Exit.
450
451       procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id);
452       --  Check the specified argument Arg to make sure that it has the proper
453       --  syntactic form for a local name and meets the semantic requirements
454       --  for a local name. The local name is analyzed as part of the
455       --  processing for this call. In addition, the local name is required
456       --  to represent an entity at the library level.
457
458       procedure Check_Arg_Is_Local_Name (Arg : Node_Id);
459       --  Check the specified argument Arg to make sure that it has the proper
460       --  syntactic form for a local name and meets the semantic requirements
461       --  for a local name. The local name is analyzed as part of the
462       --  processing for this call.
463
464       procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id);
465       --  Check the specified argument Arg to make sure that it is a valid
466       --  locking policy name. If not give error and raise Pragma_Exit.
467
468       procedure Check_Arg_Is_One_Of
469         (Arg                : Node_Id;
470          N1, N2             : Name_Id);
471       procedure Check_Arg_Is_One_Of
472         (Arg                : Node_Id;
473          N1, N2, N3         : Name_Id);
474       procedure Check_Arg_Is_One_Of
475         (Arg                : Node_Id;
476          N1, N2, N3, N4     : Name_Id);
477       procedure Check_Arg_Is_One_Of
478         (Arg                : Node_Id;
479          N1, N2, N3, N4, N5 : Name_Id);
480       --  Check the specified argument Arg to make sure that it is an
481       --  identifier whose name matches either N1 or N2 (or N3, N4, N5 if
482       --  present). If not then give error and raise Pragma_Exit.
483
484       procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id);
485       --  Check the specified argument Arg to make sure that it is a valid
486       --  queuing policy name. If not give error and raise Pragma_Exit.
487
488       procedure Check_Arg_Is_Static_Expression
489         (Arg : Node_Id;
490          Typ : Entity_Id := Empty);
491       --  Check the specified argument Arg to make sure that it is a static
492       --  expression of the given type (i.e. it will be analyzed and resolved
493       --  using this type, which can be any valid argument to Resolve, e.g.
494       --  Any_Integer is OK). If not, given error and raise Pragma_Exit. If
495       --  Typ is left Empty, then any static expression is allowed.
496
497       procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id);
498       --  Check the specified argument Arg to make sure that it is a valid task
499       --  dispatching policy name. If not give error and raise Pragma_Exit.
500
501       procedure Check_Arg_Order (Names : Name_List);
502       --  Checks for an instance of two arguments with identifiers for the
503       --  current pragma which are not in the sequence indicated by Names,
504       --  and if so, generates a fatal message about bad order of arguments.
505
506       procedure Check_At_Least_N_Arguments (N : Nat);
507       --  Check there are at least N arguments present
508
509       procedure Check_At_Most_N_Arguments (N : Nat);
510       --  Check there are no more than N arguments present
511
512       procedure Check_Component
513         (Comp            : Node_Id;
514          UU_Typ          : Entity_Id;
515          In_Variant_Part : Boolean := False);
516       --  Examine an Unchecked_Union component for correct use of per-object
517       --  constrained subtypes, and for restrictions on finalizable components.
518       --  UU_Typ is the related Unchecked_Union type. Flag In_Variant_Part
519       --  should be set when Comp comes from a record variant.
520
521       procedure Check_Duplicate_Pragma (E : Entity_Id);
522       --  Check if a pragma of the same name as the current pragma is already
523       --  chained as a rep pragma to the given entity. If so give a message
524       --  about the duplicate, and then raise Pragma_Exit so does not return.
525       --  Also checks for delayed aspect specification node in the chain.
526
527       procedure Check_Duplicated_Export_Name (Nam : Node_Id);
528       --  Nam is an N_String_Literal node containing the external name set by
529       --  an Import or Export pragma (or extended Import or Export pragma).
530       --  This procedure checks for possible duplications if this is the export
531       --  case, and if found, issues an appropriate error message.
532
533       procedure Check_Expr_Is_Static_Expression
534         (Expr : Node_Id;
535          Typ  : Entity_Id := Empty);
536       --  Check the specified expression Expr to make sure that it is a static
537       --  expression of the given type (i.e. it will be analyzed and resolved
538       --  using this type, which can be any valid argument to Resolve, e.g.
539       --  Any_Integer is OK). If not, given error and raise Pragma_Exit. If
540       --  Typ is left Empty, then any static expression is allowed.
541
542       procedure Check_First_Subtype (Arg : Node_Id);
543       --  Checks that Arg, whose expression is an entity name, references a
544       --  first subtype.
545
546       procedure Check_Identifier (Arg : Node_Id; Id : Name_Id);
547       --  Checks that the given argument has an identifier, and if so, requires
548       --  it to match the given identifier name. If there is no identifier, or
549       --  a non-matching identifier, then an error message is given and
550       --  Pragma_Exit is raised.
551
552       procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id);
553       --  Checks that the given argument has an identifier, and if so, requires
554       --  it to match one of the given identifier names. If there is no
555       --  identifier, or a non-matching identifier, then an error message is
556       --  given and Pragma_Exit is raised.
557
558       procedure Check_In_Main_Program;
559       --  Common checks for pragmas that appear within a main program
560       --  (Priority, Main_Storage, Time_Slice, Relative_Deadline, CPU).
561
562       procedure Check_Interrupt_Or_Attach_Handler;
563       --  Common processing for first argument of pragma Interrupt_Handler or
564       --  pragma Attach_Handler.
565
566       procedure Check_Is_In_Decl_Part_Or_Package_Spec;
567       --  Check that pragma appears in a declarative part, or in a package
568       --  specification, i.e. that it does not occur in a statement sequence
569       --  in a body.
570
571       procedure Check_No_Identifier (Arg : Node_Id);
572       --  Checks that the given argument does not have an identifier. If
573       --  an identifier is present, then an error message is issued, and
574       --  Pragma_Exit is raised.
575
576       procedure Check_No_Identifiers;
577       --  Checks that none of the arguments to the pragma has an identifier.
578       --  If any argument has an identifier, then an error message is issued,
579       --  and Pragma_Exit is raised.
580
581       procedure Check_No_Link_Name;
582       --  Checks that no link name is specified
583
584       procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id);
585       --  Checks if the given argument has an identifier, and if so, requires
586       --  it to match the given identifier name. If there is a non-matching
587       --  identifier, then an error message is given and Pragma_Exit is raised.
588
589       procedure Check_Optional_Identifier (Arg : Node_Id; Id : String);
590       --  Checks if the given argument has an identifier, and if so, requires
591       --  it to match the given identifier name. If there is a non-matching
592       --  identifier, then an error message is given and Pragma_Exit is raised.
593       --  In this version of the procedure, the identifier name is given as
594       --  a string with lower case letters.
595
596       procedure Check_Precondition_Postcondition (In_Body : out Boolean);
597       --  Called to process a precondition or postcondition pragma. There are
598       --  three cases:
599       --
600       --    The pragma appears after a subprogram spec
601       --
602       --      If the corresponding check is not enabled, the pragma is analyzed
603       --      but otherwise ignored and control returns with In_Body set False.
604       --
605       --      If the check is enabled, then the first step is to analyze the
606       --      pragma, but this is skipped if the subprogram spec appears within
607       --      a package specification (because this is the case where we delay
608       --      analysis till the end of the spec). Then (whether or not it was
609       --      analyzed), the pragma is chained to the subprogram in question
610       --      (using Spec_PPC_List and Next_Pragma) and control returns to the
611       --      caller with In_Body set False.
612       --
613       --    The pragma appears at the start of subprogram body declarations
614       --
615       --      In this case an immediate return to the caller is made with
616       --      In_Body set True, and the pragma is NOT analyzed.
617       --
618       --    In all other cases, an error message for bad placement is given
619
620       procedure Check_Static_Constraint (Constr : Node_Id);
621       --  Constr is a constraint from an N_Subtype_Indication node from a
622       --  component constraint in an Unchecked_Union type. This routine checks
623       --  that the constraint is static as required by the restrictions for
624       --  Unchecked_Union.
625
626       procedure Check_Test_Case;
627       --  Called to process a test-case pragma. The treatment is similar to the
628       --  one for pre- and postcondition in Check_Precondition_Postcondition,
629       --  except the placement rules for the test-case pragma are stricter.
630       --  This pragma may only occur after a subprogram spec declared directly
631       --  in a package spec unit. In this case, the pragma is chained to the
632       --  subprogram in question (using Spec_TC_List and Next_Pragma) and
633       --  analysis of the pragma is delayed till the end of the spec. In
634       --  all other cases, an error message for bad placement is given.
635
636       procedure Check_Valid_Configuration_Pragma;
637       --  Legality checks for placement of a configuration pragma
638
639       procedure Check_Valid_Library_Unit_Pragma;
640       --  Legality checks for library unit pragmas. A special case arises for
641       --  pragmas in generic instances that come from copies of the original
642       --  library unit pragmas in the generic templates. In the case of other
643       --  than library level instantiations these can appear in contexts which
644       --  would normally be invalid (they only apply to the original template
645       --  and to library level instantiations), and they are simply ignored,
646       --  which is implemented by rewriting them as null statements.
647
648       procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id);
649       --  Check an Unchecked_Union variant for lack of nested variants and
650       --  presence of at least one component. UU_Typ is the related Unchecked_
651       --  Union type.
652
653       procedure Error_Pragma (Msg : String);
654       pragma No_Return (Error_Pragma);
655       --  Outputs error message for current pragma. The message contains a %
656       --  that will be replaced with the pragma name, and the flag is placed
657       --  on the pragma itself. Pragma_Exit is then raised.
658
659       procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id);
660       pragma No_Return (Error_Pragma_Arg);
661       --  Outputs error message for current pragma. The message may contain
662       --  a % that will be replaced with the pragma name. The parameter Arg
663       --  may either be a pragma argument association, in which case the flag
664       --  is placed on the expression of this association, or an expression,
665       --  in which case the flag is placed directly on the expression. The
666       --  message is placed using Error_Msg_N, so the message may also contain
667       --  an & insertion character which will reference the given Arg value.
668       --  After placing the message, Pragma_Exit is raised.
669
670       procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id);
671       pragma No_Return (Error_Pragma_Arg);
672       --  Similar to above form of Error_Pragma_Arg except that two messages
673       --  are provided, the second is a continuation comment starting with \.
674
675       procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id);
676       pragma No_Return (Error_Pragma_Arg_Ident);
677       --  Outputs error message for current pragma. The message may contain
678       --  a % that will be replaced with the pragma name. The parameter Arg
679       --  must be a pragma argument association with a non-empty identifier
680       --  (i.e. its Chars field must be set), and the error message is placed
681       --  on the identifier. The message is placed using Error_Msg_N so
682       --  the message may also contain an & insertion character which will
683       --  reference the identifier. After placing the message, Pragma_Exit
684       --  is raised.
685
686       procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id);
687       pragma No_Return (Error_Pragma_Ref);
688       --  Outputs error message for current pragma. The message may contain
689       --  a % that will be replaced with the pragma name. The parameter Ref
690       --  must be an entity whose name can be referenced by & and sloc by #.
691       --  After placing the message, Pragma_Exit is raised.
692
693       function Find_Lib_Unit_Name return Entity_Id;
694       --  Used for a library unit pragma to find the entity to which the
695       --  library unit pragma applies, returns the entity found.
696
697       procedure Find_Program_Unit_Name (Id : Node_Id);
698       --  If the pragma is a compilation unit pragma, the id must denote the
699       --  compilation unit in the same compilation, and the pragma must appear
700       --  in the list of preceding or trailing pragmas. If it is a program
701       --  unit pragma that is not a compilation unit pragma, then the
702       --  identifier must be visible.
703
704       function Find_Unique_Parameterless_Procedure
705         (Name : Entity_Id;
706          Arg  : Node_Id) return Entity_Id;
707       --  Used for a procedure pragma to find the unique parameterless
708       --  procedure identified by Name, returns it if it exists, otherwise
709       --  errors out and uses Arg as the pragma argument for the message.
710
711       procedure Fix_Error (Msg : in out String);
712       --  This is called prior to issuing an error message. Msg is a string
713       --  that typically contains the substring "pragma". If the current pragma
714       --  comes from an aspect, each such "pragma" substring is replaced with
715       --  the characters "aspect", and if Error_Msg_Name_1 is Name_Precondition
716       --  (resp Name_Postcondition) it is changed to Name_Pre (resp Name_Post).
717
718       procedure Gather_Associations
719         (Names : Name_List;
720          Args  : out Args_List);
721       --  This procedure is used to gather the arguments for a pragma that
722       --  permits arbitrary ordering of parameters using the normal rules
723       --  for named and positional parameters. The Names argument is a list
724       --  of Name_Id values that corresponds to the allowed pragma argument
725       --  association identifiers in order. The result returned in Args is
726       --  a list of corresponding expressions that are the pragma arguments.
727       --  Note that this is a list of expressions, not of pragma argument
728       --  associations (Gather_Associations has completely checked all the
729       --  optional identifiers when it returns). An entry in Args is Empty
730       --  on return if the corresponding argument is not present.
731
732       procedure GNAT_Pragma;
733       --  Called for all GNAT defined pragmas to check the relevant restriction
734       --  (No_Implementation_Pragmas).
735
736       function Is_Before_First_Decl
737         (Pragma_Node : Node_Id;
738          Decls       : List_Id) return Boolean;
739       --  Return True if Pragma_Node is before the first declarative item in
740       --  Decls where Decls is the list of declarative items.
741
742       function Is_Configuration_Pragma return Boolean;
743       --  Determines if the placement of the current pragma is appropriate
744       --  for a configuration pragma.
745
746       function Is_In_Context_Clause return Boolean;
747       --  Returns True if pragma appears within the context clause of a unit,
748       --  and False for any other placement (does not generate any messages).
749
750       function Is_Static_String_Expression (Arg : Node_Id) return Boolean;
751       --  Analyzes the argument, and determines if it is a static string
752       --  expression, returns True if so, False if non-static or not String.
753
754       procedure Pragma_Misplaced;
755       pragma No_Return (Pragma_Misplaced);
756       --  Issue fatal error message for misplaced pragma
757
758       procedure Process_Atomic_Shared_Volatile;
759       --  Common processing for pragmas Atomic, Shared, Volatile. Note that
760       --  Shared is an obsolete Ada 83 pragma, treated as being identical
761       --  in effect to pragma Atomic.
762
763       procedure Process_Compile_Time_Warning_Or_Error;
764       --  Common processing for Compile_Time_Error and Compile_Time_Warning
765
766       procedure Process_Convention
767         (C   : out Convention_Id;
768          Ent : out Entity_Id);
769       --  Common processing for Convention, Interface, Import and Export.
770       --  Checks first two arguments of pragma, and sets the appropriate
771       --  convention value in the specified entity or entities. On return
772       --  C is the convention, Ent is the referenced entity.
773
774       procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id);
775       --  Common processing for Disable/Enable_Atomic_Synchronization. Nam is
776       --  Name_Suppress for Disable and Name_Unsuppress for Enable.
777
778       procedure Process_Extended_Import_Export_Exception_Pragma
779         (Arg_Internal : Node_Id;
780          Arg_External : Node_Id;
781          Arg_Form     : Node_Id;
782          Arg_Code     : Node_Id);
783       --  Common processing for the pragmas Import/Export_Exception. The three
784       --  arguments correspond to the three named parameters of the pragma. An
785       --  argument is empty if the corresponding parameter is not present in
786       --  the pragma.
787
788       procedure Process_Extended_Import_Export_Object_Pragma
789         (Arg_Internal : Node_Id;
790          Arg_External : Node_Id;
791          Arg_Size     : Node_Id);
792       --  Common processing for the pragmas Import/Export_Object. The three
793       --  arguments correspond to the three named parameters of the pragmas. An
794       --  argument is empty if the corresponding parameter is not present in
795       --  the pragma.
796
797       procedure Process_Extended_Import_Export_Internal_Arg
798         (Arg_Internal : Node_Id := Empty);
799       --  Common processing for all extended Import and Export pragmas. The
800       --  argument is the pragma parameter for the Internal argument. If
801       --  Arg_Internal is empty or inappropriate, an error message is posted.
802       --  Otherwise, on normal return, the Entity_Field of Arg_Internal is
803       --  set to identify the referenced entity.
804
805       procedure Process_Extended_Import_Export_Subprogram_Pragma
806         (Arg_Internal                 : Node_Id;
807          Arg_External                 : Node_Id;
808          Arg_Parameter_Types          : Node_Id;
809          Arg_Result_Type              : Node_Id := Empty;
810          Arg_Mechanism                : Node_Id;
811          Arg_Result_Mechanism         : Node_Id := Empty;
812          Arg_First_Optional_Parameter : Node_Id := Empty);
813       --  Common processing for all extended Import and Export pragmas applying
814       --  to subprograms. The caller omits any arguments that do not apply to
815       --  the pragma in question (for example, Arg_Result_Type can be non-Empty
816       --  only in the Import_Function and Export_Function cases). The argument
817       --  names correspond to the allowed pragma association identifiers.
818
819       procedure Process_Generic_List;
820       --  Common processing for Share_Generic and Inline_Generic
821
822       procedure Process_Import_Or_Interface;
823       --  Common processing for Import of Interface
824
825       procedure Process_Import_Predefined_Type;
826       --  Processing for completing a type with pragma Import. This is used
827       --  to declare types that match predefined C types, especially for cases
828       --  without corresponding Ada predefined type.
829
830       procedure Process_Inline (Active : Boolean);
831       --  Common processing for Inline and Inline_Always. The parameter
832       --  indicates if the inline pragma is active, i.e. if it should actually
833       --  cause inlining to occur.
834
835       procedure Process_Interface_Name
836         (Subprogram_Def : Entity_Id;
837          Ext_Arg        : Node_Id;
838          Link_Arg       : Node_Id);
839       --  Given the last two arguments of pragma Import, pragma Export, or
840       --  pragma Interface_Name, performs validity checks and sets the
841       --  Interface_Name field of the given subprogram entity to the
842       --  appropriate external or link name, depending on the arguments given.
843       --  Ext_Arg is always present, but Link_Arg may be missing. Note that
844       --  Ext_Arg may represent the Link_Name if Link_Arg is missing, and
845       --  appropriate named notation is used for Ext_Arg. If neither Ext_Arg
846       --  nor Link_Arg is present, the interface name is set to the default
847       --  from the subprogram name.
848
849       procedure Process_Interrupt_Or_Attach_Handler;
850       --  Common processing for Interrupt and Attach_Handler pragmas
851
852       procedure Process_Restrictions_Or_Restriction_Warnings (Warn : Boolean);
853       --  Common processing for Restrictions and Restriction_Warnings pragmas.
854       --  Warn is True for Restriction_Warnings, or for Restrictions if the
855       --  flag Treat_Restrictions_As_Warnings is set, and False if this flag
856       --  is not set in the Restrictions case.
857
858       procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean);
859       --  Common processing for Suppress and Unsuppress. The boolean parameter
860       --  Suppress_Case is True for the Suppress case, and False for the
861       --  Unsuppress case.
862
863       procedure Set_Exported (E : Entity_Id; Arg : Node_Id);
864       --  This procedure sets the Is_Exported flag for the given entity,
865       --  checking that the entity was not previously imported. Arg is
866       --  the argument that specified the entity. A check is also made
867       --  for exporting inappropriate entities.
868
869       procedure Set_Extended_Import_Export_External_Name
870         (Internal_Ent : Entity_Id;
871          Arg_External : Node_Id);
872       --  Common processing for all extended import export pragmas. The first
873       --  argument, Internal_Ent, is the internal entity, which has already
874       --  been checked for validity by the caller. Arg_External is from the
875       --  Import or Export pragma, and may be null if no External parameter
876       --  was present. If Arg_External is present and is a non-null string
877       --  (a null string is treated as the default), then the Interface_Name
878       --  field of Internal_Ent is set appropriately.
879
880       procedure Set_Imported (E : Entity_Id);
881       --  This procedure sets the Is_Imported flag for the given entity,
882       --  checking that it is not previously exported or imported.
883
884       procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id);
885       --  Mech is a parameter passing mechanism (see Import_Function syntax
886       --  for MECHANISM_NAME). This routine checks that the mechanism argument
887       --  has the right form, and if not issues an error message. If the
888       --  argument has the right form then the Mechanism field of Ent is
889       --  set appropriately.
890
891       procedure Set_Ravenscar_Profile (N : Node_Id);
892       --  Activate the set of configuration pragmas and restrictions that make
893       --  up the Ravenscar Profile. N is the corresponding pragma node, which
894       --  is used for error messages on any constructs that violate the
895       --  profile.
896
897       ---------------------
898       -- Ada_2005_Pragma --
899       ---------------------
900
901       procedure Ada_2005_Pragma is
902       begin
903          if Ada_Version <= Ada_95 then
904             Check_Restriction (No_Implementation_Pragmas, N);
905          end if;
906       end Ada_2005_Pragma;
907
908       ---------------------
909       -- Ada_2012_Pragma --
910       ---------------------
911
912       procedure Ada_2012_Pragma is
913       begin
914          if Ada_Version <= Ada_2005 then
915             Check_Restriction (No_Implementation_Pragmas, N);
916          end if;
917       end Ada_2012_Pragma;
918
919       --------------------------
920       -- Check_Ada_83_Warning --
921       --------------------------
922
923       procedure Check_Ada_83_Warning is
924       begin
925          if Ada_Version = Ada_83 and then Comes_From_Source (N) then
926             Error_Msg_N ("(Ada 83) pragma& is non-standard?", N);
927          end if;
928       end Check_Ada_83_Warning;
929
930       ---------------------
931       -- Check_Arg_Count --
932       ---------------------
933
934       procedure Check_Arg_Count (Required : Nat) is
935       begin
936          if Arg_Count /= Required then
937             Error_Pragma ("wrong number of arguments for pragma%");
938          end if;
939       end Check_Arg_Count;
940
941       --------------------------------
942       -- Check_Arg_Is_External_Name --
943       --------------------------------
944
945       procedure Check_Arg_Is_External_Name (Arg : Node_Id) is
946          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
947
948       begin
949          if Nkind (Argx) = N_Identifier then
950             return;
951
952          else
953             Analyze_And_Resolve (Argx, Standard_String);
954
955             if Is_OK_Static_Expression (Argx) then
956                return;
957
958             elsif Etype (Argx) = Any_Type then
959                raise Pragma_Exit;
960
961             --  An interesting special case, if we have a string literal and
962             --  we are in Ada 83 mode, then we allow it even though it will
963             --  not be flagged as static. This allows expected Ada 83 mode
964             --  use of external names which are string literals, even though
965             --  technically these are not static in Ada 83.
966
967             elsif Ada_Version = Ada_83
968               and then Nkind (Argx) = N_String_Literal
969             then
970                return;
971
972             --  Static expression that raises Constraint_Error. This has
973             --  already been flagged, so just exit from pragma processing.
974
975             elsif Is_Static_Expression (Argx) then
976                raise Pragma_Exit;
977
978             --  Here we have a real error (non-static expression)
979
980             else
981                Error_Msg_Name_1 := Pname;
982
983                declare
984                   Msg : String :=
985                           "argument for pragma% must be a identifier or "
986                           & "static string expression!";
987                begin
988                   Fix_Error (Msg);
989                   Flag_Non_Static_Expr (Msg, Argx);
990                   raise Pragma_Exit;
991                end;
992             end if;
993          end if;
994       end Check_Arg_Is_External_Name;
995
996       -----------------------------
997       -- Check_Arg_Is_Identifier --
998       -----------------------------
999
1000       procedure Check_Arg_Is_Identifier (Arg : Node_Id) is
1001          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1002       begin
1003          if Nkind (Argx) /= N_Identifier then
1004             Error_Pragma_Arg
1005               ("argument for pragma% must be identifier", Argx);
1006          end if;
1007       end Check_Arg_Is_Identifier;
1008
1009       ----------------------------------
1010       -- Check_Arg_Is_Integer_Literal --
1011       ----------------------------------
1012
1013       procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id) is
1014          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1015       begin
1016          if Nkind (Argx) /= N_Integer_Literal then
1017             Error_Pragma_Arg
1018               ("argument for pragma% must be integer literal", Argx);
1019          end if;
1020       end Check_Arg_Is_Integer_Literal;
1021
1022       -------------------------------------------
1023       -- Check_Arg_Is_Library_Level_Local_Name --
1024       -------------------------------------------
1025
1026       --  LOCAL_NAME ::=
1027       --    DIRECT_NAME
1028       --  | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
1029       --  | library_unit_NAME
1030
1031       procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id) is
1032       begin
1033          Check_Arg_Is_Local_Name (Arg);
1034
1035          if not Is_Library_Level_Entity (Entity (Get_Pragma_Arg (Arg)))
1036            and then Comes_From_Source (N)
1037          then
1038             Error_Pragma_Arg
1039               ("argument for pragma% must be library level entity", Arg);
1040          end if;
1041       end Check_Arg_Is_Library_Level_Local_Name;
1042
1043       -----------------------------
1044       -- Check_Arg_Is_Local_Name --
1045       -----------------------------
1046
1047       --  LOCAL_NAME ::=
1048       --    DIRECT_NAME
1049       --  | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
1050       --  | library_unit_NAME
1051
1052       procedure Check_Arg_Is_Local_Name (Arg : Node_Id) is
1053          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1054
1055       begin
1056          Analyze (Argx);
1057
1058          if Nkind (Argx) not in N_Direct_Name
1059            and then (Nkind (Argx) /= N_Attribute_Reference
1060                       or else Present (Expressions (Argx))
1061                       or else Nkind (Prefix (Argx)) /= N_Identifier)
1062            and then (not Is_Entity_Name (Argx)
1063                       or else not Is_Compilation_Unit (Entity (Argx)))
1064          then
1065             Error_Pragma_Arg ("argument for pragma% must be local name", Argx);
1066          end if;
1067
1068          --  No further check required if not an entity name
1069
1070          if not Is_Entity_Name (Argx) then
1071             null;
1072
1073          else
1074             declare
1075                OK   : Boolean;
1076                Ent  : constant Entity_Id := Entity (Argx);
1077                Scop : constant Entity_Id := Scope (Ent);
1078             begin
1079                --  Case of a pragma applied to a compilation unit: pragma must
1080                --  occur immediately after the program unit in the compilation.
1081
1082                if Is_Compilation_Unit (Ent) then
1083                   declare
1084                      Decl : constant Node_Id := Unit_Declaration_Node (Ent);
1085
1086                   begin
1087                      --  Case of pragma placed immediately after spec
1088
1089                      if Parent (N) = Aux_Decls_Node (Parent (Decl)) then
1090                         OK := True;
1091
1092                      --  Case of pragma placed immediately after body
1093
1094                      elsif Nkind (Decl) = N_Subprogram_Declaration
1095                              and then Present (Corresponding_Body (Decl))
1096                      then
1097                         OK := Parent (N) =
1098                                 Aux_Decls_Node
1099                                   (Parent (Unit_Declaration_Node
1100                                              (Corresponding_Body (Decl))));
1101
1102                      --  All other cases are illegal
1103
1104                      else
1105                         OK := False;
1106                      end if;
1107                   end;
1108
1109                --  Special restricted placement rule from 10.2.1(11.8/2)
1110
1111                elsif Is_Generic_Formal (Ent)
1112                        and then Prag_Id = Pragma_Preelaborable_Initialization
1113                then
1114                   OK := List_Containing (N) =
1115                           Generic_Formal_Declarations
1116                             (Unit_Declaration_Node (Scop));
1117
1118                --  Default case, just check that the pragma occurs in the scope
1119                --  of the entity denoted by the name.
1120
1121                else
1122                   OK := Current_Scope = Scop;
1123                end if;
1124
1125                if not OK then
1126                   Error_Pragma_Arg
1127                     ("pragma% argument must be in same declarative part", Arg);
1128                end if;
1129             end;
1130          end if;
1131       end Check_Arg_Is_Local_Name;
1132
1133       ---------------------------------
1134       -- Check_Arg_Is_Locking_Policy --
1135       ---------------------------------
1136
1137       procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id) is
1138          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1139
1140       begin
1141          Check_Arg_Is_Identifier (Argx);
1142
1143          if not Is_Locking_Policy_Name (Chars (Argx)) then
1144             Error_Pragma_Arg ("& is not a valid locking policy name", Argx);
1145          end if;
1146       end Check_Arg_Is_Locking_Policy;
1147
1148       -------------------------
1149       -- Check_Arg_Is_One_Of --
1150       -------------------------
1151
1152       procedure Check_Arg_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
1153          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1154
1155       begin
1156          Check_Arg_Is_Identifier (Argx);
1157
1158          if Chars (Argx) /= N1 and then Chars (Argx) /= N2 then
1159             Error_Msg_Name_2 := N1;
1160             Error_Msg_Name_3 := N2;
1161             Error_Pragma_Arg ("argument for pragma% must be% or%", Argx);
1162          end if;
1163       end Check_Arg_Is_One_Of;
1164
1165       procedure Check_Arg_Is_One_Of
1166         (Arg        : Node_Id;
1167          N1, N2, N3 : Name_Id)
1168       is
1169          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1170
1171       begin
1172          Check_Arg_Is_Identifier (Argx);
1173
1174          if Chars (Argx) /= N1
1175            and then Chars (Argx) /= N2
1176            and then Chars (Argx) /= N3
1177          then
1178             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1179          end if;
1180       end Check_Arg_Is_One_Of;
1181
1182       procedure Check_Arg_Is_One_Of
1183         (Arg                : Node_Id;
1184          N1, N2, N3, N4     : Name_Id)
1185       is
1186          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1187
1188       begin
1189          Check_Arg_Is_Identifier (Argx);
1190
1191          if Chars (Argx) /= N1
1192            and then Chars (Argx) /= N2
1193            and then Chars (Argx) /= N3
1194            and then Chars (Argx) /= N4
1195          then
1196             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1197          end if;
1198       end Check_Arg_Is_One_Of;
1199
1200       procedure Check_Arg_Is_One_Of
1201         (Arg                : Node_Id;
1202          N1, N2, N3, N4, N5 : Name_Id)
1203       is
1204          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1205
1206       begin
1207          Check_Arg_Is_Identifier (Argx);
1208
1209          if Chars (Argx) /= N1
1210            and then Chars (Argx) /= N2
1211            and then Chars (Argx) /= N3
1212            and then Chars (Argx) /= N4
1213            and then Chars (Argx) /= N5
1214          then
1215             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1216          end if;
1217       end Check_Arg_Is_One_Of;
1218       ---------------------------------
1219       -- Check_Arg_Is_Queuing_Policy --
1220       ---------------------------------
1221
1222       procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id) is
1223          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1224
1225       begin
1226          Check_Arg_Is_Identifier (Argx);
1227
1228          if not Is_Queuing_Policy_Name (Chars (Argx)) then
1229             Error_Pragma_Arg ("& is not a valid queuing policy name", Argx);
1230          end if;
1231       end Check_Arg_Is_Queuing_Policy;
1232
1233       ------------------------------------
1234       -- Check_Arg_Is_Static_Expression --
1235       ------------------------------------
1236
1237       procedure Check_Arg_Is_Static_Expression
1238         (Arg : Node_Id;
1239          Typ : Entity_Id := Empty)
1240       is
1241       begin
1242          Check_Expr_Is_Static_Expression (Get_Pragma_Arg (Arg), Typ);
1243       end Check_Arg_Is_Static_Expression;
1244
1245       ------------------------------------------
1246       -- Check_Arg_Is_Task_Dispatching_Policy --
1247       ------------------------------------------
1248
1249       procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id) is
1250          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1251
1252       begin
1253          Check_Arg_Is_Identifier (Argx);
1254
1255          if not Is_Task_Dispatching_Policy_Name (Chars (Argx)) then
1256             Error_Pragma_Arg
1257               ("& is not a valid task dispatching policy name", Argx);
1258          end if;
1259       end Check_Arg_Is_Task_Dispatching_Policy;
1260
1261       ---------------------
1262       -- Check_Arg_Order --
1263       ---------------------
1264
1265       procedure Check_Arg_Order (Names : Name_List) is
1266          Arg : Node_Id;
1267
1268          Highest_So_Far : Natural := 0;
1269          --  Highest index in Names seen do far
1270
1271       begin
1272          Arg := Arg1;
1273          for J in 1 .. Arg_Count loop
1274             if Chars (Arg) /= No_Name then
1275                for K in Names'Range loop
1276                   if Chars (Arg) = Names (K) then
1277                      if K < Highest_So_Far then
1278                         Error_Msg_Name_1 := Pname;
1279                         Error_Msg_N
1280                           ("parameters out of order for pragma%", Arg);
1281                         Error_Msg_Name_1 := Names (K);
1282                         Error_Msg_Name_2 := Names (Highest_So_Far);
1283                         Error_Msg_N ("\% must appear before %", Arg);
1284                         raise Pragma_Exit;
1285
1286                      else
1287                         Highest_So_Far := K;
1288                      end if;
1289                   end if;
1290                end loop;
1291             end if;
1292
1293             Arg := Next (Arg);
1294          end loop;
1295       end Check_Arg_Order;
1296
1297       --------------------------------
1298       -- Check_At_Least_N_Arguments --
1299       --------------------------------
1300
1301       procedure Check_At_Least_N_Arguments (N : Nat) is
1302       begin
1303          if Arg_Count < N then
1304             Error_Pragma ("too few arguments for pragma%");
1305          end if;
1306       end Check_At_Least_N_Arguments;
1307
1308       -------------------------------
1309       -- Check_At_Most_N_Arguments --
1310       -------------------------------
1311
1312       procedure Check_At_Most_N_Arguments (N : Nat) is
1313          Arg : Node_Id;
1314       begin
1315          if Arg_Count > N then
1316             Arg := Arg1;
1317             for J in 1 .. N loop
1318                Next (Arg);
1319                Error_Pragma_Arg ("too many arguments for pragma%", Arg);
1320             end loop;
1321          end if;
1322       end Check_At_Most_N_Arguments;
1323
1324       ---------------------
1325       -- Check_Component --
1326       ---------------------
1327
1328       procedure Check_Component
1329         (Comp            : Node_Id;
1330          UU_Typ          : Entity_Id;
1331          In_Variant_Part : Boolean := False)
1332       is
1333          Comp_Id : constant Entity_Id := Defining_Identifier (Comp);
1334          Sindic  : constant Node_Id :=
1335                      Subtype_Indication (Component_Definition (Comp));
1336          Typ     : constant Entity_Id := Etype (Comp_Id);
1337
1338       begin
1339          --  Ada 2005 (AI-216): If a component subtype is subject to a per-
1340          --  object constraint, then the component type shall be an Unchecked_
1341          --  Union.
1342
1343          if Nkind (Sindic) = N_Subtype_Indication
1344            and then Has_Per_Object_Constraint (Comp_Id)
1345            and then not Is_Unchecked_Union (Etype (Subtype_Mark (Sindic)))
1346          then
1347             Error_Msg_N
1348               ("component subtype subject to per-object constraint " &
1349                "must be an Unchecked_Union", Comp);
1350
1351          --  Ada 2012 (AI05-0026): For an unchecked union type declared within
1352          --  the body of a generic unit, or within the body of any of its
1353          --  descendant library units, no part of the type of a component
1354          --  declared in a variant_part of the unchecked union type shall be of
1355          --  a formal private type or formal private extension declared within
1356          --  the formal part of the generic unit.
1357
1358          elsif Ada_Version >= Ada_2012
1359            and then In_Generic_Body (UU_Typ)
1360            and then In_Variant_Part
1361            and then Is_Private_Type (Typ)
1362            and then Is_Generic_Type (Typ)
1363          then
1364             Error_Msg_N
1365               ("component of Unchecked_Union cannot be of generic type", Comp);
1366
1367          elsif Needs_Finalization (Typ) then
1368             Error_Msg_N
1369               ("component of Unchecked_Union cannot be controlled", Comp);
1370
1371          elsif Has_Task (Typ) then
1372             Error_Msg_N
1373               ("component of Unchecked_Union cannot have tasks", Comp);
1374          end if;
1375       end Check_Component;
1376
1377       ----------------------------
1378       -- Check_Duplicate_Pragma --
1379       ----------------------------
1380
1381       procedure Check_Duplicate_Pragma (E : Entity_Id) is
1382          P : Node_Id;
1383
1384       begin
1385          --  Nothing to do if this pragma comes from an aspect specification,
1386          --  since we could not be duplicating a pragma, and we dealt with the
1387          --  case of duplicated aspects in Analyze_Aspect_Specifications.
1388
1389          if From_Aspect_Specification (N) then
1390             return;
1391          end if;
1392
1393          --  Otherwise current pragma may duplicate previous pragma or a
1394          --  previously given aspect specification for the same pragma.
1395
1396          P := Get_Rep_Item_For_Entity (E, Pragma_Name (N));
1397
1398          if Present (P) then
1399             Error_Msg_Name_1 := Pragma_Name (N);
1400             Error_Msg_Sloc := Sloc (P);
1401
1402             if Nkind (P) = N_Aspect_Specification
1403               or else From_Aspect_Specification (P)
1404             then
1405                Error_Msg_NE ("aspect% for & previously given#", N, E);
1406             else
1407                Error_Msg_NE ("pragma% for & duplicates pragma#", N, E);
1408             end if;
1409
1410             raise Pragma_Exit;
1411          end if;
1412       end Check_Duplicate_Pragma;
1413
1414       ----------------------------------
1415       -- Check_Duplicated_Export_Name --
1416       ----------------------------------
1417
1418       procedure Check_Duplicated_Export_Name (Nam : Node_Id) is
1419          String_Val : constant String_Id := Strval (Nam);
1420
1421       begin
1422          --  We are only interested in the export case, and in the case of
1423          --  generics, it is the instance, not the template, that is the
1424          --  problem (the template will generate a warning in any case).
1425
1426          if not Inside_A_Generic
1427            and then (Prag_Id = Pragma_Export
1428                        or else
1429                      Prag_Id = Pragma_Export_Procedure
1430                        or else
1431                      Prag_Id = Pragma_Export_Valued_Procedure
1432                        or else
1433                      Prag_Id = Pragma_Export_Function)
1434          then
1435             for J in Externals.First .. Externals.Last loop
1436                if String_Equal (String_Val, Strval (Externals.Table (J))) then
1437                   Error_Msg_Sloc := Sloc (Externals.Table (J));
1438                   Error_Msg_N ("external name duplicates name given#", Nam);
1439                   exit;
1440                end if;
1441             end loop;
1442
1443             Externals.Append (Nam);
1444          end if;
1445       end Check_Duplicated_Export_Name;
1446
1447       -------------------------------------
1448       -- Check_Expr_Is_Static_Expression --
1449       -------------------------------------
1450
1451       procedure Check_Expr_Is_Static_Expression
1452         (Expr : Node_Id;
1453          Typ  : Entity_Id := Empty)
1454       is
1455       begin
1456          if Present (Typ) then
1457             Analyze_And_Resolve (Expr, Typ);
1458          else
1459             Analyze_And_Resolve (Expr);
1460          end if;
1461
1462          if Is_OK_Static_Expression (Expr) then
1463             return;
1464
1465          elsif Etype (Expr) = Any_Type then
1466             raise Pragma_Exit;
1467
1468          --  An interesting special case, if we have a string literal and we
1469          --  are in Ada 83 mode, then we allow it even though it will not be
1470          --  flagged as static. This allows the use of Ada 95 pragmas like
1471          --  Import in Ada 83 mode. They will of course be flagged with
1472          --  warnings as usual, but will not cause errors.
1473
1474          elsif Ada_Version = Ada_83
1475            and then Nkind (Expr) = N_String_Literal
1476          then
1477             return;
1478
1479          --  Static expression that raises Constraint_Error. This has already
1480          --  been flagged, so just exit from pragma processing.
1481
1482          elsif Is_Static_Expression (Expr) then
1483             raise Pragma_Exit;
1484
1485          --  Finally, we have a real error
1486
1487          else
1488             Error_Msg_Name_1 := Pname;
1489
1490             declare
1491                Msg : String :=
1492                        "argument for pragma% must be a static expression!";
1493             begin
1494                Fix_Error (Msg);
1495                Flag_Non_Static_Expr (Msg, Expr);
1496             end;
1497
1498             raise Pragma_Exit;
1499          end if;
1500       end Check_Expr_Is_Static_Expression;
1501
1502       -------------------------
1503       -- Check_First_Subtype --
1504       -------------------------
1505
1506       procedure Check_First_Subtype (Arg : Node_Id) is
1507          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1508          Ent  : constant Entity_Id := Entity (Argx);
1509
1510       begin
1511          if Is_First_Subtype (Ent) then
1512             null;
1513
1514          elsif Is_Type (Ent) then
1515             Error_Pragma_Arg
1516               ("pragma% cannot apply to subtype", Argx);
1517
1518          elsif Is_Object (Ent) then
1519             Error_Pragma_Arg
1520               ("pragma% cannot apply to object, requires a type", Argx);
1521
1522          else
1523             Error_Pragma_Arg
1524               ("pragma% cannot apply to&, requires a type", Argx);
1525          end if;
1526       end Check_First_Subtype;
1527
1528       ----------------------
1529       -- Check_Identifier --
1530       ----------------------
1531
1532       procedure Check_Identifier (Arg : Node_Id; Id : Name_Id) is
1533       begin
1534          if Present (Arg)
1535            and then Nkind (Arg) = N_Pragma_Argument_Association
1536          then
1537             if Chars (Arg) = No_Name or else Chars (Arg) /= Id then
1538                Error_Msg_Name_1 := Pname;
1539                Error_Msg_Name_2 := Id;
1540                Error_Msg_N ("pragma% argument expects identifier%", Arg);
1541                raise Pragma_Exit;
1542             end if;
1543          end if;
1544       end Check_Identifier;
1545
1546       --------------------------------
1547       -- Check_Identifier_Is_One_Of --
1548       --------------------------------
1549
1550       procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
1551       begin
1552          if Present (Arg)
1553            and then Nkind (Arg) = N_Pragma_Argument_Association
1554          then
1555             if Chars (Arg) = No_Name then
1556                Error_Msg_Name_1 := Pname;
1557                Error_Msg_N ("pragma% argument expects an identifier", Arg);
1558                raise Pragma_Exit;
1559
1560             elsif Chars (Arg) /= N1
1561               and then Chars (Arg) /= N2
1562             then
1563                Error_Msg_Name_1 := Pname;
1564                Error_Msg_N ("invalid identifier for pragma% argument", Arg);
1565                raise Pragma_Exit;
1566             end if;
1567          end if;
1568       end Check_Identifier_Is_One_Of;
1569
1570       ---------------------------
1571       -- Check_In_Main_Program --
1572       ---------------------------
1573
1574       procedure Check_In_Main_Program is
1575          P : constant Node_Id := Parent (N);
1576
1577       begin
1578          --  Must be at in subprogram body
1579
1580          if Nkind (P) /= N_Subprogram_Body then
1581             Error_Pragma ("% pragma allowed only in subprogram");
1582
1583          --  Otherwise warn if obviously not main program
1584
1585          elsif Present (Parameter_Specifications (Specification (P)))
1586            or else not Is_Compilation_Unit (Defining_Entity (P))
1587          then
1588             Error_Msg_Name_1 := Pname;
1589             Error_Msg_N
1590               ("?pragma% is only effective in main program", N);
1591          end if;
1592       end Check_In_Main_Program;
1593
1594       ---------------------------------------
1595       -- Check_Interrupt_Or_Attach_Handler --
1596       ---------------------------------------
1597
1598       procedure Check_Interrupt_Or_Attach_Handler is
1599          Arg1_X : constant Node_Id := Get_Pragma_Arg (Arg1);
1600          Handler_Proc, Proc_Scope : Entity_Id;
1601
1602       begin
1603          Analyze (Arg1_X);
1604
1605          if Prag_Id = Pragma_Interrupt_Handler then
1606             Check_Restriction (No_Dynamic_Attachment, N);
1607          end if;
1608
1609          Handler_Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
1610          Proc_Scope := Scope (Handler_Proc);
1611
1612          --  On AAMP only, a pragma Interrupt_Handler is supported for
1613          --  nonprotected parameterless procedures.
1614
1615          if not AAMP_On_Target
1616            or else Prag_Id = Pragma_Attach_Handler
1617          then
1618             if Ekind (Proc_Scope) /= E_Protected_Type then
1619                Error_Pragma_Arg
1620                  ("argument of pragma% must be protected procedure", Arg1);
1621             end if;
1622
1623             if Parent (N) /= Protected_Definition (Parent (Proc_Scope)) then
1624                Error_Pragma ("pragma% must be in protected definition");
1625             end if;
1626          end if;
1627
1628          if not Is_Library_Level_Entity (Proc_Scope)
1629            or else (AAMP_On_Target
1630                      and then not Is_Library_Level_Entity (Handler_Proc))
1631          then
1632             Error_Pragma_Arg
1633               ("argument for pragma% must be library level entity", Arg1);
1634          end if;
1635
1636          --  AI05-0033: A pragma cannot appear within a generic body, because
1637          --  instance can be in a nested scope. The check that protected type
1638          --  is itself a library-level declaration is done elsewhere.
1639
1640          --  Note: we omit this check in Codepeer mode to properly handle code
1641          --  prior to AI-0033 (pragmas don't matter to codepeer in any case).
1642
1643          if Inside_A_Generic then
1644             if Ekind (Scope (Current_Scope)) = E_Generic_Package
1645               and then In_Package_Body (Scope (Current_Scope))
1646               and then not CodePeer_Mode
1647             then
1648                Error_Pragma ("pragma% cannot be used inside a generic");
1649             end if;
1650          end if;
1651       end Check_Interrupt_Or_Attach_Handler;
1652
1653       -------------------------------------------
1654       -- Check_Is_In_Decl_Part_Or_Package_Spec --
1655       -------------------------------------------
1656
1657       procedure Check_Is_In_Decl_Part_Or_Package_Spec is
1658          P : Node_Id;
1659
1660       begin
1661          P := Parent (N);
1662          loop
1663             if No (P) then
1664                exit;
1665
1666             elsif Nkind (P) = N_Handled_Sequence_Of_Statements then
1667                exit;
1668
1669             elsif Nkind_In (P, N_Package_Specification,
1670                                N_Block_Statement)
1671             then
1672                return;
1673
1674             --  Note: the following tests seem a little peculiar, because
1675             --  they test for bodies, but if we were in the statement part
1676             --  of the body, we would already have hit the handled statement
1677             --  sequence, so the only way we get here is by being in the
1678             --  declarative part of the body.
1679
1680             elsif Nkind_In (P, N_Subprogram_Body,
1681                                N_Package_Body,
1682                                N_Task_Body,
1683                                N_Entry_Body)
1684             then
1685                return;
1686             end if;
1687
1688             P := Parent (P);
1689          end loop;
1690
1691          Error_Pragma ("pragma% is not in declarative part or package spec");
1692       end Check_Is_In_Decl_Part_Or_Package_Spec;
1693
1694       -------------------------
1695       -- Check_No_Identifier --
1696       -------------------------
1697
1698       procedure Check_No_Identifier (Arg : Node_Id) is
1699       begin
1700          if Nkind (Arg) = N_Pragma_Argument_Association
1701            and then Chars (Arg) /= No_Name
1702          then
1703             Error_Pragma_Arg_Ident
1704               ("pragma% does not permit identifier& here", Arg);
1705          end if;
1706       end Check_No_Identifier;
1707
1708       --------------------------
1709       -- Check_No_Identifiers --
1710       --------------------------
1711
1712       procedure Check_No_Identifiers is
1713          Arg_Node : Node_Id;
1714       begin
1715          if Arg_Count > 0 then
1716             Arg_Node := Arg1;
1717             while Present (Arg_Node) loop
1718                Check_No_Identifier (Arg_Node);
1719                Next (Arg_Node);
1720             end loop;
1721          end if;
1722       end Check_No_Identifiers;
1723
1724       ------------------------
1725       -- Check_No_Link_Name --
1726       ------------------------
1727
1728       procedure Check_No_Link_Name is
1729       begin
1730          if Present (Arg3)
1731            and then Chars (Arg3) = Name_Link_Name
1732          then
1733             Arg4 := Arg3;
1734          end if;
1735
1736          if Present (Arg4) then
1737             Error_Pragma_Arg
1738               ("Link_Name argument not allowed for Import Intrinsic", Arg4);
1739          end if;
1740       end Check_No_Link_Name;
1741
1742       -------------------------------
1743       -- Check_Optional_Identifier --
1744       -------------------------------
1745
1746       procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id) is
1747       begin
1748          if Present (Arg)
1749            and then Nkind (Arg) = N_Pragma_Argument_Association
1750            and then Chars (Arg) /= No_Name
1751          then
1752             if Chars (Arg) /= Id then
1753                Error_Msg_Name_1 := Pname;
1754                Error_Msg_Name_2 := Id;
1755                Error_Msg_N ("pragma% argument expects identifier%", Arg);
1756                raise Pragma_Exit;
1757             end if;
1758          end if;
1759       end Check_Optional_Identifier;
1760
1761       procedure Check_Optional_Identifier (Arg : Node_Id; Id : String) is
1762       begin
1763          Name_Buffer (1 .. Id'Length) := Id;
1764          Name_Len := Id'Length;
1765          Check_Optional_Identifier (Arg, Name_Find);
1766       end Check_Optional_Identifier;
1767
1768       --------------------------------------
1769       -- Check_Precondition_Postcondition --
1770       --------------------------------------
1771
1772       procedure Check_Precondition_Postcondition (In_Body : out Boolean) is
1773          P  : Node_Id;
1774          PO : Node_Id;
1775
1776          procedure Chain_PPC (PO : Node_Id);
1777          --  If PO is an entry or a [generic] subprogram declaration node, then
1778          --  the precondition/postcondition applies to this subprogram and the
1779          --  processing for the pragma is completed. Otherwise the pragma is
1780          --  misplaced.
1781
1782          ---------------
1783          -- Chain_PPC --
1784          ---------------
1785
1786          procedure Chain_PPC (PO : Node_Id) is
1787             S   : Entity_Id;
1788             P   : Node_Id;
1789
1790          begin
1791             if Nkind (PO) = N_Abstract_Subprogram_Declaration then
1792                if not From_Aspect_Specification (N) then
1793                   Error_Pragma
1794                     ("pragma% cannot be applied to abstract subprogram");
1795
1796                elsif Class_Present (N) then
1797                   null;
1798
1799                else
1800                   Error_Pragma
1801                     ("aspect % requires ''Class for abstract subprogram");
1802                end if;
1803
1804             --  AI05-0230: The same restriction applies to null procedures. For
1805             --  compatibility with earlier uses of the Ada pragma, apply this
1806             --  rule only to aspect specifications.
1807
1808             --  The above discrpency needs documentation. Robert is dubious
1809             --  about whether it is a good idea ???
1810
1811             elsif Nkind (PO) = N_Subprogram_Declaration
1812               and then Nkind (Specification (PO)) = N_Procedure_Specification
1813               and then Null_Present (Specification (PO))
1814               and then From_Aspect_Specification (N)
1815               and then not Class_Present (N)
1816             then
1817                Error_Pragma
1818                  ("aspect % requires ''Class for null procedure");
1819
1820             elsif not Nkind_In (PO, N_Subprogram_Declaration,
1821                                     N_Generic_Subprogram_Declaration,
1822                                     N_Entry_Declaration)
1823             then
1824                Pragma_Misplaced;
1825             end if;
1826
1827             --  Here if we have [generic] subprogram or entry declaration
1828
1829             if Nkind (PO) = N_Entry_Declaration then
1830                S := Defining_Entity (PO);
1831             else
1832                S := Defining_Unit_Name (Specification (PO));
1833             end if;
1834
1835             --  Make sure we do not have the case of a precondition pragma when
1836             --  the Pre'Class aspect is present.
1837
1838             --  We do this by looking at pragmas already chained to the entity
1839             --  since the aspect derived pragma will be put on this list first.
1840
1841             if Pragma_Name (N) = Name_Precondition then
1842                if not From_Aspect_Specification (N) then
1843                   P := Spec_PPC_List (Contract (S));
1844                   while Present (P) loop
1845                      if Pragma_Name (P) = Name_Precondition
1846                        and then From_Aspect_Specification (P)
1847                        and then Class_Present (P)
1848                      then
1849                         Error_Msg_Sloc := Sloc (P);
1850                         Error_Pragma
1851                           ("pragma% not allowed, `Pre''Class` aspect given#");
1852                      end if;
1853
1854                      P := Next_Pragma (P);
1855                   end loop;
1856                end if;
1857             end if;
1858
1859             --  Similarly check for Pre with inherited Pre'Class. Note that
1860             --  we cover the aspect case as well here.
1861
1862             if Pragma_Name (N) = Name_Precondition
1863               and then not Class_Present (N)
1864             then
1865                declare
1866                   Inherited : constant Subprogram_List :=
1867                                 Inherited_Subprograms (S);
1868                   P         : Node_Id;
1869
1870                begin
1871                   for J in Inherited'Range loop
1872                      P := Spec_PPC_List (Contract (Inherited (J)));
1873                      while Present (P) loop
1874                         if Pragma_Name (P) = Name_Precondition
1875                           and then Class_Present (P)
1876                         then
1877                            Error_Msg_Sloc := Sloc (P);
1878                            Error_Pragma
1879                              ("pragma% not allowed, `Pre''Class` "
1880                               & "aspect inherited from#");
1881                         end if;
1882
1883                         P := Next_Pragma (P);
1884                      end loop;
1885                   end loop;
1886                end;
1887             end if;
1888
1889             --  Note: we do not analyze the pragma at this point. Instead we
1890             --  delay this analysis until the end of the declarative part in
1891             --  which the pragma appears. This implements the required delay
1892             --  in this analysis, allowing forward references. The analysis
1893             --  happens at the end of Analyze_Declarations.
1894
1895             --  Chain spec PPC pragma to list for subprogram
1896
1897             Set_Next_Pragma (N, Spec_PPC_List (Contract (S)));
1898             Set_Spec_PPC_List (Contract (S), N);
1899
1900             --  Return indicating spec case
1901
1902             In_Body := False;
1903             return;
1904          end Chain_PPC;
1905
1906       --  Start of processing for Check_Precondition_Postcondition
1907
1908       begin
1909          if not Is_List_Member (N) then
1910             Pragma_Misplaced;
1911          end if;
1912
1913          --  Preanalyze message argument if present. Visibility in this
1914          --  argument is established at the point of pragma occurrence.
1915
1916          if Arg_Count = 2 then
1917             Check_Optional_Identifier (Arg2, Name_Message);
1918             Preanalyze_Spec_Expression
1919               (Get_Pragma_Arg (Arg2), Standard_String);
1920          end if;
1921
1922          --  Record if pragma is disabled
1923
1924          if Check_Enabled (Pname) then
1925             Set_SCO_Pragma_Enabled (Loc);
1926          end if;
1927
1928          --  If we are within an inlined body, the legality of the pragma
1929          --  has been checked already.
1930
1931          if In_Inlined_Body then
1932             In_Body := True;
1933             return;
1934          end if;
1935
1936          --  Search prior declarations
1937
1938          P := N;
1939          while Present (Prev (P)) loop
1940             P := Prev (P);
1941
1942             --  If the previous node is a generic subprogram, do not go to to
1943             --  the original node, which is the unanalyzed tree: we need to
1944             --  attach the pre/postconditions to the analyzed version at this
1945             --  point. They get propagated to the original tree when analyzing
1946             --  the corresponding body.
1947
1948             if Nkind (P) not in N_Generic_Declaration then
1949                PO := Original_Node (P);
1950             else
1951                PO := P;
1952             end if;
1953
1954             --  Skip past prior pragma
1955
1956             if Nkind (PO) = N_Pragma then
1957                null;
1958
1959             --  Skip stuff not coming from source
1960
1961             elsif not Comes_From_Source (PO) then
1962
1963                --  The condition may apply to a subprogram instantiation
1964
1965                if Nkind (PO) = N_Subprogram_Declaration
1966                  and then Present (Generic_Parent (Specification (PO)))
1967                then
1968                   Chain_PPC (PO);
1969                   return;
1970
1971                elsif Nkind (PO) = N_Subprogram_Declaration
1972                  and then In_Instance
1973                then
1974                   Chain_PPC (PO);
1975                   return;
1976
1977                --  For all other cases of non source code, do nothing
1978
1979                else
1980                   null;
1981                end if;
1982
1983             --  Only remaining possibility is subprogram declaration
1984
1985             else
1986                Chain_PPC (PO);
1987                return;
1988             end if;
1989          end loop;
1990
1991          --  If we fall through loop, pragma is at start of list, so see if it
1992          --  is at the start of declarations of a subprogram body.
1993
1994          if Nkind (Parent (N)) = N_Subprogram_Body
1995            and then List_Containing (N) = Declarations (Parent (N))
1996          then
1997             if Operating_Mode /= Generate_Code
1998               or else Inside_A_Generic
1999             then
2000                --  Analyze pragma expression for correctness and for ASIS use
2001
2002                Preanalyze_Spec_Expression
2003                  (Get_Pragma_Arg (Arg1), Standard_Boolean);
2004
2005                --  In ASIS mode, for a pragma generated from a source aspect,
2006                --  also analyze the original aspect expression.
2007
2008                if ASIS_Mode
2009                  and then Present (Corresponding_Aspect (N))
2010                then
2011                   Preanalyze_Spec_Expression
2012                     (Expression (Corresponding_Aspect (N)), Standard_Boolean);
2013                end if;
2014             end if;
2015
2016             In_Body := True;
2017             return;
2018
2019          --  See if it is in the pragmas after a library level subprogram
2020
2021          elsif Nkind (Parent (N)) = N_Compilation_Unit_Aux then
2022
2023             --  In formal verification mode, analyze pragma expression for
2024             --  correctness, as it is not expanded later.
2025
2026             if Alfa_Mode then
2027                Analyze_PPC_In_Decl_Part
2028                  (N, Defining_Entity (Unit (Parent (Parent (N)))));
2029             end if;
2030
2031             Chain_PPC (Unit (Parent (Parent (N))));
2032             return;
2033          end if;
2034
2035          --  If we fall through, pragma was misplaced
2036
2037          Pragma_Misplaced;
2038       end Check_Precondition_Postcondition;
2039
2040       -----------------------------
2041       -- Check_Static_Constraint --
2042       -----------------------------
2043
2044       --  Note: for convenience in writing this procedure, in addition to
2045       --  the officially (i.e. by spec) allowed argument which is always a
2046       --  constraint, it also allows ranges and discriminant associations.
2047       --  Above is not clear ???
2048
2049       procedure Check_Static_Constraint (Constr : Node_Id) is
2050
2051          procedure Require_Static (E : Node_Id);
2052          --  Require given expression to be static expression
2053
2054          --------------------
2055          -- Require_Static --
2056          --------------------
2057
2058          procedure Require_Static (E : Node_Id) is
2059          begin
2060             if not Is_OK_Static_Expression (E) then
2061                Flag_Non_Static_Expr
2062                  ("non-static constraint not allowed in Unchecked_Union!", E);
2063                raise Pragma_Exit;
2064             end if;
2065          end Require_Static;
2066
2067       --  Start of processing for Check_Static_Constraint
2068
2069       begin
2070          case Nkind (Constr) is
2071             when N_Discriminant_Association =>
2072                Require_Static (Expression (Constr));
2073
2074             when N_Range =>
2075                Require_Static (Low_Bound (Constr));
2076                Require_Static (High_Bound (Constr));
2077
2078             when N_Attribute_Reference =>
2079                Require_Static (Type_Low_Bound  (Etype (Prefix (Constr))));
2080                Require_Static (Type_High_Bound (Etype (Prefix (Constr))));
2081
2082             when N_Range_Constraint =>
2083                Check_Static_Constraint (Range_Expression (Constr));
2084
2085             when N_Index_Or_Discriminant_Constraint =>
2086                declare
2087                   IDC : Entity_Id;
2088                begin
2089                   IDC := First (Constraints (Constr));
2090                   while Present (IDC) loop
2091                      Check_Static_Constraint (IDC);
2092                      Next (IDC);
2093                   end loop;
2094                end;
2095
2096             when others =>
2097                null;
2098          end case;
2099       end Check_Static_Constraint;
2100
2101       ---------------------
2102       -- Check_Test_Case --
2103       ---------------------
2104
2105       procedure Check_Test_Case is
2106          P  : Node_Id;
2107          PO : Node_Id;
2108
2109          procedure Chain_TC (PO : Node_Id);
2110          --  If PO is a [generic] subprogram declaration node, then the
2111          --  test-case applies to this subprogram and the processing for the
2112          --  pragma is completed. Otherwise the pragma is misplaced.
2113
2114          --------------
2115          -- Chain_TC --
2116          --------------
2117
2118          procedure Chain_TC (PO : Node_Id) is
2119             S   : Entity_Id;
2120
2121          begin
2122             if Nkind (PO) = N_Abstract_Subprogram_Declaration then
2123                if From_Aspect_Specification (N) then
2124                   Error_Pragma
2125                     ("aspect% cannot be applied to abstract subprogram");
2126                else
2127                   Error_Pragma
2128                     ("pragma% cannot be applied to abstract subprogram");
2129                end if;
2130
2131             elsif Nkind (PO) = N_Entry_Declaration then
2132                if From_Aspect_Specification (N) then
2133                   Error_Pragma ("aspect% cannot be applied to entry");
2134                else
2135                   Error_Pragma ("pragma% cannot be applied to entry");
2136                end if;
2137
2138             elsif not Nkind_In (PO, N_Subprogram_Declaration,
2139                                     N_Generic_Subprogram_Declaration)
2140             then
2141                Pragma_Misplaced;
2142             end if;
2143
2144             --  Here if we have [generic] subprogram declaration
2145
2146             S := Defining_Unit_Name (Specification (PO));
2147
2148             --  Note: we do not analyze the pragma at this point. Instead we
2149             --  delay this analysis until the end of the declarative part in
2150             --  which the pragma appears. This implements the required delay
2151             --  in this analysis, allowing forward references. The analysis
2152             --  happens at the end of Analyze_Declarations.
2153
2154             --  There should not be another test case with the same name
2155             --  associated to this subprogram.
2156
2157             declare
2158                Name : constant String_Id := Get_Name_From_Test_Case_Pragma (N);
2159                TC   : Node_Id;
2160
2161             begin
2162                TC := Spec_TC_List (Contract (S));
2163                while Present (TC) loop
2164
2165                   if String_Equal
2166                     (Name, Get_Name_From_Test_Case_Pragma (TC))
2167                   then
2168                      Error_Msg_Sloc := Sloc (TC);
2169
2170                      if From_Aspect_Specification (N) then
2171                         Error_Pragma ("name for aspect% is already used#");
2172                      else
2173                         Error_Pragma ("name for pragma% is already used#");
2174                      end if;
2175                   end if;
2176
2177                   TC := Next_Pragma (TC);
2178                end loop;
2179             end;
2180
2181             --  Chain spec TC pragma to list for subprogram
2182
2183             Set_Next_Pragma (N, Spec_TC_List (Contract (S)));
2184             Set_Spec_TC_List (Contract (S), N);
2185          end Chain_TC;
2186
2187       --  Start of processing for Check_Test_Case
2188
2189       begin
2190          if not Is_List_Member (N) then
2191             Pragma_Misplaced;
2192          end if;
2193
2194          --  Test cases should only appear in package spec unit
2195
2196          if Get_Source_Unit (N) = No_Unit
2197            or else not Nkind_In (Sinfo.Unit (Cunit (Get_Source_Unit (N))),
2198                                  N_Package_Declaration,
2199                                  N_Generic_Package_Declaration)
2200          then
2201             Pragma_Misplaced;
2202          end if;
2203
2204          --  Search prior declarations
2205
2206          P := N;
2207          while Present (Prev (P)) loop
2208             P := Prev (P);
2209
2210             --  If the previous node is a generic subprogram, do not go to to
2211             --  the original node, which is the unanalyzed tree: we need to
2212             --  attach the test-case to the analyzed version at this point.
2213             --  They get propagated to the original tree when analyzing the
2214             --  corresponding body.
2215
2216             if Nkind (P) not in N_Generic_Declaration then
2217                PO := Original_Node (P);
2218             else
2219                PO := P;
2220             end if;
2221
2222             --  Skip past prior pragma
2223
2224             if Nkind (PO) = N_Pragma then
2225                null;
2226
2227             --  Skip stuff not coming from source
2228
2229             elsif not Comes_From_Source (PO) then
2230                null;
2231
2232             --  Only remaining possibility is subprogram declaration. First
2233             --  check that it is declared directly in a package declaration.
2234             --  This may be either the package declaration for the current unit
2235             --  being defined or a local package declaration.
2236
2237             elsif not Present (Parent (Parent (PO)))
2238               or else not Present (Parent (Parent (Parent (PO))))
2239               or else not Nkind_In (Parent (Parent (PO)),
2240                                     N_Package_Declaration,
2241                                     N_Generic_Package_Declaration)
2242             then
2243                Pragma_Misplaced;
2244
2245             else
2246                Chain_TC (PO);
2247                return;
2248             end if;
2249          end loop;
2250
2251          --  If we fall through, pragma was misplaced
2252
2253          Pragma_Misplaced;
2254       end Check_Test_Case;
2255
2256       --------------------------------------
2257       -- Check_Valid_Configuration_Pragma --
2258       --------------------------------------
2259
2260       --  A configuration pragma must appear in the context clause of a
2261       --  compilation unit, and only other pragmas may precede it. Note that
2262       --  the test also allows use in a configuration pragma file.
2263
2264       procedure Check_Valid_Configuration_Pragma is
2265       begin
2266          if not Is_Configuration_Pragma then
2267             Error_Pragma ("incorrect placement for configuration pragma%");
2268          end if;
2269       end Check_Valid_Configuration_Pragma;
2270
2271       -------------------------------------
2272       -- Check_Valid_Library_Unit_Pragma --
2273       -------------------------------------
2274
2275       procedure Check_Valid_Library_Unit_Pragma is
2276          Plist       : List_Id;
2277          Parent_Node : Node_Id;
2278          Unit_Name   : Entity_Id;
2279          Unit_Kind   : Node_Kind;
2280          Unit_Node   : Node_Id;
2281          Sindex      : Source_File_Index;
2282
2283       begin
2284          if not Is_List_Member (N) then
2285             Pragma_Misplaced;
2286
2287          else
2288             Plist := List_Containing (N);
2289             Parent_Node := Parent (Plist);
2290
2291             if Parent_Node = Empty then
2292                Pragma_Misplaced;
2293
2294             --  Case of pragma appearing after a compilation unit. In this case
2295             --  it must have an argument with the corresponding name and must
2296             --  be part of the following pragmas of its parent.
2297
2298             elsif Nkind (Parent_Node) = N_Compilation_Unit_Aux then
2299                if Plist /= Pragmas_After (Parent_Node) then
2300                   Pragma_Misplaced;
2301
2302                elsif Arg_Count = 0 then
2303                   Error_Pragma
2304                     ("argument required if outside compilation unit");
2305
2306                else
2307                   Check_No_Identifiers;
2308                   Check_Arg_Count (1);
2309                   Unit_Node := Unit (Parent (Parent_Node));
2310                   Unit_Kind := Nkind (Unit_Node);
2311
2312                   Analyze (Get_Pragma_Arg (Arg1));
2313
2314                   if Unit_Kind = N_Generic_Subprogram_Declaration
2315                     or else Unit_Kind = N_Subprogram_Declaration
2316                   then
2317                      Unit_Name := Defining_Entity (Unit_Node);
2318
2319                   elsif Unit_Kind in N_Generic_Instantiation then
2320                      Unit_Name := Defining_Entity (Unit_Node);
2321
2322                   else
2323                      Unit_Name := Cunit_Entity (Current_Sem_Unit);
2324                   end if;
2325
2326                   if Chars (Unit_Name) /=
2327                      Chars (Entity (Get_Pragma_Arg (Arg1)))
2328                   then
2329                      Error_Pragma_Arg
2330                        ("pragma% argument is not current unit name", Arg1);
2331                   end if;
2332
2333                   if Ekind (Unit_Name) = E_Package
2334                     and then Present (Renamed_Entity (Unit_Name))
2335                   then
2336                      Error_Pragma ("pragma% not allowed for renamed package");
2337                   end if;
2338                end if;
2339
2340             --  Pragma appears other than after a compilation unit
2341
2342             else
2343                --  Here we check for the generic instantiation case and also
2344                --  for the case of processing a generic formal package. We
2345                --  detect these cases by noting that the Sloc on the node
2346                --  does not belong to the current compilation unit.
2347
2348                Sindex := Source_Index (Current_Sem_Unit);
2349
2350                if Loc not in Source_First (Sindex) .. Source_Last (Sindex) then
2351                   Rewrite (N, Make_Null_Statement (Loc));
2352                   return;
2353
2354                --  If before first declaration, the pragma applies to the
2355                --  enclosing unit, and the name if present must be this name.
2356
2357                elsif Is_Before_First_Decl (N, Plist) then
2358                   Unit_Node := Unit_Declaration_Node (Current_Scope);
2359                   Unit_Kind := Nkind (Unit_Node);
2360
2361                   if Nkind (Parent (Unit_Node)) /= N_Compilation_Unit then
2362                      Pragma_Misplaced;
2363
2364                   elsif Unit_Kind = N_Subprogram_Body
2365                     and then not Acts_As_Spec (Unit_Node)
2366                   then
2367                      Pragma_Misplaced;
2368
2369                   elsif Nkind (Parent_Node) = N_Package_Body then
2370                      Pragma_Misplaced;
2371
2372                   elsif Nkind (Parent_Node) = N_Package_Specification
2373                     and then Plist = Private_Declarations (Parent_Node)
2374                   then
2375                      Pragma_Misplaced;
2376
2377                   elsif (Nkind (Parent_Node) = N_Generic_Package_Declaration
2378                            or else Nkind (Parent_Node) =
2379                                              N_Generic_Subprogram_Declaration)
2380                     and then Plist = Generic_Formal_Declarations (Parent_Node)
2381                   then
2382                      Pragma_Misplaced;
2383
2384                   elsif Arg_Count > 0 then
2385                      Analyze (Get_Pragma_Arg (Arg1));
2386
2387                      if Entity (Get_Pragma_Arg (Arg1)) /= Current_Scope then
2388                         Error_Pragma_Arg
2389                           ("name in pragma% must be enclosing unit", Arg1);
2390                      end if;
2391
2392                   --  It is legal to have no argument in this context
2393
2394                   else
2395                      return;
2396                   end if;
2397
2398                --  Error if not before first declaration. This is because a
2399                --  library unit pragma argument must be the name of a library
2400                --  unit (RM 10.1.5(7)), but the only names permitted in this
2401                --  context are (RM 10.1.5(6)) names of subprogram declarations,
2402                --  generic subprogram declarations or generic instantiations.
2403
2404                else
2405                   Error_Pragma
2406                     ("pragma% misplaced, must be before first declaration");
2407                end if;
2408             end if;
2409          end if;
2410       end Check_Valid_Library_Unit_Pragma;
2411
2412       -------------------
2413       -- Check_Variant --
2414       -------------------
2415
2416       procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id) is
2417          Clist : constant Node_Id := Component_List (Variant);
2418          Comp  : Node_Id;
2419
2420       begin
2421          if not Is_Non_Empty_List (Component_Items (Clist)) then
2422             Error_Msg_N
2423               ("Unchecked_Union may not have empty component list",
2424                Variant);
2425             return;
2426          end if;
2427
2428          Comp := First (Component_Items (Clist));
2429          while Present (Comp) loop
2430             Check_Component (Comp, UU_Typ, In_Variant_Part => True);
2431             Next (Comp);
2432          end loop;
2433       end Check_Variant;
2434
2435       ------------------
2436       -- Error_Pragma --
2437       ------------------
2438
2439       procedure Error_Pragma (Msg : String) is
2440          MsgF : String := Msg;
2441       begin
2442          Error_Msg_Name_1 := Pname;
2443          Fix_Error (MsgF);
2444          Error_Msg_N (MsgF, N);
2445          raise Pragma_Exit;
2446       end Error_Pragma;
2447
2448       ----------------------
2449       -- Error_Pragma_Arg --
2450       ----------------------
2451
2452       procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id) is
2453          MsgF : String := Msg;
2454       begin
2455          Error_Msg_Name_1 := Pname;
2456          Fix_Error (MsgF);
2457          Error_Msg_N (MsgF, Get_Pragma_Arg (Arg));
2458          raise Pragma_Exit;
2459       end Error_Pragma_Arg;
2460
2461       procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id) is
2462          MsgF : String := Msg1;
2463       begin
2464          Error_Msg_Name_1 := Pname;
2465          Fix_Error (MsgF);
2466          Error_Msg_N (MsgF, Get_Pragma_Arg (Arg));
2467          Error_Pragma_Arg (Msg2, Arg);
2468       end Error_Pragma_Arg;
2469
2470       ----------------------------
2471       -- Error_Pragma_Arg_Ident --
2472       ----------------------------
2473
2474       procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id) is
2475          MsgF : String := Msg;
2476       begin
2477          Error_Msg_Name_1 := Pname;
2478          Fix_Error (MsgF);
2479          Error_Msg_N (MsgF, Arg);
2480          raise Pragma_Exit;
2481       end Error_Pragma_Arg_Ident;
2482
2483       ----------------------
2484       -- Error_Pragma_Ref --
2485       ----------------------
2486
2487       procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id) is
2488          MsgF : String := Msg;
2489       begin
2490          Error_Msg_Name_1 := Pname;
2491          Fix_Error (MsgF);
2492          Error_Msg_Sloc   := Sloc (Ref);
2493          Error_Msg_NE (MsgF, N, Ref);
2494          raise Pragma_Exit;
2495       end Error_Pragma_Ref;
2496
2497       ------------------------
2498       -- Find_Lib_Unit_Name --
2499       ------------------------
2500
2501       function Find_Lib_Unit_Name return Entity_Id is
2502       begin
2503          --  Return inner compilation unit entity, for case of nested
2504          --  categorization pragmas. This happens in generic unit.
2505
2506          if Nkind (Parent (N)) = N_Package_Specification
2507            and then Defining_Entity (Parent (N)) /= Current_Scope
2508          then
2509             return Defining_Entity (Parent (N));
2510          else
2511             return Current_Scope;
2512          end if;
2513       end Find_Lib_Unit_Name;
2514
2515       ----------------------------
2516       -- Find_Program_Unit_Name --
2517       ----------------------------
2518
2519       procedure Find_Program_Unit_Name (Id : Node_Id) is
2520          Unit_Name : Entity_Id;
2521          Unit_Kind : Node_Kind;
2522          P         : constant Node_Id := Parent (N);
2523
2524       begin
2525          if Nkind (P) = N_Compilation_Unit then
2526             Unit_Kind := Nkind (Unit (P));
2527
2528             if Unit_Kind = N_Subprogram_Declaration
2529               or else Unit_Kind = N_Package_Declaration
2530               or else Unit_Kind in N_Generic_Declaration
2531             then
2532                Unit_Name := Defining_Entity (Unit (P));
2533
2534                if Chars (Id) = Chars (Unit_Name) then
2535                   Set_Entity (Id, Unit_Name);
2536                   Set_Etype (Id, Etype (Unit_Name));
2537                else
2538                   Set_Etype (Id, Any_Type);
2539                   Error_Pragma
2540                     ("cannot find program unit referenced by pragma%");
2541                end if;
2542
2543             else
2544                Set_Etype (Id, Any_Type);
2545                Error_Pragma ("pragma% inapplicable to this unit");
2546             end if;
2547
2548          else
2549             Analyze (Id);
2550          end if;
2551       end Find_Program_Unit_Name;
2552
2553       -----------------------------------------
2554       -- Find_Unique_Parameterless_Procedure --
2555       -----------------------------------------
2556
2557       function Find_Unique_Parameterless_Procedure
2558         (Name : Entity_Id;
2559          Arg  : Node_Id) return Entity_Id
2560       is
2561          Proc : Entity_Id := Empty;
2562
2563       begin
2564          --  The body of this procedure needs some comments ???
2565
2566          if not Is_Entity_Name (Name) then
2567             Error_Pragma_Arg
2568               ("argument of pragma% must be entity name", Arg);
2569
2570          elsif not Is_Overloaded (Name) then
2571             Proc := Entity (Name);
2572
2573             if Ekind (Proc) /= E_Procedure
2574               or else Present (First_Formal (Proc))
2575             then
2576                Error_Pragma_Arg
2577                  ("argument of pragma% must be parameterless procedure", Arg);
2578             end if;
2579
2580          else
2581             declare
2582                Found : Boolean := False;
2583                It    : Interp;
2584                Index : Interp_Index;
2585
2586             begin
2587                Get_First_Interp (Name, Index, It);
2588                while Present (It.Nam) loop
2589                   Proc := It.Nam;
2590
2591                   if Ekind (Proc) = E_Procedure
2592                     and then No (First_Formal (Proc))
2593                   then
2594                      if not Found then
2595                         Found := True;
2596                         Set_Entity (Name, Proc);
2597                         Set_Is_Overloaded (Name, False);
2598                      else
2599                         Error_Pragma_Arg
2600                           ("ambiguous handler name for pragma% ", Arg);
2601                      end if;
2602                   end if;
2603
2604                   Get_Next_Interp (Index, It);
2605                end loop;
2606
2607                if not Found then
2608                   Error_Pragma_Arg
2609                     ("argument of pragma% must be parameterless procedure",
2610                      Arg);
2611                else
2612                   Proc := Entity (Name);
2613                end if;
2614             end;
2615          end if;
2616
2617          return Proc;
2618       end Find_Unique_Parameterless_Procedure;
2619
2620       ---------------
2621       -- Fix_Error --
2622       ---------------
2623
2624       procedure Fix_Error (Msg : in out String) is
2625       begin
2626          if From_Aspect_Specification (N) then
2627             for J in Msg'First .. Msg'Last - 5 loop
2628                if Msg (J .. J + 5) = "pragma" then
2629                   Msg (J .. J + 5) := "aspect";
2630                end if;
2631             end loop;
2632
2633             if Error_Msg_Name_1 = Name_Precondition then
2634                Error_Msg_Name_1 := Name_Pre;
2635             elsif Error_Msg_Name_1 = Name_Postcondition then
2636                Error_Msg_Name_1 := Name_Post;
2637             end if;
2638          end if;
2639       end Fix_Error;
2640
2641       -------------------------
2642       -- Gather_Associations --
2643       -------------------------
2644
2645       procedure Gather_Associations
2646         (Names : Name_List;
2647          Args  : out Args_List)
2648       is
2649          Arg : Node_Id;
2650
2651       begin
2652          --  Initialize all parameters to Empty
2653
2654          for J in Args'Range loop
2655             Args (J) := Empty;
2656          end loop;
2657
2658          --  That's all we have to do if there are no argument associations
2659
2660          if No (Pragma_Argument_Associations (N)) then
2661             return;
2662          end if;
2663
2664          --  Otherwise first deal with any positional parameters present
2665
2666          Arg := First (Pragma_Argument_Associations (N));
2667          for Index in Args'Range loop
2668             exit when No (Arg) or else Chars (Arg) /= No_Name;
2669             Args (Index) := Get_Pragma_Arg (Arg);
2670             Next (Arg);
2671          end loop;
2672
2673          --  Positional parameters all processed, if any left, then we
2674          --  have too many positional parameters.
2675
2676          if Present (Arg) and then Chars (Arg) = No_Name then
2677             Error_Pragma_Arg
2678               ("too many positional associations for pragma%", Arg);
2679          end if;
2680
2681          --  Process named parameters if any are present
2682
2683          while Present (Arg) loop
2684             if Chars (Arg) = No_Name then
2685                Error_Pragma_Arg
2686                  ("positional association cannot follow named association",
2687                   Arg);
2688
2689             else
2690                for Index in Names'Range loop
2691                   if Names (Index) = Chars (Arg) then
2692                      if Present (Args (Index)) then
2693                         Error_Pragma_Arg
2694                           ("duplicate argument association for pragma%", Arg);
2695                      else
2696                         Args (Index) := Get_Pragma_Arg (Arg);
2697                         exit;
2698                      end if;
2699                   end if;
2700
2701                   if Index = Names'Last then
2702                      Error_Msg_Name_1 := Pname;
2703                      Error_Msg_N ("pragma% does not allow & argument", Arg);
2704
2705                      --  Check for possible misspelling
2706
2707                      for Index1 in Names'Range loop
2708                         if Is_Bad_Spelling_Of
2709                              (Chars (Arg), Names (Index1))
2710                         then
2711                            Error_Msg_Name_1 := Names (Index1);
2712                            Error_Msg_N -- CODEFIX
2713                              ("\possible misspelling of%", Arg);
2714                            exit;
2715                         end if;
2716                      end loop;
2717
2718                      raise Pragma_Exit;
2719                   end if;
2720                end loop;
2721             end if;
2722
2723             Next (Arg);
2724          end loop;
2725       end Gather_Associations;
2726
2727       -----------------
2728       -- GNAT_Pragma --
2729       -----------------
2730
2731       procedure GNAT_Pragma is
2732       begin
2733          --  We need to check the No_Implementation_Pragmas restriction for
2734          --  the case of a pragma from source. Note that the case of aspects
2735          --  generating corresponding pragmas marks these pragmas as not being
2736          --  from source, so this test also catches that case.
2737
2738          if Comes_From_Source (N) then
2739             Check_Restriction (No_Implementation_Pragmas, N);
2740          end if;
2741       end GNAT_Pragma;
2742
2743       --------------------------
2744       -- Is_Before_First_Decl --
2745       --------------------------
2746
2747       function Is_Before_First_Decl
2748         (Pragma_Node : Node_Id;
2749          Decls       : List_Id) return Boolean
2750       is
2751          Item : Node_Id := First (Decls);
2752
2753       begin
2754          --  Only other pragmas can come before this pragma
2755
2756          loop
2757             if No (Item) or else Nkind (Item) /= N_Pragma then
2758                return False;
2759
2760             elsif Item = Pragma_Node then
2761                return True;
2762             end if;
2763
2764             Next (Item);
2765          end loop;
2766       end Is_Before_First_Decl;
2767
2768       -----------------------------
2769       -- Is_Configuration_Pragma --
2770       -----------------------------
2771
2772       --  A configuration pragma must appear in the context clause of a
2773       --  compilation unit, and only other pragmas may precede it. Note that
2774       --  the test below also permits use in a configuration pragma file.
2775
2776       function Is_Configuration_Pragma return Boolean is
2777          Lis : constant List_Id := List_Containing (N);
2778          Par : constant Node_Id := Parent (N);
2779          Prg : Node_Id;
2780
2781       begin
2782          --  If no parent, then we are in the configuration pragma file,
2783          --  so the placement is definitely appropriate.
2784
2785          if No (Par) then
2786             return True;
2787
2788          --  Otherwise we must be in the context clause of a compilation unit
2789          --  and the only thing allowed before us in the context list is more
2790          --  configuration pragmas.
2791
2792          elsif Nkind (Par) = N_Compilation_Unit
2793            and then Context_Items (Par) = Lis
2794          then
2795             Prg := First (Lis);
2796
2797             loop
2798                if Prg = N then
2799                   return True;
2800                elsif Nkind (Prg) /= N_Pragma then
2801                   return False;
2802                end if;
2803
2804                Next (Prg);
2805             end loop;
2806
2807          else
2808             return False;
2809          end if;
2810       end Is_Configuration_Pragma;
2811
2812       --------------------------
2813       -- Is_In_Context_Clause --
2814       --------------------------
2815
2816       function Is_In_Context_Clause return Boolean is
2817          Plist       : List_Id;
2818          Parent_Node : Node_Id;
2819
2820       begin
2821          if not Is_List_Member (N) then
2822             return False;
2823
2824          else
2825             Plist := List_Containing (N);
2826             Parent_Node := Parent (Plist);
2827
2828             if Parent_Node = Empty
2829               or else Nkind (Parent_Node) /= N_Compilation_Unit
2830               or else Context_Items (Parent_Node) /= Plist
2831             then
2832                return False;
2833             end if;
2834          end if;
2835
2836          return True;
2837       end Is_In_Context_Clause;
2838
2839       ---------------------------------
2840       -- Is_Static_String_Expression --
2841       ---------------------------------
2842
2843       function Is_Static_String_Expression (Arg : Node_Id) return Boolean is
2844          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
2845
2846       begin
2847          Analyze_And_Resolve (Argx);
2848          return Is_OK_Static_Expression (Argx)
2849            and then Nkind (Argx) = N_String_Literal;
2850       end Is_Static_String_Expression;
2851
2852       ----------------------
2853       -- Pragma_Misplaced --
2854       ----------------------
2855
2856       procedure Pragma_Misplaced is
2857       begin
2858          Error_Pragma ("incorrect placement of pragma%");
2859       end Pragma_Misplaced;
2860
2861       ------------------------------------
2862       -- Process Atomic_Shared_Volatile --
2863       ------------------------------------
2864
2865       procedure Process_Atomic_Shared_Volatile is
2866          E_Id : Node_Id;
2867          E    : Entity_Id;
2868          D    : Node_Id;
2869          K    : Node_Kind;
2870          Utyp : Entity_Id;
2871
2872          procedure Set_Atomic (E : Entity_Id);
2873          --  Set given type as atomic, and if no explicit alignment was given,
2874          --  set alignment to unknown, since back end knows what the alignment
2875          --  requirements are for atomic arrays. Note: this step is necessary
2876          --  for derived types.
2877
2878          ----------------
2879          -- Set_Atomic --
2880          ----------------
2881
2882          procedure Set_Atomic (E : Entity_Id) is
2883          begin
2884             Set_Is_Atomic (E);
2885
2886             if not Has_Alignment_Clause (E) then
2887                Set_Alignment (E, Uint_0);
2888             end if;
2889          end Set_Atomic;
2890
2891       --  Start of processing for Process_Atomic_Shared_Volatile
2892
2893       begin
2894          Check_Ada_83_Warning;
2895          Check_No_Identifiers;
2896          Check_Arg_Count (1);
2897          Check_Arg_Is_Local_Name (Arg1);
2898          E_Id := Get_Pragma_Arg (Arg1);
2899
2900          if Etype (E_Id) = Any_Type then
2901             return;
2902          end if;
2903
2904          E := Entity (E_Id);
2905          D := Declaration_Node (E);
2906          K := Nkind (D);
2907
2908          --  Check duplicate before we chain ourselves!
2909
2910          Check_Duplicate_Pragma (E);
2911
2912          --  Now check appropriateness of the entity
2913
2914          if Is_Type (E) then
2915             if Rep_Item_Too_Early (E, N)
2916                  or else
2917                Rep_Item_Too_Late (E, N)
2918             then
2919                return;
2920             else
2921                Check_First_Subtype (Arg1);
2922             end if;
2923
2924             if Prag_Id /= Pragma_Volatile then
2925                Set_Atomic (E);
2926                Set_Atomic (Underlying_Type (E));
2927                Set_Atomic (Base_Type (E));
2928             end if;
2929
2930             --  Attribute belongs on the base type. If the view of the type is
2931             --  currently private, it also belongs on the underlying type.
2932
2933             Set_Is_Volatile (Base_Type (E));
2934             Set_Is_Volatile (Underlying_Type (E));
2935
2936             Set_Treat_As_Volatile (E);
2937             Set_Treat_As_Volatile (Underlying_Type (E));
2938
2939          elsif K = N_Object_Declaration
2940            or else (K = N_Component_Declaration
2941                      and then Original_Record_Component (E) = E)
2942          then
2943             if Rep_Item_Too_Late (E, N) then
2944                return;
2945             end if;
2946
2947             if Prag_Id /= Pragma_Volatile then
2948                Set_Is_Atomic (E);
2949
2950                --  If the object declaration has an explicit initialization, a
2951                --  temporary may have to be created to hold the expression, to
2952                --  ensure that access to the object remain atomic.
2953
2954                if Nkind (Parent (E)) = N_Object_Declaration
2955                  and then Present (Expression (Parent (E)))
2956                then
2957                   Set_Has_Delayed_Freeze (E);
2958                end if;
2959
2960                --  An interesting improvement here. If an object of type X is
2961                --  declared atomic, and the type X is not atomic, that's a
2962                --  pity, since it may not have appropriate alignment etc. We
2963                --  can rescue this in the special case where the object and
2964                --  type are in the same unit by just setting the type as
2965                --  atomic, so that the back end will process it as atomic.
2966
2967                Utyp := Underlying_Type (Etype (E));
2968
2969                if Present (Utyp)
2970                  and then Sloc (E) > No_Location
2971                  and then Sloc (Utyp) > No_Location
2972                  and then
2973                    Get_Source_File_Index (Sloc (E)) =
2974                    Get_Source_File_Index (Sloc (Underlying_Type (Etype (E))))
2975                then
2976                   Set_Is_Atomic (Underlying_Type (Etype (E)));
2977                end if;
2978             end if;
2979
2980             Set_Is_Volatile (E);
2981             Set_Treat_As_Volatile (E);
2982
2983          else
2984             Error_Pragma_Arg
2985               ("inappropriate entity for pragma%", Arg1);
2986          end if;
2987       end Process_Atomic_Shared_Volatile;
2988
2989       -------------------------------------------
2990       -- Process_Compile_Time_Warning_Or_Error --
2991       -------------------------------------------
2992
2993       procedure Process_Compile_Time_Warning_Or_Error is
2994          Arg1x : constant Node_Id := Get_Pragma_Arg (Arg1);
2995
2996       begin
2997          Check_Arg_Count (2);
2998          Check_No_Identifiers;
2999          Check_Arg_Is_Static_Expression (Arg2, Standard_String);
3000          Analyze_And_Resolve (Arg1x, Standard_Boolean);
3001
3002          if Compile_Time_Known_Value (Arg1x) then
3003             if Is_True (Expr_Value (Get_Pragma_Arg (Arg1))) then
3004                declare
3005                   Str   : constant String_Id :=
3006                             Strval (Get_Pragma_Arg (Arg2));
3007                   Len   : constant Int := String_Length (Str);
3008                   Cont  : Boolean;
3009                   Ptr   : Nat;
3010                   CC    : Char_Code;
3011                   C     : Character;
3012                   Cent  : constant Entity_Id :=
3013                             Cunit_Entity (Current_Sem_Unit);
3014
3015                   Force : constant Boolean :=
3016                             Prag_Id = Pragma_Compile_Time_Warning
3017                               and then
3018                                 Is_Spec_Name (Unit_Name (Current_Sem_Unit))
3019                               and then (Ekind (Cent) /= E_Package
3020                                           or else not In_Private_Part (Cent));
3021                   --  Set True if this is the warning case, and we are in the
3022                   --  visible part of a package spec, or in a subprogram spec,
3023                   --  in which case we want to force the client to see the
3024                   --  warning, even though it is not in the main unit.
3025
3026                begin
3027                   --  Loop through segments of message separated by line feeds.
3028                   --  We output these segments as separate messages with
3029                   --  continuation marks for all but the first.
3030
3031                   Cont := False;
3032                   Ptr := 1;
3033                   loop
3034                      Error_Msg_Strlen := 0;
3035
3036                      --  Loop to copy characters from argument to error message
3037                      --  string buffer.
3038
3039                      loop
3040                         exit when Ptr > Len;
3041                         CC := Get_String_Char (Str, Ptr);
3042                         Ptr := Ptr + 1;
3043
3044                         --  Ignore wide chars ??? else store character
3045
3046                         if In_Character_Range (CC) then
3047                            C := Get_Character (CC);
3048                            exit when C = ASCII.LF;
3049                            Error_Msg_Strlen := Error_Msg_Strlen + 1;
3050                            Error_Msg_String (Error_Msg_Strlen) := C;
3051                         end if;
3052                      end loop;
3053
3054                      --  Here with one line ready to go
3055
3056                      Error_Msg_Warn := Prag_Id = Pragma_Compile_Time_Warning;
3057
3058                      --  If this is a warning in a spec, then we want clients
3059                      --  to see the warning, so mark the message with the
3060                      --  special sequence !! to force the warning. In the case
3061                      --  of a package spec, we do not force this if we are in
3062                      --  the private part of the spec.
3063
3064                      if Force then
3065                         if Cont = False then
3066                            Error_Msg_N ("<~!!", Arg1);
3067                            Cont := True;
3068                         else
3069                            Error_Msg_N ("\<~!!", Arg1);
3070                         end if;
3071
3072                      --  Error, rather than warning, or in a body, so we do not
3073                      --  need to force visibility for client (error will be
3074                      --  output in any case, and this is the situation in which
3075                      --  we do not want a client to get a warning, since the
3076                      --  warning is in the body or the spec private part).
3077
3078                      else
3079                         if Cont = False then
3080                            Error_Msg_N ("<~", Arg1);
3081                            Cont := True;
3082                         else
3083                            Error_Msg_N ("\<~", Arg1);
3084                         end if;
3085                      end if;
3086
3087                      exit when Ptr > Len;
3088                   end loop;
3089                end;
3090             end if;
3091          end if;
3092       end Process_Compile_Time_Warning_Or_Error;
3093
3094       ------------------------
3095       -- Process_Convention --
3096       ------------------------
3097
3098       procedure Process_Convention
3099         (C   : out Convention_Id;
3100          Ent : out Entity_Id)
3101       is
3102          Id        : Node_Id;
3103          E         : Entity_Id;
3104          E1        : Entity_Id;
3105          Cname     : Name_Id;
3106          Comp_Unit : Unit_Number_Type;
3107
3108          procedure Diagnose_Multiple_Pragmas (S : Entity_Id);
3109          --  Called if we have more than one Export/Import/Convention pragma.
3110          --  This is generally illegal, but we have a special case of allowing
3111          --  Import and Interface to coexist if they specify the convention in
3112          --  a consistent manner. We are allowed to do this, since Interface is
3113          --  an implementation defined pragma, and we choose to do it since we
3114          --  know Rational allows this combination. S is the entity id of the
3115          --  subprogram in question. This procedure also sets the special flag
3116          --  Import_Interface_Present in both pragmas in the case where we do
3117          --  have matching Import and Interface pragmas.
3118
3119          procedure Set_Convention_From_Pragma (E : Entity_Id);
3120          --  Set convention in entity E, and also flag that the entity has a
3121          --  convention pragma. If entity is for a private or incomplete type,
3122          --  also set convention and flag on underlying type. This procedure
3123          --  also deals with the special case of C_Pass_By_Copy convention.
3124
3125          -------------------------------
3126          -- Diagnose_Multiple_Pragmas --
3127          -------------------------------
3128
3129          procedure Diagnose_Multiple_Pragmas (S : Entity_Id) is
3130             Pdec : constant Node_Id := Declaration_Node (S);
3131             Decl : Node_Id;
3132             Err  : Boolean;
3133
3134             function Same_Convention (Decl : Node_Id) return Boolean;
3135             --  Decl is a pragma node. This function returns True if this
3136             --  pragma has a first argument that is an identifier with a
3137             --  Chars field corresponding to the Convention_Id C.
3138
3139             function Same_Name (Decl : Node_Id) return Boolean;
3140             --  Decl is a pragma node. This function returns True if this
3141             --  pragma has a second argument that is an identifier with a
3142             --  Chars field that matches the Chars of the current subprogram.
3143
3144             ---------------------
3145             -- Same_Convention --
3146             ---------------------
3147
3148             function Same_Convention (Decl : Node_Id) return Boolean is
3149                Arg1 : constant Node_Id :=
3150                         First (Pragma_Argument_Associations (Decl));
3151
3152             begin
3153                if Present (Arg1) then
3154                   declare
3155                      Arg : constant Node_Id := Get_Pragma_Arg (Arg1);
3156                   begin
3157                      if Nkind (Arg) = N_Identifier
3158                        and then Is_Convention_Name (Chars (Arg))
3159                        and then Get_Convention_Id (Chars (Arg)) = C
3160                      then
3161                         return True;
3162                      end if;
3163                   end;
3164                end if;
3165
3166                return False;
3167             end Same_Convention;
3168
3169             ---------------
3170             -- Same_Name --
3171             ---------------
3172
3173             function Same_Name (Decl : Node_Id) return Boolean is
3174                Arg1 : constant Node_Id :=
3175                         First (Pragma_Argument_Associations (Decl));
3176                Arg2 : Node_Id;
3177
3178             begin
3179                if No (Arg1) then
3180                   return False;
3181                end if;
3182
3183                Arg2 := Next (Arg1);
3184
3185                if No (Arg2) then
3186                   return False;
3187                end if;
3188
3189                declare
3190                   Arg : constant Node_Id := Get_Pragma_Arg (Arg2);
3191                begin
3192                   if Nkind (Arg) = N_Identifier
3193                     and then Chars (Arg) = Chars (S)
3194                   then
3195                      return True;
3196                   end if;
3197                end;
3198
3199                return False;
3200             end Same_Name;
3201
3202          --  Start of processing for Diagnose_Multiple_Pragmas
3203
3204          begin
3205             Err := True;
3206
3207             --  Definitely give message if we have Convention/Export here
3208
3209             if Prag_Id = Pragma_Convention or else Prag_Id = Pragma_Export then
3210                null;
3211
3212                --  If we have an Import or Export, scan back from pragma to
3213                --  find any previous pragma applying to the same procedure.
3214                --  The scan will be terminated by the start of the list, or
3215                --  hitting the subprogram declaration. This won't allow one
3216                --  pragma to appear in the public part and one in the private
3217                --  part, but that seems very unlikely in practice.
3218
3219             else
3220                Decl := Prev (N);
3221                while Present (Decl) and then Decl /= Pdec loop
3222
3223                   --  Look for pragma with same name as us
3224
3225                   if Nkind (Decl) = N_Pragma
3226                     and then Same_Name (Decl)
3227                   then
3228                      --  Give error if same as our pragma or Export/Convention
3229
3230                      if Pragma_Name (Decl) = Name_Export
3231                           or else
3232                         Pragma_Name (Decl) = Name_Convention
3233                           or else
3234                         Pragma_Name (Decl) = Pragma_Name (N)
3235                      then
3236                         exit;
3237
3238                      --  Case of Import/Interface or the other way round
3239
3240                      elsif Pragma_Name (Decl) = Name_Interface
3241                              or else
3242                            Pragma_Name (Decl) = Name_Import
3243                      then
3244                         --  Here we know that we have Import and Interface. It
3245                         --  doesn't matter which way round they are. See if
3246                         --  they specify the same convention. If so, all OK,
3247                         --  and set special flags to stop other messages
3248
3249                         if Same_Convention (Decl) then
3250                            Set_Import_Interface_Present (N);
3251                            Set_Import_Interface_Present (Decl);
3252                            Err := False;
3253
3254                         --  If different conventions, special message
3255
3256                         else
3257                            Error_Msg_Sloc := Sloc (Decl);
3258                            Error_Pragma_Arg
3259                              ("convention differs from that given#", Arg1);
3260                            return;
3261                         end if;
3262                      end if;
3263                   end if;
3264
3265                   Next (Decl);
3266                end loop;
3267             end if;
3268
3269             --  Give message if needed if we fall through those tests
3270
3271             if Err then
3272                Error_Pragma_Arg
3273                  ("at most one Convention/Export/Import pragma is allowed",
3274                   Arg2);
3275             end if;
3276          end Diagnose_Multiple_Pragmas;
3277
3278          --------------------------------
3279          -- Set_Convention_From_Pragma --
3280          --------------------------------
3281
3282          procedure Set_Convention_From_Pragma (E : Entity_Id) is
3283          begin
3284             --  Ada 2005 (AI-430): Check invalid attempt to change convention
3285             --  for an overridden dispatching operation. Technically this is
3286             --  an amendment and should only be done in Ada 2005 mode. However,
3287             --  this is clearly a mistake, since the problem that is addressed
3288             --  by this AI is that there is a clear gap in the RM!
3289
3290             if Is_Dispatching_Operation (E)
3291               and then Present (Overridden_Operation (E))
3292               and then C /= Convention (Overridden_Operation (E))
3293             then
3294                Error_Pragma_Arg
3295                  ("cannot change convention for " &
3296                   "overridden dispatching operation",
3297                   Arg1);
3298             end if;
3299
3300             --  Set the convention
3301
3302             Set_Convention (E, C);
3303             Set_Has_Convention_Pragma (E);
3304
3305             if Is_Incomplete_Or_Private_Type (E)
3306               and then Present (Underlying_Type (E))
3307             then
3308                Set_Convention            (Underlying_Type (E), C);
3309                Set_Has_Convention_Pragma (Underlying_Type (E), True);
3310             end if;
3311
3312             --  A class-wide type should inherit the convention of the specific
3313             --  root type (although this isn't specified clearly by the RM).
3314
3315             if Is_Type (E) and then Present (Class_Wide_Type (E)) then
3316                Set_Convention (Class_Wide_Type (E), C);
3317             end if;
3318
3319             --  If the entity is a record type, then check for special case of
3320             --  C_Pass_By_Copy, which is treated the same as C except that the
3321             --  special record flag is set. This convention is only permitted
3322             --  on record types (see AI95-00131).
3323
3324             if Cname = Name_C_Pass_By_Copy then
3325                if Is_Record_Type (E) then
3326                   Set_C_Pass_By_Copy (Base_Type (E));
3327                elsif Is_Incomplete_Or_Private_Type (E)
3328                  and then Is_Record_Type (Underlying_Type (E))
3329                then
3330                   Set_C_Pass_By_Copy (Base_Type (Underlying_Type (E)));
3331                else
3332                   Error_Pragma_Arg
3333                     ("C_Pass_By_Copy convention allowed only for record type",
3334                      Arg2);
3335                end if;
3336             end if;
3337
3338             --  If the entity is a derived boolean type, check for the special
3339             --  case of convention C, C++, or Fortran, where we consider any
3340             --  nonzero value to represent true.
3341
3342             if Is_Discrete_Type (E)
3343               and then Root_Type (Etype (E)) = Standard_Boolean
3344               and then
3345                 (C = Convention_C
3346                    or else
3347                  C = Convention_CPP
3348                    or else
3349                  C = Convention_Fortran)
3350             then
3351                Set_Nonzero_Is_True (Base_Type (E));
3352             end if;
3353          end Set_Convention_From_Pragma;
3354
3355       --  Start of processing for Process_Convention
3356
3357       begin
3358          Check_At_Least_N_Arguments (2);
3359          Check_Optional_Identifier (Arg1, Name_Convention);
3360          Check_Arg_Is_Identifier (Arg1);
3361          Cname := Chars (Get_Pragma_Arg (Arg1));
3362
3363          --  C_Pass_By_Copy is treated as a synonym for convention C (this is
3364          --  tested again below to set the critical flag).
3365
3366          if Cname = Name_C_Pass_By_Copy then
3367             C := Convention_C;
3368
3369          --  Otherwise we must have something in the standard convention list
3370
3371          elsif Is_Convention_Name (Cname) then
3372             C := Get_Convention_Id (Chars (Get_Pragma_Arg (Arg1)));
3373
3374          --  In DEC VMS, it seems that there is an undocumented feature that
3375          --  any unrecognized convention is treated as the default, which for
3376          --  us is convention C. It does not seem so terrible to do this
3377          --  unconditionally, silently in the VMS case, and with a warning
3378          --  in the non-VMS case.
3379
3380          else
3381             if Warn_On_Export_Import and not OpenVMS_On_Target then
3382                Error_Msg_N
3383                  ("?unrecognized convention name, C assumed",
3384                   Get_Pragma_Arg (Arg1));
3385             end if;
3386
3387             C := Convention_C;
3388          end if;
3389
3390          Check_Optional_Identifier (Arg2, Name_Entity);
3391          Check_Arg_Is_Local_Name (Arg2);
3392
3393          Id := Get_Pragma_Arg (Arg2);
3394          Analyze (Id);
3395
3396          if not Is_Entity_Name (Id) then
3397             Error_Pragma_Arg ("entity name required", Arg2);
3398          end if;
3399
3400          E := Entity (Id);
3401
3402          --  Set entity to return
3403
3404          Ent := E;
3405
3406          --  Ada_Pass_By_Copy special checking
3407
3408          if C = Convention_Ada_Pass_By_Copy then
3409             if not Is_First_Subtype (E) then
3410                Error_Pragma_Arg
3411                  ("convention `Ada_Pass_By_Copy` only "
3412                   & "allowed for types", Arg2);
3413             end if;
3414
3415             if Is_By_Reference_Type (E) then
3416                Error_Pragma_Arg
3417                  ("convention `Ada_Pass_By_Copy` not allowed for "
3418                   & "by-reference type", Arg1);
3419             end if;
3420          end if;
3421
3422          --  Ada_Pass_By_Reference special checking
3423
3424          if C = Convention_Ada_Pass_By_Reference then
3425             if not Is_First_Subtype (E) then
3426                Error_Pragma_Arg
3427                  ("convention `Ada_Pass_By_Reference` only "
3428                   & "allowed for types", Arg2);
3429             end if;
3430
3431             if Is_By_Copy_Type (E) then
3432                Error_Pragma_Arg
3433                  ("convention `Ada_Pass_By_Reference` not allowed for "
3434                   & "by-copy type", Arg1);
3435             end if;
3436          end if;
3437
3438          --  Go to renamed subprogram if present, since convention applies to
3439          --  the actual renamed entity, not to the renaming entity. If the
3440          --  subprogram is inherited, go to parent subprogram.
3441
3442          if Is_Subprogram (E)
3443            and then Present (Alias (E))
3444          then
3445             if Nkind (Parent (Declaration_Node (E))) =
3446                                        N_Subprogram_Renaming_Declaration
3447             then
3448                if Scope (E) /= Scope (Alias (E)) then
3449                   Error_Pragma_Ref
3450                     ("cannot apply pragma% to non-local entity&#", E);
3451                end if;
3452
3453                E := Alias (E);
3454
3455             elsif Nkind_In (Parent (E), N_Full_Type_Declaration,
3456                                         N_Private_Extension_Declaration)
3457               and then Scope (E) = Scope (Alias (E))
3458             then
3459                E := Alias (E);
3460
3461                --  Return the parent subprogram the entity was inherited from
3462
3463                Ent := E;
3464             end if;
3465          end if;
3466
3467          --  Check that we are not applying this to a specless body
3468
3469          if Is_Subprogram (E)
3470            and then Nkind (Parent (Declaration_Node (E))) = N_Subprogram_Body
3471          then
3472             Error_Pragma
3473               ("pragma% requires separate spec and must come before body");
3474          end if;
3475
3476          --  Check that we are not applying this to a named constant
3477
3478          if Ekind_In (E, E_Named_Integer, E_Named_Real) then
3479             Error_Msg_Name_1 := Pname;
3480             Error_Msg_N
3481               ("cannot apply pragma% to named constant!",
3482                Get_Pragma_Arg (Arg2));
3483             Error_Pragma_Arg
3484               ("\supply appropriate type for&!", Arg2);
3485          end if;
3486
3487          if Ekind (E) = E_Enumeration_Literal then
3488             Error_Pragma ("enumeration literal not allowed for pragma%");
3489          end if;
3490
3491          --  Check for rep item appearing too early or too late
3492
3493          if Etype (E) = Any_Type
3494            or else Rep_Item_Too_Early (E, N)
3495          then
3496             raise Pragma_Exit;
3497
3498          elsif Present (Underlying_Type (E)) then
3499             E := Underlying_Type (E);
3500          end if;
3501
3502          if Rep_Item_Too_Late (E, N) then
3503             raise Pragma_Exit;
3504          end if;
3505
3506          if Has_Convention_Pragma (E) then
3507             Diagnose_Multiple_Pragmas (E);
3508
3509          elsif Convention (E) = Convention_Protected
3510            or else Ekind (Scope (E)) = E_Protected_Type
3511          then
3512             Error_Pragma_Arg
3513               ("a protected operation cannot be given a different convention",
3514                 Arg2);
3515          end if;
3516
3517          --  For Intrinsic, a subprogram is required
3518
3519          if C = Convention_Intrinsic
3520            and then not Is_Subprogram (E)
3521            and then not Is_Generic_Subprogram (E)
3522          then
3523             Error_Pragma_Arg
3524               ("second argument of pragma% must be a subprogram", Arg2);
3525          end if;
3526
3527          --  Stdcall case
3528
3529          if C = Convention_Stdcall then
3530
3531             --  A dispatching call is not allowed. A dispatching subprogram
3532             --  cannot be used to interface to the Win32 API, so in fact this
3533             --  check does not impose any effective restriction.
3534
3535             if Is_Dispatching_Operation (E) then
3536
3537                Error_Pragma
3538                  ("dispatching subprograms cannot use Stdcall convention");
3539
3540             --  Subprogram is allowed, but not a generic subprogram, and not a
3541             --  dispatching operation.
3542
3543             elsif not Is_Subprogram (E)
3544               and then not Is_Generic_Subprogram (E)
3545
3546               --  A variable is OK
3547
3548               and then Ekind (E) /= E_Variable
3549
3550               --  An access to subprogram is also allowed
3551
3552               and then not
3553                 (Is_Access_Type (E)
3554                   and then Ekind (Designated_Type (E)) = E_Subprogram_Type)
3555             then
3556                Error_Pragma_Arg
3557                  ("second argument of pragma% must be subprogram (type)",
3558                   Arg2);
3559             end if;
3560          end if;
3561
3562          if not Is_Subprogram (E)
3563            and then not Is_Generic_Subprogram (E)
3564          then
3565             Set_Convention_From_Pragma (E);
3566
3567             if Is_Type (E) then
3568                Check_First_Subtype (Arg2);
3569                Set_Convention_From_Pragma (Base_Type (E));
3570
3571                --  For subprograms, we must set the convention on the
3572                --  internally generated directly designated type as well.
3573
3574                if Ekind (E) = E_Access_Subprogram_Type then
3575                   Set_Convention_From_Pragma (Directly_Designated_Type (E));
3576                end if;
3577             end if;
3578
3579          --  For the subprogram case, set proper convention for all homonyms
3580          --  in same scope and the same declarative part, i.e. the same
3581          --  compilation unit.
3582
3583          else
3584             Comp_Unit := Get_Source_Unit (E);
3585             Set_Convention_From_Pragma (E);
3586
3587             --  Treat a pragma Import as an implicit body, for GPS use
3588
3589             if Prag_Id = Pragma_Import then
3590                Generate_Reference (E, Id, 'b');
3591             end if;
3592
3593             --  Loop through the homonyms of the pragma argument's entity
3594
3595             E1 := Ent;
3596             loop
3597                E1 := Homonym (E1);
3598                exit when No (E1) or else Scope (E1) /= Current_Scope;
3599
3600                --  Do not set the pragma on inherited operations or on formal
3601                --  subprograms.
3602
3603                if Comes_From_Source (E1)
3604                  and then Comp_Unit = Get_Source_Unit (E1)
3605                  and then not Is_Formal_Subprogram (E1)
3606                  and then Nkind (Original_Node (Parent (E1))) /=
3607                                                     N_Full_Type_Declaration
3608                then
3609                   if Present (Alias (E1))
3610                     and then Scope (E1) /= Scope (Alias (E1))
3611                   then
3612                      Error_Pragma_Ref
3613                        ("cannot apply pragma% to non-local entity& declared#",
3614                         E1);
3615                   end if;
3616
3617                   Set_Convention_From_Pragma (E1);
3618
3619                   if Prag_Id = Pragma_Import then
3620                      Generate_Reference (E1, Id, 'b');
3621                   end if;
3622                end if;
3623
3624                --  For aspect case, do NOT apply to homonyms
3625
3626                exit when From_Aspect_Specification (N);
3627             end loop;
3628          end if;
3629       end Process_Convention;
3630
3631       ----------------------------------------
3632       -- Process_Disable_Enable_Atomic_Sync --
3633       ----------------------------------------
3634
3635       procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id) is
3636       begin
3637          GNAT_Pragma;
3638          Check_No_Identifiers;
3639          Check_At_Most_N_Arguments (1);
3640
3641          --  Modeled internally as
3642          --    pragma Unsuppress (Atomic_Synchronization [,Entity])
3643
3644          Rewrite (N,
3645            Make_Pragma (Loc,
3646              Pragma_Identifier            =>
3647                Make_Identifier (Loc, Nam),
3648              Pragma_Argument_Associations => New_List (
3649                Make_Pragma_Argument_Association (Loc,
3650                  Expression =>
3651                    Make_Identifier (Loc, Name_Atomic_Synchronization)))));
3652
3653          if Present (Arg1) then
3654             Append_To (Pragma_Argument_Associations (N), New_Copy (Arg1));
3655          end if;
3656
3657          Analyze (N);
3658       end Process_Disable_Enable_Atomic_Sync;
3659
3660       -----------------------------------------------------
3661       -- Process_Extended_Import_Export_Exception_Pragma --
3662       -----------------------------------------------------
3663
3664       procedure Process_Extended_Import_Export_Exception_Pragma
3665         (Arg_Internal : Node_Id;
3666          Arg_External : Node_Id;
3667          Arg_Form     : Node_Id;
3668          Arg_Code     : Node_Id)
3669       is
3670          Def_Id   : Entity_Id;
3671          Code_Val : Uint;
3672
3673       begin
3674          if not OpenVMS_On_Target then
3675             Error_Pragma
3676               ("?pragma% ignored (applies only to Open'V'M'S)");
3677          end if;
3678
3679          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3680          Def_Id := Entity (Arg_Internal);
3681
3682          if Ekind (Def_Id) /= E_Exception then
3683             Error_Pragma_Arg
3684               ("pragma% must refer to declared exception", Arg_Internal);
3685          end if;
3686
3687          Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
3688
3689          if Present (Arg_Form) then
3690             Check_Arg_Is_One_Of (Arg_Form, Name_Ada, Name_VMS);
3691          end if;
3692
3693          if Present (Arg_Form)
3694            and then Chars (Arg_Form) = Name_Ada
3695          then
3696             null;
3697          else
3698             Set_Is_VMS_Exception (Def_Id);
3699             Set_Exception_Code (Def_Id, No_Uint);
3700          end if;
3701
3702          if Present (Arg_Code) then
3703             if not Is_VMS_Exception (Def_Id) then
3704                Error_Pragma_Arg
3705                  ("Code option for pragma% not allowed for Ada case",
3706                   Arg_Code);
3707             end if;
3708
3709             Check_Arg_Is_Static_Expression (Arg_Code, Any_Integer);
3710             Code_Val := Expr_Value (Arg_Code);
3711
3712             if not UI_Is_In_Int_Range (Code_Val) then
3713                Error_Pragma_Arg
3714                  ("Code option for pragma% must be in 32-bit range",
3715                   Arg_Code);
3716
3717             else
3718                Set_Exception_Code (Def_Id, Code_Val);
3719             end if;
3720          end if;
3721       end Process_Extended_Import_Export_Exception_Pragma;
3722
3723       -------------------------------------------------
3724       -- Process_Extended_Import_Export_Internal_Arg --
3725       -------------------------------------------------
3726
3727       procedure Process_Extended_Import_Export_Internal_Arg
3728         (Arg_Internal : Node_Id := Empty)
3729       is
3730       begin
3731          if No (Arg_Internal) then
3732             Error_Pragma ("Internal parameter required for pragma%");
3733          end if;
3734
3735          if Nkind (Arg_Internal) = N_Identifier then
3736             null;
3737
3738          elsif Nkind (Arg_Internal) = N_Operator_Symbol
3739            and then (Prag_Id = Pragma_Import_Function
3740                        or else
3741                      Prag_Id = Pragma_Export_Function)
3742          then
3743             null;
3744
3745          else
3746             Error_Pragma_Arg
3747               ("wrong form for Internal parameter for pragma%", Arg_Internal);
3748          end if;
3749
3750          Check_Arg_Is_Local_Name (Arg_Internal);
3751       end Process_Extended_Import_Export_Internal_Arg;
3752
3753       --------------------------------------------------
3754       -- Process_Extended_Import_Export_Object_Pragma --
3755       --------------------------------------------------
3756
3757       procedure Process_Extended_Import_Export_Object_Pragma
3758         (Arg_Internal : Node_Id;
3759          Arg_External : Node_Id;
3760          Arg_Size     : Node_Id)
3761       is
3762          Def_Id : Entity_Id;
3763
3764       begin
3765          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3766          Def_Id := Entity (Arg_Internal);
3767
3768          if not Ekind_In (Def_Id, E_Constant, E_Variable) then
3769             Error_Pragma_Arg
3770               ("pragma% must designate an object", Arg_Internal);
3771          end if;
3772
3773          if Has_Rep_Pragma (Def_Id, Name_Common_Object)
3774               or else
3775             Has_Rep_Pragma (Def_Id, Name_Psect_Object)
3776          then
3777             Error_Pragma_Arg
3778               ("previous Common/Psect_Object applies, pragma % not permitted",
3779                Arg_Internal);
3780          end if;
3781
3782          if Rep_Item_Too_Late (Def_Id, N) then
3783             raise Pragma_Exit;
3784          end if;
3785
3786          Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
3787
3788          if Present (Arg_Size) then
3789             Check_Arg_Is_External_Name (Arg_Size);
3790          end if;
3791
3792          --  Export_Object case
3793
3794          if Prag_Id = Pragma_Export_Object then
3795             if not Is_Library_Level_Entity (Def_Id) then
3796                Error_Pragma_Arg
3797                  ("argument for pragma% must be library level entity",
3798                   Arg_Internal);
3799             end if;
3800
3801             if Ekind (Current_Scope) = E_Generic_Package then
3802                Error_Pragma ("pragma& cannot appear in a generic unit");
3803             end if;
3804
3805             if not Size_Known_At_Compile_Time (Etype (Def_Id)) then
3806                Error_Pragma_Arg
3807                  ("exported object must have compile time known size",
3808                   Arg_Internal);
3809             end if;
3810
3811             if Warn_On_Export_Import and then Is_Exported (Def_Id) then
3812                Error_Msg_N ("?duplicate Export_Object pragma", N);
3813             else
3814                Set_Exported (Def_Id, Arg_Internal);
3815             end if;
3816
3817          --  Import_Object case
3818
3819          else
3820             if Is_Concurrent_Type (Etype (Def_Id)) then
3821                Error_Pragma_Arg
3822                  ("cannot use pragma% for task/protected object",
3823                   Arg_Internal);
3824             end if;
3825
3826             if Ekind (Def_Id) = E_Constant then
3827                Error_Pragma_Arg
3828                  ("cannot import a constant", Arg_Internal);
3829             end if;
3830
3831             if Warn_On_Export_Import
3832               and then Has_Discriminants (Etype (Def_Id))
3833             then
3834                Error_Msg_N
3835                  ("imported value must be initialized?", Arg_Internal);
3836             end if;
3837
3838             if Warn_On_Export_Import
3839               and then Is_Access_Type (Etype (Def_Id))
3840             then
3841                Error_Pragma_Arg
3842                  ("cannot import object of an access type?", Arg_Internal);
3843             end if;
3844
3845             if Warn_On_Export_Import
3846               and then Is_Imported (Def_Id)
3847             then
3848                Error_Msg_N
3849                  ("?duplicate Import_Object pragma", N);
3850
3851             --  Check for explicit initialization present. Note that an
3852             --  initialization generated by the code generator, e.g. for an
3853             --  access type, does not count here.
3854
3855             elsif Present (Expression (Parent (Def_Id)))
3856                and then
3857                  Comes_From_Source
3858                    (Original_Node (Expression (Parent (Def_Id))))
3859             then
3860                Error_Msg_Sloc := Sloc (Def_Id);
3861                Error_Pragma_Arg
3862                  ("imported entities cannot be initialized (RM B.1(24))",
3863                   "\no initialization allowed for & declared#", Arg1);
3864             else
3865                Set_Imported (Def_Id);
3866                Note_Possible_Modification (Arg_Internal, Sure => False);
3867             end if;
3868          end if;
3869       end Process_Extended_Import_Export_Object_Pragma;
3870
3871       ------------------------------------------------------
3872       -- Process_Extended_Import_Export_Subprogram_Pragma --
3873       ------------------------------------------------------
3874
3875       procedure Process_Extended_Import_Export_Subprogram_Pragma
3876         (Arg_Internal                 : Node_Id;
3877          Arg_External                 : Node_Id;
3878          Arg_Parameter_Types          : Node_Id;
3879          Arg_Result_Type              : Node_Id := Empty;
3880          Arg_Mechanism                : Node_Id;
3881          Arg_Result_Mechanism         : Node_Id := Empty;
3882          Arg_First_Optional_Parameter : Node_Id := Empty)
3883       is
3884          Ent       : Entity_Id;
3885          Def_Id    : Entity_Id;
3886          Hom_Id    : Entity_Id;
3887          Formal    : Entity_Id;
3888          Ambiguous : Boolean;
3889          Match     : Boolean;
3890          Dval      : Node_Id;
3891
3892          function Same_Base_Type
3893           (Ptype  : Node_Id;
3894            Formal : Entity_Id) return Boolean;
3895          --  Determines if Ptype references the type of Formal. Note that only
3896          --  the base types need to match according to the spec. Ptype here is
3897          --  the argument from the pragma, which is either a type name, or an
3898          --  access attribute.
3899
3900          --------------------
3901          -- Same_Base_Type --
3902          --------------------
3903
3904          function Same_Base_Type
3905            (Ptype  : Node_Id;
3906             Formal : Entity_Id) return Boolean
3907          is
3908             Ftyp : constant Entity_Id := Base_Type (Etype (Formal));
3909             Pref : Node_Id;
3910
3911          begin
3912             --  Case where pragma argument is typ'Access
3913
3914             if Nkind (Ptype) = N_Attribute_Reference
3915               and then Attribute_Name (Ptype) = Name_Access
3916             then
3917                Pref := Prefix (Ptype);
3918                Find_Type (Pref);
3919
3920                if not Is_Entity_Name (Pref)
3921                  or else Entity (Pref) = Any_Type
3922                then
3923                   raise Pragma_Exit;
3924                end if;
3925
3926                --  We have a match if the corresponding argument is of an
3927                --  anonymous access type, and its designated type matches the
3928                --  type of the prefix of the access attribute
3929
3930                return Ekind (Ftyp) = E_Anonymous_Access_Type
3931                  and then Base_Type (Entity (Pref)) =
3932                             Base_Type (Etype (Designated_Type (Ftyp)));
3933
3934             --  Case where pragma argument is a type name
3935
3936             else
3937                Find_Type (Ptype);
3938
3939                if not Is_Entity_Name (Ptype)
3940                  or else Entity (Ptype) = Any_Type
3941                then
3942                   raise Pragma_Exit;
3943                end if;
3944
3945                --  We have a match if the corresponding argument is of the type
3946                --  given in the pragma (comparing base types)
3947
3948                return Base_Type (Entity (Ptype)) = Ftyp;
3949             end if;
3950          end Same_Base_Type;
3951
3952       --  Start of processing for
3953       --  Process_Extended_Import_Export_Subprogram_Pragma
3954
3955       begin
3956          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3957          Ent := Empty;
3958          Ambiguous := False;
3959
3960          --  Loop through homonyms (overloadings) of the entity
3961
3962          Hom_Id := Entity (Arg_Internal);
3963          while Present (Hom_Id) loop
3964             Def_Id := Get_Base_Subprogram (Hom_Id);
3965
3966             --  We need a subprogram in the current scope
3967
3968             if not Is_Subprogram (Def_Id)
3969               or else Scope (Def_Id) /= Current_Scope
3970             then
3971                null;
3972
3973             else
3974                Match := True;
3975
3976                --  Pragma cannot apply to subprogram body
3977
3978                if Is_Subprogram (Def_Id)
3979                  and then Nkind (Parent (Declaration_Node (Def_Id))) =
3980                                                              N_Subprogram_Body
3981                then
3982                   Error_Pragma
3983                     ("pragma% requires separate spec"
3984                       & " and must come before body");
3985                end if;
3986
3987                --  Test result type if given, note that the result type
3988                --  parameter can only be present for the function cases.
3989
3990                if Present (Arg_Result_Type)
3991                  and then not Same_Base_Type (Arg_Result_Type, Def_Id)
3992                then
3993                   Match := False;
3994
3995                elsif Etype (Def_Id) /= Standard_Void_Type
3996                  and then
3997                    (Pname = Name_Export_Procedure
3998                       or else
3999                     Pname = Name_Import_Procedure)
4000                then
4001                   Match := False;
4002
4003                --  Test parameter types if given. Note that this parameter
4004                --  has not been analyzed (and must not be, since it is
4005                --  semantic nonsense), so we get it as the parser left it.
4006
4007                elsif Present (Arg_Parameter_Types) then
4008                   Check_Matching_Types : declare
4009                      Formal : Entity_Id;
4010                      Ptype  : Node_Id;
4011
4012                   begin
4013                      Formal := First_Formal (Def_Id);
4014
4015                      if Nkind (Arg_Parameter_Types) = N_Null then
4016                         if Present (Formal) then
4017                            Match := False;
4018                         end if;
4019
4020                      --  A list of one type, e.g. (List) is parsed as
4021                      --  a parenthesized expression.
4022
4023                      elsif Nkind (Arg_Parameter_Types) /= N_Aggregate
4024                        and then Paren_Count (Arg_Parameter_Types) = 1
4025                      then
4026                         if No (Formal)
4027                           or else Present (Next_Formal (Formal))
4028                         then
4029                            Match := False;
4030                         else
4031                            Match :=
4032                              Same_Base_Type (Arg_Parameter_Types, Formal);
4033                         end if;
4034
4035                      --  A list of more than one type is parsed as a aggregate
4036
4037                      elsif Nkind (Arg_Parameter_Types) = N_Aggregate
4038                        and then Paren_Count (Arg_Parameter_Types) = 0
4039                      then
4040                         Ptype := First (Expressions (Arg_Parameter_Types));
4041                         while Present (Ptype) or else Present (Formal) loop
4042                            if No (Ptype)
4043                              or else No (Formal)
4044                              or else not Same_Base_Type (Ptype, Formal)
4045                            then
4046                               Match := False;
4047                               exit;
4048                            else
4049                               Next_Formal (Formal);
4050                               Next (Ptype);
4051                            end if;
4052                         end loop;
4053
4054                      --  Anything else is of the wrong form
4055
4056                      else
4057                         Error_Pragma_Arg
4058                           ("wrong form for Parameter_Types parameter",
4059                            Arg_Parameter_Types);
4060                      end if;
4061                   end Check_Matching_Types;
4062                end if;
4063
4064                --  Match is now False if the entry we found did not match
4065                --  either a supplied Parameter_Types or Result_Types argument
4066
4067                if Match then
4068                   if No (Ent) then
4069                      Ent := Def_Id;
4070
4071                   --  Ambiguous case, the flag Ambiguous shows if we already
4072                   --  detected this and output the initial messages.
4073
4074                   else
4075                      if not Ambiguous then
4076                         Ambiguous := True;
4077                         Error_Msg_Name_1 := Pname;
4078                         Error_Msg_N
4079                           ("pragma% does not uniquely identify subprogram!",
4080                            N);
4081                         Error_Msg_Sloc := Sloc (Ent);
4082                         Error_Msg_N ("matching subprogram #!", N);
4083                         Ent := Empty;
4084                      end if;
4085
4086                      Error_Msg_Sloc := Sloc (Def_Id);
4087                      Error_Msg_N ("matching subprogram #!", N);
4088                   end if;
4089                end if;
4090             end if;
4091
4092             Hom_Id := Homonym (Hom_Id);
4093          end loop;
4094
4095          --  See if we found an entry
4096
4097          if No (Ent) then
4098             if not Ambiguous then
4099                if Is_Generic_Subprogram (Entity (Arg_Internal)) then
4100                   Error_Pragma
4101                     ("pragma% cannot be given for generic subprogram");
4102                else
4103                   Error_Pragma
4104                     ("pragma% does not identify local subprogram");
4105                end if;
4106             end if;
4107
4108             return;
4109          end if;
4110
4111          --  Import pragmas must be for imported entities
4112
4113          if Prag_Id = Pragma_Import_Function
4114               or else
4115             Prag_Id = Pragma_Import_Procedure
4116               or else
4117             Prag_Id = Pragma_Import_Valued_Procedure
4118          then
4119             if not Is_Imported (Ent) then
4120                Error_Pragma
4121                  ("pragma Import or Interface must precede pragma%");
4122             end if;
4123
4124          --  Here we have the Export case which can set the entity as exported
4125
4126          --  But does not do so if the specified external name is null, since
4127          --  that is taken as a signal in DEC Ada 83 (with which we want to be
4128          --  compatible) to request no external name.
4129
4130          elsif Nkind (Arg_External) = N_String_Literal
4131            and then String_Length (Strval (Arg_External)) = 0
4132          then
4133             null;
4134
4135          --  In all other cases, set entity as exported
4136
4137          else
4138             Set_Exported (Ent, Arg_Internal);
4139          end if;
4140
4141          --  Special processing for Valued_Procedure cases
4142
4143          if Prag_Id = Pragma_Import_Valued_Procedure
4144            or else
4145             Prag_Id = Pragma_Export_Valued_Procedure
4146          then
4147             Formal := First_Formal (Ent);
4148
4149             if No (Formal) then
4150                Error_Pragma ("at least one parameter required for pragma%");
4151
4152             elsif Ekind (Formal) /= E_Out_Parameter then
4153                Error_Pragma ("first parameter must have mode out for pragma%");
4154
4155             else
4156                Set_Is_Valued_Procedure (Ent);
4157             end if;
4158          end if;
4159
4160          Set_Extended_Import_Export_External_Name (Ent, Arg_External);
4161
4162          --  Process Result_Mechanism argument if present. We have already
4163          --  checked that this is only allowed for the function case.
4164
4165          if Present (Arg_Result_Mechanism) then
4166             Set_Mechanism_Value (Ent, Arg_Result_Mechanism);
4167          end if;
4168
4169          --  Process Mechanism parameter if present. Note that this parameter
4170          --  is not analyzed, and must not be analyzed since it is semantic
4171          --  nonsense, so we get it in exactly as the parser left it.
4172
4173          if Present (Arg_Mechanism) then
4174             declare
4175                Formal : Entity_Id;
4176                Massoc : Node_Id;
4177                Mname  : Node_Id;
4178                Choice : Node_Id;
4179
4180             begin
4181                --  A single mechanism association without a formal parameter
4182                --  name is parsed as a parenthesized expression. All other
4183                --  cases are parsed as aggregates, so we rewrite the single
4184                --  parameter case as an aggregate for consistency.
4185
4186                if Nkind (Arg_Mechanism) /= N_Aggregate
4187                  and then Paren_Count (Arg_Mechanism) = 1
4188                then
4189                   Rewrite (Arg_Mechanism,
4190                     Make_Aggregate (Sloc (Arg_Mechanism),
4191                       Expressions => New_List (
4192                         Relocate_Node (Arg_Mechanism))));
4193                end if;
4194
4195                --  Case of only mechanism name given, applies to all formals
4196
4197                if Nkind (Arg_Mechanism) /= N_Aggregate then
4198                   Formal := First_Formal (Ent);
4199                   while Present (Formal) loop
4200                      Set_Mechanism_Value (Formal, Arg_Mechanism);
4201                      Next_Formal (Formal);
4202                   end loop;
4203
4204                --  Case of list of mechanism associations given
4205
4206                else
4207                   if Null_Record_Present (Arg_Mechanism) then
4208                      Error_Pragma_Arg
4209                        ("inappropriate form for Mechanism parameter",
4210                         Arg_Mechanism);
4211                   end if;
4212
4213                   --  Deal with positional ones first
4214
4215                   Formal := First_Formal (Ent);
4216
4217                   if Present (Expressions (Arg_Mechanism)) then
4218                      Mname := First (Expressions (Arg_Mechanism));
4219                      while Present (Mname) loop
4220                         if No (Formal) then
4221                            Error_Pragma_Arg
4222                              ("too many mechanism associations", Mname);
4223                         end if;
4224
4225                         Set_Mechanism_Value (Formal, Mname);
4226                         Next_Formal (Formal);
4227                         Next (Mname);
4228                      end loop;
4229                   end if;
4230
4231                   --  Deal with named entries
4232
4233                   if Present (Component_Associations (Arg_Mechanism)) then
4234                      Massoc := First (Component_Associations (Arg_Mechanism));
4235                      while Present (Massoc) loop
4236                         Choice := First (Choices (Massoc));
4237
4238                         if Nkind (Choice) /= N_Identifier
4239                           or else Present (Next (Choice))
4240                         then
4241                            Error_Pragma_Arg
4242                              ("incorrect form for mechanism association",
4243                               Massoc);
4244                         end if;
4245
4246                         Formal := First_Formal (Ent);
4247                         loop
4248                            if No (Formal) then
4249                               Error_Pragma_Arg
4250                                 ("parameter name & not present", Choice);
4251                            end if;
4252
4253                            if Chars (Choice) = Chars (Formal) then
4254                               Set_Mechanism_Value
4255                                 (Formal, Expression (Massoc));
4256
4257                               --  Set entity on identifier (needed by ASIS)
4258
4259                               Set_Entity (Choice, Formal);
4260
4261                               exit;
4262                            end if;
4263
4264                            Next_Formal (Formal);
4265                         end loop;
4266
4267                         Next (Massoc);
4268                      end loop;
4269                   end if;
4270                end if;
4271             end;
4272          end if;
4273
4274          --  Process First_Optional_Parameter argument if present. We have
4275          --  already checked that this is only allowed for the Import case.
4276
4277          if Present (Arg_First_Optional_Parameter) then
4278             if Nkind (Arg_First_Optional_Parameter) /= N_Identifier then
4279                Error_Pragma_Arg
4280                  ("first optional parameter must be formal parameter name",
4281                   Arg_First_Optional_Parameter);
4282             end if;
4283
4284             Formal := First_Formal (Ent);
4285             loop
4286                if No (Formal) then
4287                   Error_Pragma_Arg
4288                     ("specified formal parameter& not found",
4289                      Arg_First_Optional_Parameter);
4290                end if;
4291
4292                exit when Chars (Formal) =
4293                          Chars (Arg_First_Optional_Parameter);
4294
4295                Next_Formal (Formal);
4296             end loop;
4297
4298             Set_First_Optional_Parameter (Ent, Formal);
4299
4300             --  Check specified and all remaining formals have right form
4301
4302             while Present (Formal) loop
4303                if Ekind (Formal) /= E_In_Parameter then
4304                   Error_Msg_NE
4305                     ("optional formal& is not of mode in!",
4306                      Arg_First_Optional_Parameter, Formal);
4307
4308                else
4309                   Dval := Default_Value (Formal);
4310
4311                   if No (Dval) then
4312                      Error_Msg_NE
4313                        ("optional formal& does not have default value!",
4314                         Arg_First_Optional_Parameter, Formal);
4315
4316                   elsif Compile_Time_Known_Value_Or_Aggr (Dval) then
4317                      null;
4318
4319                   else
4320                      Error_Msg_FE
4321                        ("default value for optional formal& is non-static!",
4322                         Arg_First_Optional_Parameter, Formal);
4323                   end if;
4324                end if;
4325
4326                Set_Is_Optional_Parameter (Formal);
4327                Next_Formal (Formal);
4328             end loop;
4329          end if;
4330       end Process_Extended_Import_Export_Subprogram_Pragma;
4331
4332       --------------------------
4333       -- Process_Generic_List --
4334       --------------------------
4335
4336       procedure Process_Generic_List is
4337          Arg : Node_Id;
4338          Exp : Node_Id;
4339
4340       begin
4341          Check_No_Identifiers;
4342          Check_At_Least_N_Arguments (1);
4343
4344          Arg := Arg1;
4345          while Present (Arg) loop
4346             Exp := Get_Pragma_Arg (Arg);
4347             Analyze (Exp);
4348
4349             if not Is_Entity_Name (Exp)
4350               or else
4351                 (not Is_Generic_Instance (Entity (Exp))
4352                   and then
4353                  not Is_Generic_Unit (Entity (Exp)))
4354             then
4355                Error_Pragma_Arg
4356                  ("pragma% argument must be name of generic unit/instance",
4357                   Arg);
4358             end if;
4359
4360             Next (Arg);
4361          end loop;
4362       end Process_Generic_List;
4363
4364       ------------------------------------
4365       -- Process_Import_Predefined_Type --
4366       ------------------------------------
4367
4368       procedure Process_Import_Predefined_Type is
4369          Loc  : constant Source_Ptr := Sloc (N);
4370          Elmt : Elmt_Id;
4371          Ftyp : Node_Id := Empty;
4372          Decl : Node_Id;
4373          Def  : Node_Id;
4374          Nam  : Name_Id;
4375
4376       begin
4377          String_To_Name_Buffer (Strval (Expression (Arg3)));
4378          Nam := Name_Find;
4379
4380          Elmt := First_Elmt (Predefined_Float_Types);
4381          while Present (Elmt) and then Chars (Node (Elmt)) /= Nam loop
4382             Next_Elmt (Elmt);
4383          end loop;
4384
4385          Ftyp := Node (Elmt);
4386
4387          if Present (Ftyp) then
4388
4389             --  Don't build a derived type declaration, because predefined C
4390             --  types have no declaration anywhere, so cannot really be named.
4391             --  Instead build a full type declaration, starting with an
4392             --  appropriate type definition is built
4393
4394             if Is_Floating_Point_Type (Ftyp) then
4395                Def := Make_Floating_Point_Definition (Loc,
4396                  Make_Integer_Literal (Loc, Digits_Value (Ftyp)),
4397                  Make_Real_Range_Specification (Loc,
4398                    Make_Real_Literal (Loc, Realval (Type_Low_Bound (Ftyp))),
4399                    Make_Real_Literal (Loc, Realval (Type_High_Bound (Ftyp)))));
4400
4401             --  Should never have a predefined type we cannot handle
4402
4403             else
4404                raise Program_Error;
4405             end if;
4406
4407             --  Build and insert a Full_Type_Declaration, which will be
4408             --  analyzed as soon as this list entry has been analyzed.
4409
4410             Decl := Make_Full_Type_Declaration (Loc,
4411               Make_Defining_Identifier (Loc, Chars (Expression (Arg2))),
4412               Type_Definition => Def);
4413
4414             Insert_After (N, Decl);
4415             Mark_Rewrite_Insertion (Decl);
4416
4417          else
4418             Error_Pragma_Arg ("no matching type found for pragma%",
4419             Arg2);
4420          end if;
4421       end Process_Import_Predefined_Type;
4422
4423       ---------------------------------
4424       -- Process_Import_Or_Interface --
4425       ---------------------------------
4426
4427       procedure Process_Import_Or_Interface is
4428          C      : Convention_Id;
4429          Def_Id : Entity_Id;
4430          Hom_Id : Entity_Id;
4431
4432       begin
4433          Process_Convention (C, Def_Id);
4434          Kill_Size_Check_Code (Def_Id);
4435          Note_Possible_Modification (Get_Pragma_Arg (Arg2), Sure => False);
4436
4437          if Ekind_In (Def_Id, E_Variable, E_Constant) then
4438
4439             --  We do not permit Import to apply to a renaming declaration
4440
4441             if Present (Renamed_Object (Def_Id)) then
4442                Error_Pragma_Arg
4443                  ("pragma% not allowed for object renaming", Arg2);
4444
4445             --  User initialization is not allowed for imported object, but
4446             --  the object declaration may contain a default initialization,
4447             --  that will be discarded. Note that an explicit initialization
4448             --  only counts if it comes from source, otherwise it is simply
4449             --  the code generator making an implicit initialization explicit.
4450
4451             elsif Present (Expression (Parent (Def_Id)))
4452               and then Comes_From_Source (Expression (Parent (Def_Id)))
4453             then
4454                Error_Msg_Sloc := Sloc (Def_Id);
4455                Error_Pragma_Arg
4456                  ("no initialization allowed for declaration of& #",
4457                   "\imported entities cannot be initialized (RM B.1(24))",
4458                   Arg2);
4459
4460             else
4461                Set_Imported (Def_Id);
4462                Process_Interface_Name (Def_Id, Arg3, Arg4);
4463
4464                --  Note that we do not set Is_Public here. That's because we
4465                --  only want to set it if there is no address clause, and we
4466                --  don't know that yet, so we delay that processing till
4467                --  freeze time.
4468
4469                --  pragma Import completes deferred constants
4470
4471                if Ekind (Def_Id) = E_Constant then
4472                   Set_Has_Completion (Def_Id);
4473                end if;
4474
4475                --  It is not possible to import a constant of an unconstrained
4476                --  array type (e.g. string) because there is no simple way to
4477                --  write a meaningful subtype for it.
4478
4479                if Is_Array_Type (Etype (Def_Id))
4480                  and then not Is_Constrained (Etype (Def_Id))
4481                then
4482                   Error_Msg_NE
4483                     ("imported constant& must have a constrained subtype",
4484                       N, Def_Id);
4485                end if;
4486             end if;
4487
4488          elsif Is_Subprogram (Def_Id)
4489            or else Is_Generic_Subprogram (Def_Id)
4490          then
4491             --  If the name is overloaded, pragma applies to all of the denoted
4492             --  entities in the same declarative part.
4493
4494             Hom_Id := Def_Id;
4495             while Present (Hom_Id) loop
4496                Def_Id := Get_Base_Subprogram (Hom_Id);
4497
4498                --  Ignore inherited subprograms because the pragma will apply
4499                --  to the parent operation, which is the one called.
4500
4501                if Is_Overloadable (Def_Id)
4502                  and then Present (Alias (Def_Id))
4503                then
4504                   null;
4505
4506                --  If it is not a subprogram, it must be in an outer scope and
4507                --  pragma does not apply.
4508
4509                elsif not Is_Subprogram (Def_Id)
4510                  and then not Is_Generic_Subprogram (Def_Id)
4511                then
4512                   null;
4513
4514                --  The pragma does not apply to primitives of interfaces
4515
4516                elsif Is_Dispatching_Operation (Def_Id)
4517                  and then Present (Find_Dispatching_Type (Def_Id))
4518                  and then Is_Interface (Find_Dispatching_Type (Def_Id))
4519                then
4520                   null;
4521
4522                --  Verify that the homonym is in the same declarative part (not
4523                --  just the same scope).
4524
4525                elsif Parent (Unit_Declaration_Node (Def_Id)) /= Parent (N)
4526                  and then Nkind (Parent (N)) /= N_Compilation_Unit_Aux
4527                then
4528                   exit;
4529
4530                else
4531                   Set_Imported (Def_Id);
4532
4533                   --  Reject an Import applied to an abstract subprogram
4534
4535                   if Is_Subprogram (Def_Id)
4536                     and then Is_Abstract_Subprogram (Def_Id)
4537                   then
4538                      Error_Msg_Sloc := Sloc (Def_Id);
4539                      Error_Msg_NE
4540                        ("cannot import abstract subprogram& declared#",
4541                         Arg2, Def_Id);
4542                   end if;
4543
4544                   --  Special processing for Convention_Intrinsic
4545
4546                   if C = Convention_Intrinsic then
4547
4548                      --  Link_Name argument not allowed for intrinsic
4549
4550                      Check_No_Link_Name;
4551
4552                      Set_Is_Intrinsic_Subprogram (Def_Id);
4553
4554                      --  If no external name is present, then check that this
4555                      --  is a valid intrinsic subprogram. If an external name
4556                      --  is present, then this is handled by the back end.
4557
4558                      if No (Arg3) then
4559                         Check_Intrinsic_Subprogram
4560                           (Def_Id, Get_Pragma_Arg (Arg2));
4561                      end if;
4562                   end if;
4563
4564                   --  All interfaced procedures need an external symbol created
4565                   --  for them since they are always referenced from another
4566                   --  object file.
4567
4568                   Set_Is_Public (Def_Id);
4569
4570                   --  Verify that the subprogram does not have a completion
4571                   --  through a renaming declaration. For other completions the
4572                   --  pragma appears as a too late representation.
4573
4574                   declare
4575                      Decl : constant Node_Id := Unit_Declaration_Node (Def_Id);
4576
4577                   begin
4578                      if Present (Decl)
4579                        and then Nkind (Decl) = N_Subprogram_Declaration
4580                        and then Present (Corresponding_Body (Decl))
4581                        and then Nkind (Unit_Declaration_Node
4582                                         (Corresponding_Body (Decl))) =
4583                                              N_Subprogram_Renaming_Declaration
4584                      then
4585                         Error_Msg_Sloc := Sloc (Def_Id);
4586                         Error_Msg_NE
4587                           ("cannot import&, renaming already provided for " &
4588                            "declaration #", N, Def_Id);
4589                      end if;
4590                   end;
4591
4592                   Set_Has_Completion (Def_Id);
4593                   Process_Interface_Name (Def_Id, Arg3, Arg4);
4594                end if;
4595
4596                if Is_Compilation_Unit (Hom_Id) then
4597
4598                   --  Its possible homonyms are not affected by the pragma.
4599                   --  Such homonyms might be present in the context of other
4600                   --  units being compiled.
4601
4602                   exit;
4603
4604                else
4605                   Hom_Id := Homonym (Hom_Id);
4606                end if;
4607             end loop;
4608
4609          --  When the convention is Java or CIL, we also allow Import to be
4610          --  given for packages, generic packages, exceptions, record
4611          --  components, and access to subprograms.
4612
4613          elsif (C = Convention_Java or else C = Convention_CIL)
4614            and then
4615              (Is_Package_Or_Generic_Package (Def_Id)
4616                or else Ekind (Def_Id) = E_Exception
4617                or else Ekind (Def_Id) = E_Access_Subprogram_Type
4618                or else Nkind (Parent (Def_Id)) = N_Component_Declaration)
4619          then
4620             Set_Imported (Def_Id);
4621             Set_Is_Public (Def_Id);
4622             Process_Interface_Name (Def_Id, Arg3, Arg4);
4623
4624          --  Import a CPP class
4625
4626          elsif C = Convention_CPP
4627            and then (Is_Record_Type (Def_Id)
4628                       or else Ekind (Def_Id) = E_Incomplete_Type)
4629          then
4630             if Ekind (Def_Id) = E_Incomplete_Type then
4631                if Present (Full_View (Def_Id)) then
4632                   Def_Id := Full_View (Def_Id);
4633
4634                else
4635                   Error_Msg_N
4636                     ("cannot import 'C'P'P type before full declaration seen",
4637                      Get_Pragma_Arg (Arg2));
4638
4639                   --  Although we have reported the error we decorate it as
4640                   --  CPP_Class to avoid reporting spurious errors
4641
4642                   Set_Is_CPP_Class (Def_Id);
4643                   return;
4644                end if;
4645             end if;
4646
4647             --  Types treated as CPP classes must be declared limited (note:
4648             --  this used to be a warning but there is no real benefit to it
4649             --  since we did effectively intend to treat the type as limited
4650             --  anyway).
4651
4652             if not Is_Limited_Type (Def_Id) then
4653                Error_Msg_N
4654                  ("imported 'C'P'P type must be limited",
4655                   Get_Pragma_Arg (Arg2));
4656             end if;
4657
4658             Set_Is_CPP_Class (Def_Id);
4659
4660             --  Imported CPP types must not have discriminants (because C++
4661             --  classes do not have discriminants).
4662
4663             if Has_Discriminants (Def_Id) then
4664                Error_Msg_N
4665                  ("imported 'C'P'P type cannot have discriminants",
4666                   First (Discriminant_Specifications
4667                           (Declaration_Node (Def_Id))));
4668             end if;
4669
4670             --  Check that components of imported CPP types do not have default
4671             --  expressions. For private types this check is performed when the
4672             --  full view is analyzed (see Process_Full_View).
4673
4674             if not Is_Private_Type (Def_Id) then
4675                Check_CPP_Type_Has_No_Defaults (Def_Id);
4676             end if;
4677
4678          elsif Nkind (Parent (Def_Id)) = N_Incomplete_Type_Declaration then
4679             Check_No_Link_Name;
4680             Check_Arg_Count (3);
4681             Check_Arg_Is_Static_Expression (Arg3, Standard_String);
4682
4683             Process_Import_Predefined_Type;
4684
4685          else
4686             Error_Pragma_Arg
4687               ("second argument of pragma% must be object, subprogram "
4688                & "or incomplete type",
4689                Arg2);
4690          end if;
4691
4692          --  If this pragma applies to a compilation unit, then the unit, which
4693          --  is a subprogram, does not require (or allow) a body. We also do
4694          --  not need to elaborate imported procedures.
4695
4696          if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
4697             declare
4698                Cunit : constant Node_Id := Parent (Parent (N));
4699             begin
4700                Set_Body_Required (Cunit, False);
4701             end;
4702          end if;
4703       end Process_Import_Or_Interface;
4704
4705       --------------------
4706       -- Process_Inline --
4707       --------------------
4708
4709       procedure Process_Inline (Active : Boolean) is
4710          Assoc     : Node_Id;
4711          Decl      : Node_Id;
4712          Subp_Id   : Node_Id;
4713          Subp      : Entity_Id;
4714          Applies   : Boolean;
4715
4716          Effective : Boolean := False;
4717          --  Set True if inline has some effect, i.e. if there is at least one
4718          --  subprogram set as inlined as a result of the use of the pragma.
4719
4720          procedure Make_Inline (Subp : Entity_Id);
4721          --  Subp is the defining unit name of the subprogram declaration. Set
4722          --  the flag, as well as the flag in the corresponding body, if there
4723          --  is one present.
4724
4725          procedure Set_Inline_Flags (Subp : Entity_Id);
4726          --  Sets Is_Inlined and Has_Pragma_Inline flags for Subp and also
4727          --  Has_Pragma_Inline_Always for the Inline_Always case.
4728
4729          function Inlining_Not_Possible (Subp : Entity_Id) return Boolean;
4730          --  Returns True if it can be determined at this stage that inlining
4731          --  is not possible, for example if the body is available and contains
4732          --  exception handlers, we prevent inlining, since otherwise we can
4733          --  get undefined symbols at link time. This function also emits a
4734          --  warning if front-end inlining is enabled and the pragma appears
4735          --  too late.
4736          --
4737          --  ??? is business with link symbols still valid, or does it relate
4738          --  to front end ZCX which is being phased out ???
4739
4740          ---------------------------
4741          -- Inlining_Not_Possible --
4742          ---------------------------
4743
4744          function Inlining_Not_Possible (Subp : Entity_Id) return Boolean is
4745             Decl  : constant Node_Id := Unit_Declaration_Node (Subp);
4746             Stats : Node_Id;
4747
4748          begin
4749             if Nkind (Decl) = N_Subprogram_Body then
4750                Stats := Handled_Statement_Sequence (Decl);
4751                return Present (Exception_Handlers (Stats))
4752                  or else Present (At_End_Proc (Stats));
4753
4754             elsif Nkind (Decl) = N_Subprogram_Declaration
4755               and then Present (Corresponding_Body (Decl))
4756             then
4757                if Front_End_Inlining
4758                  and then Analyzed (Corresponding_Body (Decl))
4759                then
4760                   Error_Msg_N ("pragma appears too late, ignored?", N);
4761                   return True;
4762
4763                --  If the subprogram is a renaming as body, the body is just a
4764                --  call to the renamed subprogram, and inlining is trivially
4765                --  possible.
4766
4767                elsif
4768                  Nkind (Unit_Declaration_Node (Corresponding_Body (Decl))) =
4769                                              N_Subprogram_Renaming_Declaration
4770                then
4771                   return False;
4772
4773                else
4774                   Stats :=
4775                     Handled_Statement_Sequence
4776                         (Unit_Declaration_Node (Corresponding_Body (Decl)));
4777
4778                   return
4779                     Present (Exception_Handlers (Stats))
4780                       or else Present (At_End_Proc (Stats));
4781                end if;
4782
4783             else
4784                --  If body is not available, assume the best, the check is
4785                --  performed again when compiling enclosing package bodies.
4786
4787                return False;
4788             end if;
4789          end Inlining_Not_Possible;
4790
4791          -----------------
4792          -- Make_Inline --
4793          -----------------
4794
4795          procedure Make_Inline (Subp : Entity_Id) is
4796             Kind       : constant Entity_Kind := Ekind (Subp);
4797             Inner_Subp : Entity_Id   := Subp;
4798
4799          begin
4800             --  Ignore if bad type, avoid cascaded error
4801
4802             if Etype (Subp) = Any_Type then
4803                Applies := True;
4804                return;
4805
4806             --  Ignore if all inlining is suppressed
4807
4808             elsif Suppress_All_Inlining then
4809                Applies := True;
4810                return;
4811
4812             --  If inlining is not possible, for now do not treat as an error
4813
4814             elsif Inlining_Not_Possible (Subp) then
4815                Applies := True;
4816                return;
4817
4818             --  Here we have a candidate for inlining, but we must exclude
4819             --  derived operations. Otherwise we would end up trying to inline
4820             --  a phantom declaration, and the result would be to drag in a
4821             --  body which has no direct inlining associated with it. That
4822             --  would not only be inefficient but would also result in the
4823             --  backend doing cross-unit inlining in cases where it was
4824             --  definitely inappropriate to do so.
4825
4826             --  However, a simple Comes_From_Source test is insufficient, since
4827             --  we do want to allow inlining of generic instances which also do
4828             --  not come from source. We also need to recognize specs generated
4829             --  by the front-end for bodies that carry the pragma. Finally,
4830             --  predefined operators do not come from source but are not
4831             --  inlineable either.
4832
4833             elsif Is_Generic_Instance (Subp)
4834               or else Nkind (Parent (Parent (Subp))) = N_Subprogram_Declaration
4835             then
4836                null;
4837
4838             elsif not Comes_From_Source (Subp)
4839               and then Scope (Subp) /= Standard_Standard
4840             then
4841                Applies := True;
4842                return;
4843             end if;
4844
4845             --  The referenced entity must either be the enclosing entity, or
4846             --  an entity declared within the current open scope.
4847
4848             if Present (Scope (Subp))
4849               and then Scope (Subp) /= Current_Scope
4850               and then Subp /= Current_Scope
4851             then
4852                Error_Pragma_Arg
4853                  ("argument of% must be entity in current scope", Assoc);
4854                return;
4855             end if;
4856
4857             --  Processing for procedure, operator or function. If subprogram
4858             --  is aliased (as for an instance) indicate that the renamed
4859             --  entity (if declared in the same unit) is inlined.
4860
4861             if Is_Subprogram (Subp) then
4862                Inner_Subp := Ultimate_Alias (Inner_Subp);
4863
4864                if In_Same_Source_Unit (Subp, Inner_Subp) then
4865                   Set_Inline_Flags (Inner_Subp);
4866
4867                   Decl := Parent (Parent (Inner_Subp));
4868
4869                   if Nkind (Decl) = N_Subprogram_Declaration
4870                     and then Present (Corresponding_Body (Decl))
4871                   then
4872                      Set_Inline_Flags (Corresponding_Body (Decl));
4873
4874                   elsif Is_Generic_Instance (Subp) then
4875
4876                      --  Indicate that the body needs to be created for
4877                      --  inlining subsequent calls. The instantiation node
4878                      --  follows the declaration of the wrapper package
4879                      --  created for it.
4880
4881                      if Scope (Subp) /= Standard_Standard
4882                        and then
4883                          Need_Subprogram_Instance_Body
4884                           (Next (Unit_Declaration_Node (Scope (Alias (Subp)))),
4885                               Subp)
4886                      then
4887                         null;
4888                      end if;
4889
4890                   --  Inline is a program unit pragma (RM 10.1.5) and cannot
4891                   --  appear in a formal part to apply to a formal subprogram.
4892                   --  Do not apply check within an instance or a formal package
4893                   --  the test will have been applied to the original generic.
4894
4895                   elsif Nkind (Decl) in N_Formal_Subprogram_Declaration
4896                     and then List_Containing (Decl) = List_Containing (N)
4897                     and then not In_Instance
4898                   then
4899                      Error_Msg_N
4900                        ("Inline cannot apply to a formal subprogram", N);
4901                   end if;
4902                end if;
4903
4904                Applies := True;
4905
4906             --  For a generic subprogram set flag as well, for use at the point
4907             --  of instantiation, to determine whether the body should be
4908             --  generated.
4909
4910             elsif Is_Generic_Subprogram (Subp) then
4911                Set_Inline_Flags (Subp);
4912                Applies := True;
4913
4914             --  Literals are by definition inlined
4915
4916             elsif Kind = E_Enumeration_Literal then
4917                null;
4918
4919             --  Anything else is an error
4920
4921             else
4922                Error_Pragma_Arg
4923                  ("expect subprogram name for pragma%", Assoc);
4924             end if;
4925          end Make_Inline;
4926
4927          ----------------------
4928          -- Set_Inline_Flags --
4929          ----------------------
4930
4931          procedure Set_Inline_Flags (Subp : Entity_Id) is
4932          begin
4933             if Active then
4934                Set_Is_Inlined (Subp);
4935             end if;
4936
4937             if not Has_Pragma_Inline (Subp) then
4938                Set_Has_Pragma_Inline (Subp);
4939                Effective := True;
4940             end if;
4941
4942             if Prag_Id = Pragma_Inline_Always then
4943                Set_Has_Pragma_Inline_Always (Subp);
4944             end if;
4945          end Set_Inline_Flags;
4946
4947       --  Start of processing for Process_Inline
4948
4949       begin
4950          Check_No_Identifiers;
4951          Check_At_Least_N_Arguments (1);
4952
4953          if Active then
4954             Inline_Processing_Required := True;
4955          end if;
4956
4957          Assoc := Arg1;
4958          while Present (Assoc) loop
4959             Subp_Id := Get_Pragma_Arg (Assoc);
4960             Analyze (Subp_Id);
4961             Applies := False;
4962
4963             if Is_Entity_Name (Subp_Id) then
4964                Subp := Entity (Subp_Id);
4965
4966                if Subp = Any_Id then
4967
4968                   --  If previous error, avoid cascaded errors
4969
4970                   Applies := True;
4971                   Effective := True;
4972
4973                else
4974                   Make_Inline (Subp);
4975
4976                   --  For the pragma case, climb homonym chain. This is
4977                   --  what implements allowing the pragma in the renaming
4978                   --  case, with the result applying to the ancestors, and
4979                   --  also allows Inline to apply to all previous homonyms.
4980
4981                   if not From_Aspect_Specification (N) then
4982                      while Present (Homonym (Subp))
4983                        and then Scope (Homonym (Subp)) = Current_Scope
4984                      loop
4985                         Make_Inline (Homonym (Subp));
4986                         Subp := Homonym (Subp);
4987                      end loop;
4988                   end if;
4989                end if;
4990             end if;
4991
4992             if not Applies then
4993                Error_Pragma_Arg
4994                  ("inappropriate argument for pragma%", Assoc);
4995
4996             elsif not Effective
4997               and then Warn_On_Redundant_Constructs
4998               and then not Suppress_All_Inlining
4999             then
5000                if Inlining_Not_Possible (Subp) then
5001                   Error_Msg_NE
5002                     ("pragma Inline for& is ignored?", N, Entity (Subp_Id));
5003                else
5004                   Error_Msg_NE
5005                     ("pragma Inline for& is redundant?", N, Entity (Subp_Id));
5006                end if;
5007             end if;
5008
5009             Next (Assoc);
5010          end loop;
5011       end Process_Inline;
5012
5013       ----------------------------
5014       -- Process_Interface_Name --
5015       ----------------------------
5016
5017       procedure Process_Interface_Name
5018         (Subprogram_Def : Entity_Id;
5019          Ext_Arg        : Node_Id;
5020          Link_Arg       : Node_Id)
5021       is
5022          Ext_Nam    : Node_Id;
5023          Link_Nam   : Node_Id;
5024          String_Val : String_Id;
5025
5026          procedure Check_Form_Of_Interface_Name
5027            (SN            : Node_Id;
5028             Ext_Name_Case : Boolean);
5029          --  SN is a string literal node for an interface name. This routine
5030          --  performs some minimal checks that the name is reasonable. In
5031          --  particular that no spaces or other obviously incorrect characters
5032          --  appear. This is only a warning, since any characters are allowed.
5033          --  Ext_Name_Case is True for an External_Name, False for a Link_Name.
5034
5035          ----------------------------------
5036          -- Check_Form_Of_Interface_Name --
5037          ----------------------------------
5038
5039          procedure Check_Form_Of_Interface_Name
5040            (SN            : Node_Id;
5041             Ext_Name_Case : Boolean)
5042          is
5043             S  : constant String_Id := Strval (Expr_Value_S (SN));
5044             SL : constant Nat       := String_Length (S);
5045             C  : Char_Code;
5046
5047          begin
5048             if SL = 0 then
5049                Error_Msg_N ("interface name cannot be null string", SN);
5050             end if;
5051
5052             for J in 1 .. SL loop
5053                C := Get_String_Char (S, J);
5054
5055                --  Look for dubious character and issue unconditional warning.
5056                --  Definitely dubious if not in character range.
5057
5058                if not In_Character_Range (C)
5059
5060                   --  For all cases except CLI target,
5061                   --  commas, spaces and slashes are dubious (in CLI, we use
5062                   --  commas and backslashes in external names to specify
5063                   --  assembly version and public key, while slashes and spaces
5064                   --  can be used in names to mark nested classes and
5065                   --  valuetypes).
5066
5067                   or else ((not Ext_Name_Case or else VM_Target /= CLI_Target)
5068                              and then (Get_Character (C) = ','
5069                                          or else
5070                                        Get_Character (C) = '\'))
5071                  or else (VM_Target /= CLI_Target
5072                             and then (Get_Character (C) = ' '
5073                                         or else
5074                                       Get_Character (C) = '/'))
5075                then
5076                   Error_Msg
5077                     ("?interface name contains illegal character",
5078                      Sloc (SN) + Source_Ptr (J));
5079                end if;
5080             end loop;
5081          end Check_Form_Of_Interface_Name;
5082
5083       --  Start of processing for Process_Interface_Name
5084
5085       begin
5086          if No (Link_Arg) then
5087             if No (Ext_Arg) then
5088                if VM_Target = CLI_Target
5089                  and then Ekind (Subprogram_Def) = E_Package
5090                  and then Nkind (Parent (Subprogram_Def)) =
5091                                                  N_Package_Specification
5092                  and then Present (Generic_Parent (Parent (Subprogram_Def)))
5093                then
5094                   Set_Interface_Name
5095                      (Subprogram_Def,
5096                       Interface_Name
5097                         (Generic_Parent (Parent (Subprogram_Def))));
5098                end if;
5099
5100                return;
5101
5102             elsif Chars (Ext_Arg) = Name_Link_Name then
5103                Ext_Nam  := Empty;
5104                Link_Nam := Expression (Ext_Arg);
5105
5106             else
5107                Check_Optional_Identifier (Ext_Arg, Name_External_Name);
5108                Ext_Nam  := Expression (Ext_Arg);
5109                Link_Nam := Empty;
5110             end if;
5111
5112          else
5113             Check_Optional_Identifier (Ext_Arg,  Name_External_Name);
5114             Check_Optional_Identifier (Link_Arg, Name_Link_Name);
5115             Ext_Nam  := Expression (Ext_Arg);
5116             Link_Nam := Expression (Link_Arg);
5117          end if;
5118
5119          --  Check expressions for external name and link name are static
5120
5121          if Present (Ext_Nam) then
5122             Check_Arg_Is_Static_Expression (Ext_Nam, Standard_String);
5123             Check_Form_Of_Interface_Name (Ext_Nam, Ext_Name_Case => True);
5124
5125             --  Verify that external name is not the name of a local entity,
5126             --  which would hide the imported one and could lead to run-time
5127             --  surprises. The problem can only arise for entities declared in
5128             --  a package body (otherwise the external name is fully qualified
5129             --  and will not conflict).
5130
5131             declare
5132                Nam : Name_Id;
5133                E   : Entity_Id;
5134                Par : Node_Id;
5135
5136             begin
5137                if Prag_Id = Pragma_Import then
5138                   String_To_Name_Buffer (Strval (Expr_Value_S (Ext_Nam)));
5139                   Nam := Name_Find;
5140                   E   := Entity_Id (Get_Name_Table_Info (Nam));
5141
5142                   if Nam /= Chars (Subprogram_Def)
5143                     and then Present (E)
5144                     and then not Is_Overloadable (E)
5145                     and then Is_Immediately_Visible (E)
5146                     and then not Is_Imported (E)
5147                     and then Ekind (Scope (E)) = E_Package
5148                   then
5149                      Par := Parent (E);
5150                      while Present (Par) loop
5151                         if Nkind (Par) = N_Package_Body then
5152                            Error_Msg_Sloc := Sloc (E);
5153                            Error_Msg_NE
5154                              ("imported entity is hidden by & declared#",
5155                               Ext_Arg, E);
5156                            exit;
5157                         end if;
5158
5159                         Par := Parent (Par);
5160                      end loop;
5161                   end if;
5162                end if;
5163             end;
5164          end if;
5165
5166          if Present (Link_Nam) then
5167             Check_Arg_Is_Static_Expression (Link_Nam, Standard_String);
5168             Check_Form_Of_Interface_Name (Link_Nam, Ext_Name_Case => False);
5169          end if;
5170
5171          --  If there is no link name, just set the external name
5172
5173          if No (Link_Nam) then
5174             Link_Nam := Adjust_External_Name_Case (Expr_Value_S (Ext_Nam));
5175
5176          --  For the Link_Name case, the given literal is preceded by an
5177          --  asterisk, which indicates to GCC that the given name should be
5178          --  taken literally, and in particular that no prepending of
5179          --  underlines should occur, even in systems where this is the
5180          --  normal default.
5181
5182          else
5183             Start_String;
5184
5185             if VM_Target = No_VM then
5186                Store_String_Char (Get_Char_Code ('*'));
5187             end if;
5188
5189             String_Val := Strval (Expr_Value_S (Link_Nam));
5190             Store_String_Chars (String_Val);
5191             Link_Nam :=
5192               Make_String_Literal (Sloc (Link_Nam),
5193                 Strval => End_String);
5194          end if;
5195
5196          --  Set the interface name. If the entity is a generic instance, use
5197          --  its alias, which is the callable entity.
5198
5199          if Is_Generic_Instance (Subprogram_Def) then
5200             Set_Encoded_Interface_Name
5201               (Alias (Get_Base_Subprogram (Subprogram_Def)), Link_Nam);
5202          else
5203             Set_Encoded_Interface_Name
5204               (Get_Base_Subprogram (Subprogram_Def), Link_Nam);
5205          end if;
5206
5207          --  We allow duplicated export names in CIL/Java, as they are always
5208          --  enclosed in a namespace that differentiates them, and overloaded
5209          --  entities are supported by the VM.
5210
5211          if Convention (Subprogram_Def) /= Convention_CIL
5212               and then
5213             Convention (Subprogram_Def) /= Convention_Java
5214          then
5215             Check_Duplicated_Export_Name (Link_Nam);
5216          end if;
5217       end Process_Interface_Name;
5218
5219       -----------------------------------------
5220       -- Process_Interrupt_Or_Attach_Handler --
5221       -----------------------------------------
5222
5223       procedure Process_Interrupt_Or_Attach_Handler is
5224          Arg1_X       : constant Node_Id   := Get_Pragma_Arg (Arg1);
5225          Handler_Proc : constant Entity_Id := Entity (Arg1_X);
5226          Proc_Scope   : constant Entity_Id := Scope (Handler_Proc);
5227
5228       begin
5229          Set_Is_Interrupt_Handler (Handler_Proc);
5230
5231          --  If the pragma is not associated with a handler procedure within a
5232          --  protected type, then it must be for a nonprotected procedure for
5233          --  the AAMP target, in which case we don't associate a representation
5234          --  item with the procedure's scope.
5235
5236          if Ekind (Proc_Scope) = E_Protected_Type then
5237             if Prag_Id = Pragma_Interrupt_Handler
5238                  or else
5239                Prag_Id = Pragma_Attach_Handler
5240             then
5241                Record_Rep_Item (Proc_Scope, N);
5242             end if;
5243          end if;
5244       end Process_Interrupt_Or_Attach_Handler;
5245
5246       --------------------------------------------------
5247       -- Process_Restrictions_Or_Restriction_Warnings --
5248       --------------------------------------------------
5249
5250       --  Note: some of the simple identifier cases were handled in par-prag,
5251       --  but it is harmless (and more straightforward) to simply handle all
5252       --  cases here, even if it means we repeat a bit of work in some cases.
5253
5254       procedure Process_Restrictions_Or_Restriction_Warnings
5255         (Warn : Boolean)
5256       is
5257          Arg   : Node_Id;
5258          R_Id  : Restriction_Id;
5259          Id    : Name_Id;
5260          Expr  : Node_Id;
5261          Val   : Uint;
5262
5263          procedure Check_Unit_Name (N : Node_Id);
5264          --  Checks unit name parameter for No_Dependence. Returns if it has
5265          --  an appropriate form, otherwise raises pragma argument error.
5266
5267          ---------------------
5268          -- Check_Unit_Name --
5269          ---------------------
5270
5271          procedure Check_Unit_Name (N : Node_Id) is
5272          begin
5273             if Nkind (N) = N_Selected_Component then
5274                Check_Unit_Name (Prefix (N));
5275                Check_Unit_Name (Selector_Name (N));
5276
5277             elsif Nkind (N) = N_Identifier then
5278                return;
5279
5280             else
5281                Error_Pragma_Arg
5282                  ("wrong form for unit name for No_Dependence", N);
5283             end if;
5284          end Check_Unit_Name;
5285
5286       --  Start of processing for Process_Restrictions_Or_Restriction_Warnings
5287
5288       begin
5289          --  Ignore all Restrictions pragma in CodePeer mode
5290
5291          if CodePeer_Mode then
5292             return;
5293          end if;
5294
5295          Check_Ada_83_Warning;
5296          Check_At_Least_N_Arguments (1);
5297          Check_Valid_Configuration_Pragma;
5298
5299          Arg := Arg1;
5300          while Present (Arg) loop
5301             Id := Chars (Arg);
5302             Expr := Get_Pragma_Arg (Arg);
5303
5304             --  Case of no restriction identifier present
5305
5306             if Id = No_Name then
5307                if Nkind (Expr) /= N_Identifier then
5308                   Error_Pragma_Arg
5309                     ("invalid form for restriction", Arg);
5310                end if;
5311
5312                R_Id :=
5313                  Get_Restriction_Id
5314                    (Process_Restriction_Synonyms (Expr));
5315
5316                if R_Id not in All_Boolean_Restrictions then
5317                   Error_Msg_Name_1 := Pname;
5318                   Error_Msg_N
5319                     ("invalid restriction identifier&", Get_Pragma_Arg (Arg));
5320
5321                   --  Check for possible misspelling
5322
5323                   for J in Restriction_Id loop
5324                      declare
5325                         Rnm : constant String := Restriction_Id'Image (J);
5326
5327                      begin
5328                         Name_Buffer (1 .. Rnm'Length) := Rnm;
5329                         Name_Len := Rnm'Length;
5330                         Set_Casing (All_Lower_Case);
5331
5332                         if Is_Bad_Spelling_Of (Chars (Expr), Name_Enter) then
5333                            Set_Casing
5334                              (Identifier_Casing (Current_Source_File));
5335                            Error_Msg_String (1 .. Rnm'Length) :=
5336                              Name_Buffer (1 .. Name_Len);
5337                            Error_Msg_Strlen := Rnm'Length;
5338                            Error_Msg_N -- CODEFIX
5339                              ("\possible misspelling of ""~""",
5340                               Get_Pragma_Arg (Arg));
5341                            exit;
5342                         end if;
5343                      end;
5344                   end loop;
5345
5346                   raise Pragma_Exit;
5347                end if;
5348
5349                if Implementation_Restriction (R_Id) then
5350                   Check_Restriction (No_Implementation_Restrictions, Arg);
5351                end if;
5352
5353                --  Special processing for No_Elaboration_Code restriction
5354
5355                if R_Id = No_Elaboration_Code then
5356
5357                   --  Restriction is only recognized within a configuration
5358                   --  pragma file, or within a unit of the main extended
5359                   --  program. Note: the test for Main_Unit is needed to
5360                   --  properly include the case of configuration pragma files.
5361
5362                   if not (Current_Sem_Unit = Main_Unit
5363                            or else In_Extended_Main_Source_Unit (N))
5364                   then
5365                      return;
5366
5367                   --  Don't allow in a subunit unless already specified in
5368                   --  body or spec.
5369
5370                   elsif Nkind (Parent (N)) = N_Compilation_Unit
5371                     and then Nkind (Unit (Parent (N))) = N_Subunit
5372                     and then not Restriction_Active (No_Elaboration_Code)
5373                   then
5374                      Error_Msg_N
5375                        ("invalid specification of ""No_Elaboration_Code""",
5376                         N);
5377                      Error_Msg_N
5378                        ("\restriction cannot be specified in a subunit", N);
5379                      Error_Msg_N
5380                        ("\unless also specified in body or spec", N);
5381                      return;
5382
5383                   --  If we have a No_Elaboration_Code pragma that we
5384                   --  accept, then it needs to be added to the configuration
5385                   --  restrcition set so that we get proper application to
5386                   --  other units in the main extended source as required.
5387
5388                   else
5389                      Add_To_Config_Boolean_Restrictions (No_Elaboration_Code);
5390                   end if;
5391                end if;
5392
5393                --  If this is a warning, then set the warning unless we already
5394                --  have a real restriction active (we never want a warning to
5395                --  override a real restriction).
5396
5397                if Warn then
5398                   if not Restriction_Active (R_Id) then
5399                      Set_Restriction (R_Id, N);
5400                      Restriction_Warnings (R_Id) := True;
5401                   end if;
5402
5403                --  If real restriction case, then set it and make sure that the
5404                --  restriction warning flag is off, since a real restriction
5405                --  always overrides a warning.
5406
5407                else
5408                   Set_Restriction (R_Id, N);
5409                   Restriction_Warnings (R_Id) := False;
5410                end if;
5411
5412                --  Check for obsolescent restrictions in Ada 2005 mode
5413
5414                if not Warn
5415                  and then Ada_Version >= Ada_2005
5416                  and then (R_Id = No_Asynchronous_Control
5417                             or else
5418                            R_Id = No_Unchecked_Deallocation
5419                             or else
5420                            R_Id = No_Unchecked_Conversion)
5421                then
5422                   Check_Restriction (No_Obsolescent_Features, N);
5423                end if;
5424
5425                --  A very special case that must be processed here: pragma
5426                --  Restrictions (No_Exceptions) turns off all run-time
5427                --  checking. This is a bit dubious in terms of the formal
5428                --  language definition, but it is what is intended by RM
5429                --  H.4(12). Restriction_Warnings never affects generated code
5430                --  so this is done only in the real restriction case.
5431
5432                --  Atomic_Synchronization is not a real check, so it is not
5433                --  affected by this processing).
5434
5435                if R_Id = No_Exceptions and then not Warn then
5436                   for J in Scope_Suppress'Range loop
5437                      if J /= Atomic_Synchronization then
5438                         Scope_Suppress (J) := True;
5439                      end if;
5440                   end loop;
5441                end if;
5442
5443             --  Case of No_Dependence => unit-name. Note that the parser
5444             --  already made the necessary entry in the No_Dependence table.
5445
5446             elsif Id = Name_No_Dependence then
5447                Check_Unit_Name (Expr);
5448
5449             --  Case of No_Specification_Of_Aspect => Identifier.
5450
5451             elsif Id = Name_No_Specification_Of_Aspect then
5452                declare
5453                   A_Id : Aspect_Id;
5454
5455                begin
5456                   if Nkind (Expr) /= N_Identifier then
5457                      A_Id := No_Aspect;
5458                   else
5459                      A_Id := Get_Aspect_Id (Chars (Expr));
5460                   end if;
5461
5462                   if A_Id = No_Aspect then
5463                      Error_Pragma_Arg ("invalid restriction name", Arg);
5464                   else
5465                      Set_Restriction_No_Specification_Of_Aspect (Expr, Warn);
5466                   end if;
5467                end;
5468
5469             --  All other cases of restriction identifier present
5470
5471             else
5472                R_Id := Get_Restriction_Id (Process_Restriction_Synonyms (Arg));
5473                Analyze_And_Resolve (Expr, Any_Integer);
5474
5475                if R_Id not in All_Parameter_Restrictions then
5476                   Error_Pragma_Arg
5477                     ("invalid restriction parameter identifier", Arg);
5478
5479                elsif not Is_OK_Static_Expression (Expr) then
5480                   Flag_Non_Static_Expr
5481                     ("value must be static expression!", Expr);
5482                   raise Pragma_Exit;
5483
5484                elsif not Is_Integer_Type (Etype (Expr))
5485                  or else Expr_Value (Expr) < 0
5486                then
5487                   Error_Pragma_Arg
5488                     ("value must be non-negative integer", Arg);
5489                end if;
5490
5491                --  Restriction pragma is active
5492
5493                Val := Expr_Value (Expr);
5494
5495                if not UI_Is_In_Int_Range (Val) then
5496                   Error_Pragma_Arg
5497                     ("pragma ignored, value too large?", Arg);
5498                end if;
5499
5500                --  Warning case. If the real restriction is active, then we
5501                --  ignore the request, since warning never overrides a real
5502                --  restriction. Otherwise we set the proper warning. Note that
5503                --  this circuit sets the warning again if it is already set,
5504                --  which is what we want, since the constant may have changed.
5505
5506                if Warn then
5507                   if not Restriction_Active (R_Id) then
5508                      Set_Restriction
5509                        (R_Id, N, Integer (UI_To_Int (Val)));
5510                      Restriction_Warnings (R_Id) := True;
5511                   end if;
5512
5513                --  Real restriction case, set restriction and make sure warning
5514                --  flag is off since real restriction always overrides warning.
5515
5516                else
5517                   Set_Restriction (R_Id, N, Integer (UI_To_Int (Val)));
5518                   Restriction_Warnings (R_Id) := False;
5519                end if;
5520             end if;
5521
5522             Next (Arg);
5523          end loop;
5524       end Process_Restrictions_Or_Restriction_Warnings;
5525
5526       ---------------------------------
5527       -- Process_Suppress_Unsuppress --
5528       ---------------------------------
5529
5530       --  Note: this procedure makes entries in the check suppress data
5531       --  structures managed by Sem. See spec of package Sem for full
5532       --  details on how we handle recording of check suppression.
5533
5534       procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean) is
5535          C    : Check_Id;
5536          E_Id : Node_Id;
5537          E    : Entity_Id;
5538
5539          In_Package_Spec : constant Boolean :=
5540                              Is_Package_Or_Generic_Package (Current_Scope)
5541                                and then not In_Package_Body (Current_Scope);
5542
5543          procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id);
5544          --  Used to suppress a single check on the given entity
5545
5546          --------------------------------
5547          -- Suppress_Unsuppress_Echeck --
5548          --------------------------------
5549
5550          procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id) is
5551          begin
5552             --  Check for error of trying to set atomic synchronization for
5553             --  a non-atomic variable.
5554
5555             if C = Atomic_Synchronization
5556               and then not (Is_Atomic (E) or else Has_Atomic_Components (E))
5557             then
5558                Error_Msg_N
5559                  ("pragma & requires atomic type or variable",
5560                   Pragma_Identifier (Original_Node (N)));
5561             end if;
5562
5563             Set_Checks_May_Be_Suppressed (E);
5564
5565             if In_Package_Spec then
5566                Push_Global_Suppress_Stack_Entry
5567                  (Entity   => E,
5568                   Check    => C,
5569                   Suppress => Suppress_Case);
5570             else
5571                Push_Local_Suppress_Stack_Entry
5572                  (Entity   => E,
5573                   Check    => C,
5574                   Suppress => Suppress_Case);
5575             end if;
5576
5577             --  If this is a first subtype, and the base type is distinct,
5578             --  then also set the suppress flags on the base type.
5579
5580             if Is_First_Subtype (E)
5581               and then Etype (E) /= E
5582             then
5583                Suppress_Unsuppress_Echeck (Etype (E), C);
5584             end if;
5585          end Suppress_Unsuppress_Echeck;
5586
5587       --  Start of processing for Process_Suppress_Unsuppress
5588
5589       begin
5590          --  Ignore pragma Suppress/Unsuppress in CodePeer and Alfa modes on
5591          --  user code: we want to generate checks for analysis purposes, as
5592          --  set respectively by -gnatC and -gnatd.F
5593
5594          if (CodePeer_Mode or Alfa_Mode)
5595            and then Comes_From_Source (N)
5596          then
5597             return;
5598          end if;
5599
5600          --  Suppress/Unsuppress can appear as a configuration pragma, or in a
5601          --  declarative part or a package spec (RM 11.5(5)).
5602
5603          if not Is_Configuration_Pragma then
5604             Check_Is_In_Decl_Part_Or_Package_Spec;
5605          end if;
5606
5607          Check_At_Least_N_Arguments (1);
5608          Check_At_Most_N_Arguments (2);
5609          Check_No_Identifier (Arg1);
5610          Check_Arg_Is_Identifier (Arg1);
5611
5612          C := Get_Check_Id (Chars (Get_Pragma_Arg (Arg1)));
5613
5614          if C = No_Check_Id then
5615             Error_Pragma_Arg
5616               ("argument of pragma% is not valid check name", Arg1);
5617          end if;
5618
5619          if not Suppress_Case
5620            and then (C = All_Checks or else C = Overflow_Check)
5621          then
5622             Opt.Overflow_Checks_Unsuppressed := True;
5623          end if;
5624
5625          if Arg_Count = 1 then
5626
5627             --  Make an entry in the local scope suppress table. This is the
5628             --  table that directly shows the current value of the scope
5629             --  suppress check for any check id value.
5630
5631             if C = All_Checks then
5632
5633                --  For All_Checks, we set all specific predefined checks with
5634                --  the exception of Elaboration_Check, which is handled
5635                --  specially because of not wanting All_Checks to have the
5636                --  effect of deactivating static elaboration order processing.
5637                --  Atomic_Synchronization is also not affected, since this is
5638                --  not a real check.
5639
5640                for J in Scope_Suppress'Range loop
5641                   if J /= Elaboration_Check
5642                     and then J /= Atomic_Synchronization
5643                   then
5644                      Scope_Suppress (J) := Suppress_Case;
5645                   end if;
5646                end loop;
5647
5648             --  If not All_Checks, and predefined check, then set appropriate
5649             --  scope entry. Note that we will set Elaboration_Check if this
5650             --  is explicitly specified. Atomic_Synchronization is allowed
5651             --  only if internally generated and entity is atomic.
5652
5653             elsif C in Predefined_Check_Id
5654               and then (not Comes_From_Source (N)
5655                          or else C /= Atomic_Synchronization)
5656             then
5657                Scope_Suppress (C) := Suppress_Case;
5658             end if;
5659
5660             --  Also make an entry in the Local_Entity_Suppress table
5661
5662             Push_Local_Suppress_Stack_Entry
5663               (Entity   => Empty,
5664                Check    => C,
5665                Suppress => Suppress_Case);
5666
5667          --  Case of two arguments present, where the check is suppressed for
5668          --  a specified entity (given as the second argument of the pragma)
5669
5670          else
5671             --  This is obsolescent in Ada 2005 mode
5672
5673             if Ada_Version >= Ada_2005 then
5674                Check_Restriction (No_Obsolescent_Features, Arg2);
5675             end if;
5676
5677             Check_Optional_Identifier (Arg2, Name_On);
5678             E_Id := Get_Pragma_Arg (Arg2);
5679             Analyze (E_Id);
5680
5681             if not Is_Entity_Name (E_Id) then
5682                Error_Pragma_Arg
5683                  ("second argument of pragma% must be entity name", Arg2);
5684             end if;
5685
5686             E := Entity (E_Id);
5687
5688             if E = Any_Id then
5689                return;
5690             end if;
5691
5692             --  Enforce RM 11.5(7) which requires that for a pragma that
5693             --  appears within a package spec, the named entity must be
5694             --  within the package spec. We allow the package name itself
5695             --  to be mentioned since that makes sense, although it is not
5696             --  strictly allowed by 11.5(7).
5697
5698             if In_Package_Spec
5699               and then E /= Current_Scope
5700               and then Scope (E) /= Current_Scope
5701             then
5702                Error_Pragma_Arg
5703                  ("entity in pragma% is not in package spec (RM 11.5(7))",
5704                   Arg2);
5705             end if;
5706
5707             --  Loop through homonyms. As noted below, in the case of a package
5708             --  spec, only homonyms within the package spec are considered.
5709
5710             loop
5711                Suppress_Unsuppress_Echeck (E, C);
5712
5713                if Is_Generic_Instance (E)
5714                  and then Is_Subprogram (E)
5715                  and then Present (Alias (E))
5716                then
5717                   Suppress_Unsuppress_Echeck (Alias (E), C);
5718                end if;
5719
5720                --  Move to next homonym if not aspect spec case
5721
5722                exit when From_Aspect_Specification (N);
5723                E := Homonym (E);
5724                exit when No (E);
5725
5726                --  If we are within a package specification, the pragma only
5727                --  applies to homonyms in the same scope.
5728
5729                exit when In_Package_Spec
5730                  and then Scope (E) /= Current_Scope;
5731             end loop;
5732          end if;
5733       end Process_Suppress_Unsuppress;
5734
5735       ------------------
5736       -- Set_Exported --
5737       ------------------
5738
5739       procedure Set_Exported (E : Entity_Id; Arg : Node_Id) is
5740       begin
5741          if Is_Imported (E) then
5742             Error_Pragma_Arg
5743               ("cannot export entity& that was previously imported", Arg);
5744
5745          elsif Present (Address_Clause (E)) and then not CodePeer_Mode then
5746             Error_Pragma_Arg
5747               ("cannot export entity& that has an address clause", Arg);
5748          end if;
5749
5750          Set_Is_Exported (E);
5751
5752          --  Generate a reference for entity explicitly, because the
5753          --  identifier may be overloaded and name resolution will not
5754          --  generate one.
5755
5756          Generate_Reference (E, Arg);
5757
5758          --  Deal with exporting non-library level entity
5759
5760          if not Is_Library_Level_Entity (E) then
5761
5762             --  Not allowed at all for subprograms
5763
5764             if Is_Subprogram (E) then
5765                Error_Pragma_Arg ("local subprogram& cannot be exported", Arg);
5766
5767             --  Otherwise set public and statically allocated
5768
5769             else
5770                Set_Is_Public (E);
5771                Set_Is_Statically_Allocated (E);
5772
5773                --  Warn if the corresponding W flag is set and the pragma comes
5774                --  from source. The latter may not be true e.g. on VMS where we
5775                --  expand export pragmas for exception codes associated with
5776                --  imported or exported exceptions. We do not want to generate
5777                --  a warning for something that the user did not write.
5778
5779                if Warn_On_Export_Import
5780                  and then Comes_From_Source (Arg)
5781                then
5782                   Error_Msg_NE
5783                     ("?& has been made static as a result of Export", Arg, E);
5784                   Error_Msg_N
5785                     ("\this usage is non-standard and non-portable", Arg);
5786                end if;
5787             end if;
5788          end if;
5789
5790          if Warn_On_Export_Import and then Is_Type (E) then
5791             Error_Msg_NE ("exporting a type has no effect?", Arg, E);
5792          end if;
5793
5794          if Warn_On_Export_Import and Inside_A_Generic then
5795             Error_Msg_NE
5796               ("all instances of& will have the same external name?", Arg, E);
5797          end if;
5798       end Set_Exported;
5799
5800       ----------------------------------------------
5801       -- Set_Extended_Import_Export_External_Name --
5802       ----------------------------------------------
5803
5804       procedure Set_Extended_Import_Export_External_Name
5805         (Internal_Ent : Entity_Id;
5806          Arg_External : Node_Id)
5807       is
5808          Old_Name : constant Node_Id := Interface_Name (Internal_Ent);
5809          New_Name : Node_Id;
5810
5811       begin
5812          if No (Arg_External) then
5813             return;
5814          end if;
5815
5816          Check_Arg_Is_External_Name (Arg_External);
5817
5818          if Nkind (Arg_External) = N_String_Literal then
5819             if String_Length (Strval (Arg_External)) = 0 then
5820                return;
5821             else
5822                New_Name := Adjust_External_Name_Case (Arg_External);
5823             end if;
5824
5825          elsif Nkind (Arg_External) = N_Identifier then
5826             New_Name := Get_Default_External_Name (Arg_External);
5827
5828          --  Check_Arg_Is_External_Name should let through only identifiers and
5829          --  string literals or static string expressions (which are folded to
5830          --  string literals).
5831
5832          else
5833             raise Program_Error;
5834          end if;
5835
5836          --  If we already have an external name set (by a prior normal Import
5837          --  or Export pragma), then the external names must match
5838
5839          if Present (Interface_Name (Internal_Ent)) then
5840             Check_Matching_Internal_Names : declare
5841                S1 : constant String_Id := Strval (Old_Name);
5842                S2 : constant String_Id := Strval (New_Name);
5843
5844                procedure Mismatch;
5845                --  Called if names do not match
5846
5847                --------------
5848                -- Mismatch --
5849                --------------
5850
5851                procedure Mismatch is
5852                begin
5853                   Error_Msg_Sloc := Sloc (Old_Name);
5854                   Error_Pragma_Arg
5855                     ("external name does not match that given #",
5856                      Arg_External);
5857                end Mismatch;
5858
5859             --  Start of processing for Check_Matching_Internal_Names
5860
5861             begin
5862                if String_Length (S1) /= String_Length (S2) then
5863                   Mismatch;
5864
5865                else
5866                   for J in 1 .. String_Length (S1) loop
5867                      if Get_String_Char (S1, J) /= Get_String_Char (S2, J) then
5868                         Mismatch;
5869                      end if;
5870                   end loop;
5871                end if;
5872             end Check_Matching_Internal_Names;
5873
5874          --  Otherwise set the given name
5875
5876          else
5877             Set_Encoded_Interface_Name (Internal_Ent, New_Name);
5878             Check_Duplicated_Export_Name (New_Name);
5879          end if;
5880       end Set_Extended_Import_Export_External_Name;
5881
5882       ------------------
5883       -- Set_Imported --
5884       ------------------
5885
5886       procedure Set_Imported (E : Entity_Id) is
5887       begin
5888          --  Error message if already imported or exported
5889
5890          if Is_Exported (E) or else Is_Imported (E) then
5891
5892             --  Error if being set Exported twice
5893
5894             if Is_Exported (E) then
5895                Error_Msg_NE ("entity& was previously exported", N, E);
5896
5897             --  OK if Import/Interface case
5898
5899             elsif Import_Interface_Present (N) then
5900                goto OK;
5901
5902             --  Error if being set Imported twice
5903
5904             else
5905                Error_Msg_NE ("entity& was previously imported", N, E);
5906             end if;
5907
5908             Error_Msg_Name_1 := Pname;
5909             Error_Msg_N
5910               ("\(pragma% applies to all previous entities)", N);
5911
5912             Error_Msg_Sloc  := Sloc (E);
5913             Error_Msg_NE ("\import not allowed for& declared#", N, E);
5914
5915          --  Here if not previously imported or exported, OK to import
5916
5917          else
5918             Set_Is_Imported (E);
5919
5920             --  If the entity is an object that is not at the library level,
5921             --  then it is statically allocated. We do not worry about objects
5922             --  with address clauses in this context since they are not really
5923             --  imported in the linker sense.
5924
5925             if Is_Object (E)
5926               and then not Is_Library_Level_Entity (E)
5927               and then No (Address_Clause (E))
5928             then
5929                Set_Is_Statically_Allocated (E);
5930             end if;
5931          end if;
5932
5933          <<OK>> null;
5934       end Set_Imported;
5935
5936       -------------------------
5937       -- Set_Mechanism_Value --
5938       -------------------------
5939
5940       --  Note: the mechanism name has not been analyzed (and cannot indeed be
5941       --  analyzed, since it is semantic nonsense), so we get it in the exact
5942       --  form created by the parser.
5943
5944       procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id) is
5945          Class        : Node_Id;
5946          Param        : Node_Id;
5947          Mech_Name_Id : Name_Id;
5948
5949          procedure Bad_Class;
5950          --  Signal bad descriptor class name
5951
5952          procedure Bad_Mechanism;
5953          --  Signal bad mechanism name
5954
5955          ---------------
5956          -- Bad_Class --
5957          ---------------
5958
5959          procedure Bad_Class is
5960          begin
5961             Error_Pragma_Arg ("unrecognized descriptor class name", Class);
5962          end Bad_Class;
5963
5964          -------------------------
5965          -- Bad_Mechanism_Value --
5966          -------------------------
5967
5968          procedure Bad_Mechanism is
5969          begin
5970             Error_Pragma_Arg ("unrecognized mechanism name", Mech_Name);
5971          end Bad_Mechanism;
5972
5973       --  Start of processing for Set_Mechanism_Value
5974
5975       begin
5976          if Mechanism (Ent) /= Default_Mechanism then
5977             Error_Msg_NE
5978               ("mechanism for & has already been set", Mech_Name, Ent);
5979          end if;
5980
5981          --  MECHANISM_NAME ::= value | reference | descriptor |
5982          --                     short_descriptor
5983
5984          if Nkind (Mech_Name) = N_Identifier then
5985             if Chars (Mech_Name) = Name_Value then
5986                Set_Mechanism (Ent, By_Copy);
5987                return;
5988
5989             elsif Chars (Mech_Name) = Name_Reference then
5990                Set_Mechanism (Ent, By_Reference);
5991                return;
5992
5993             elsif Chars (Mech_Name) = Name_Descriptor then
5994                Check_VMS (Mech_Name);
5995
5996                --  Descriptor => Short_Descriptor if pragma was given
5997
5998                if Short_Descriptors then
5999                   Set_Mechanism (Ent, By_Short_Descriptor);
6000                else
6001                   Set_Mechanism (Ent, By_Descriptor);
6002                end if;
6003
6004                return;
6005
6006             elsif Chars (Mech_Name) = Name_Short_Descriptor then
6007                Check_VMS (Mech_Name);
6008                Set_Mechanism (Ent, By_Short_Descriptor);
6009                return;
6010
6011             elsif Chars (Mech_Name) = Name_Copy then
6012                Error_Pragma_Arg
6013                  ("bad mechanism name, Value assumed", Mech_Name);
6014
6015             else
6016                Bad_Mechanism;
6017             end if;
6018
6019          --  MECHANISM_NAME ::= descriptor (CLASS_NAME) |
6020          --                     short_descriptor (CLASS_NAME)
6021          --  CLASS_NAME     ::= ubs | ubsb | uba | s | sb | a | nca
6022
6023          --  Note: this form is parsed as an indexed component
6024
6025          elsif Nkind (Mech_Name) = N_Indexed_Component then
6026             Class := First (Expressions (Mech_Name));
6027
6028             if Nkind (Prefix (Mech_Name)) /= N_Identifier
6029              or else not (Chars (Prefix (Mech_Name)) = Name_Descriptor or else
6030                           Chars (Prefix (Mech_Name)) = Name_Short_Descriptor)
6031              or else Present (Next (Class))
6032             then
6033                Bad_Mechanism;
6034             else
6035                Mech_Name_Id := Chars (Prefix (Mech_Name));
6036
6037                --  Change Descriptor => Short_Descriptor if pragma was given
6038
6039                if Mech_Name_Id = Name_Descriptor
6040                  and then Short_Descriptors
6041                then
6042                   Mech_Name_Id := Name_Short_Descriptor;
6043                end if;
6044             end if;
6045
6046          --  MECHANISM_NAME ::= descriptor (Class => CLASS_NAME) |
6047          --                     short_descriptor (Class => CLASS_NAME)
6048          --  CLASS_NAME     ::= ubs | ubsb | uba | s | sb | a | nca
6049
6050          --  Note: this form is parsed as a function call
6051
6052          elsif Nkind (Mech_Name) = N_Function_Call then
6053             Param := First (Parameter_Associations (Mech_Name));
6054
6055             if Nkind (Name (Mech_Name)) /= N_Identifier
6056               or else not (Chars (Name (Mech_Name)) = Name_Descriptor or else
6057                            Chars (Name (Mech_Name)) = Name_Short_Descriptor)
6058               or else Present (Next (Param))
6059               or else No (Selector_Name (Param))
6060               or else Chars (Selector_Name (Param)) /= Name_Class
6061             then
6062                Bad_Mechanism;
6063             else
6064                Class := Explicit_Actual_Parameter (Param);
6065                Mech_Name_Id := Chars (Name (Mech_Name));
6066             end if;
6067
6068          else
6069             Bad_Mechanism;
6070          end if;
6071
6072          --  Fall through here with Class set to descriptor class name
6073
6074          Check_VMS (Mech_Name);
6075
6076          if Nkind (Class) /= N_Identifier then
6077             Bad_Class;
6078
6079          elsif Mech_Name_Id = Name_Descriptor
6080            and then Chars (Class) = Name_UBS
6081          then
6082             Set_Mechanism (Ent, By_Descriptor_UBS);
6083
6084          elsif Mech_Name_Id = Name_Descriptor
6085            and then Chars (Class) = Name_UBSB
6086          then
6087             Set_Mechanism (Ent, By_Descriptor_UBSB);
6088
6089          elsif Mech_Name_Id = Name_Descriptor
6090            and then Chars (Class) = Name_UBA
6091          then
6092             Set_Mechanism (Ent, By_Descriptor_UBA);
6093
6094          elsif Mech_Name_Id = Name_Descriptor
6095            and then Chars (Class) = Name_S
6096          then
6097             Set_Mechanism (Ent, By_Descriptor_S);
6098
6099          elsif Mech_Name_Id = Name_Descriptor
6100            and then Chars (Class) = Name_SB
6101          then
6102             Set_Mechanism (Ent, By_Descriptor_SB);
6103
6104          elsif Mech_Name_Id = Name_Descriptor
6105            and then Chars (Class) = Name_A
6106          then
6107             Set_Mechanism (Ent, By_Descriptor_A);
6108
6109          elsif Mech_Name_Id = Name_Descriptor
6110            and then Chars (Class) = Name_NCA
6111          then
6112             Set_Mechanism (Ent, By_Descriptor_NCA);
6113
6114          elsif Mech_Name_Id = Name_Short_Descriptor
6115            and then Chars (Class) = Name_UBS
6116          then
6117             Set_Mechanism (Ent, By_Short_Descriptor_UBS);
6118
6119          elsif Mech_Name_Id = Name_Short_Descriptor
6120            and then Chars (Class) = Name_UBSB
6121          then
6122             Set_Mechanism (Ent, By_Short_Descriptor_UBSB);
6123
6124          elsif Mech_Name_Id = Name_Short_Descriptor
6125            and then Chars (Class) = Name_UBA
6126          then
6127             Set_Mechanism (Ent, By_Short_Descriptor_UBA);
6128
6129          elsif Mech_Name_Id = Name_Short_Descriptor
6130            and then Chars (Class) = Name_S
6131          then
6132             Set_Mechanism (Ent, By_Short_Descriptor_S);
6133
6134          elsif Mech_Name_Id = Name_Short_Descriptor
6135            and then Chars (Class) = Name_SB
6136          then
6137             Set_Mechanism (Ent, By_Short_Descriptor_SB);
6138
6139          elsif Mech_Name_Id = Name_Short_Descriptor
6140            and then Chars (Class) = Name_A
6141          then
6142             Set_Mechanism (Ent, By_Short_Descriptor_A);
6143
6144          elsif Mech_Name_Id = Name_Short_Descriptor
6145            and then Chars (Class) = Name_NCA
6146          then
6147             Set_Mechanism (Ent, By_Short_Descriptor_NCA);
6148
6149          else
6150             Bad_Class;
6151          end if;
6152       end Set_Mechanism_Value;
6153
6154       ---------------------------
6155       -- Set_Ravenscar_Profile --
6156       ---------------------------
6157
6158       --  The tasks to be done here are
6159
6160       --    Set required policies
6161
6162       --      pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
6163       --      pragma Locking_Policy (Ceiling_Locking)
6164
6165       --    Set Detect_Blocking mode
6166
6167       --    Set required restrictions (see System.Rident for detailed list)
6168
6169       --    Set the No_Dependence rules
6170       --      No_Dependence => Ada.Asynchronous_Task_Control
6171       --      No_Dependence => Ada.Calendar
6172       --      No_Dependence => Ada.Execution_Time.Group_Budget
6173       --      No_Dependence => Ada.Execution_Time.Timers
6174       --      No_Dependence => Ada.Task_Attributes
6175       --      No_Dependence => System.Multiprocessors.Dispatching_Domains
6176
6177       procedure Set_Ravenscar_Profile (N : Node_Id) is
6178          Prefix_Entity   : Entity_Id;
6179          Selector_Entity : Entity_Id;
6180          Prefix_Node     : Node_Id;
6181          Node            : Node_Id;
6182
6183       begin
6184          --  pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
6185
6186          if Task_Dispatching_Policy /= ' '
6187            and then Task_Dispatching_Policy /= 'F'
6188          then
6189             Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
6190             Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
6191
6192          --  Set the FIFO_Within_Priorities policy, but always preserve
6193          --  System_Location since we like the error message with the run time
6194          --  name.
6195
6196          else
6197             Task_Dispatching_Policy := 'F';
6198
6199             if Task_Dispatching_Policy_Sloc /= System_Location then
6200                Task_Dispatching_Policy_Sloc := Loc;
6201             end if;
6202          end if;
6203
6204          --  pragma Locking_Policy (Ceiling_Locking)
6205
6206          if Locking_Policy /= ' '
6207            and then Locking_Policy /= 'C'
6208          then
6209             Error_Msg_Sloc := Locking_Policy_Sloc;
6210             Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
6211
6212          --  Set the Ceiling_Locking policy, but preserve System_Location since
6213          --  we like the error message with the run time name.
6214
6215          else
6216             Locking_Policy := 'C';
6217
6218             if Locking_Policy_Sloc /= System_Location then
6219                Locking_Policy_Sloc := Loc;
6220             end if;
6221          end if;
6222
6223          --  pragma Detect_Blocking
6224
6225          Detect_Blocking := True;
6226
6227          --  Set the corresponding restrictions
6228
6229          Set_Profile_Restrictions
6230            (Ravenscar, N, Warn => Treat_Restrictions_As_Warnings);
6231
6232          --  Set the No_Dependence restrictions
6233
6234          --  The following No_Dependence restrictions:
6235          --    No_Dependence => Ada.Asynchronous_Task_Control
6236          --    No_Dependence => Ada.Calendar
6237          --    No_Dependence => Ada.Task_Attributes
6238          --  are already set by previous call to Set_Profile_Restrictions.
6239
6240          --  Set the following restrictions which were added to Ada 2005:
6241          --    No_Dependence => Ada.Execution_Time.Group_Budget
6242          --    No_Dependence => Ada.Execution_Time.Timers
6243
6244          if Ada_Version >= Ada_2005 then
6245             Name_Buffer (1 .. 3) := "ada";
6246             Name_Len := 3;
6247
6248             Prefix_Entity := Make_Identifier (Loc, Name_Find);
6249
6250             Name_Buffer (1 .. 14) := "execution_time";
6251             Name_Len := 14;
6252
6253             Selector_Entity := Make_Identifier (Loc, Name_Find);
6254
6255             Prefix_Node :=
6256               Make_Selected_Component
6257                 (Sloc          => Loc,
6258                  Prefix        => Prefix_Entity,
6259                  Selector_Name => Selector_Entity);
6260
6261             Name_Buffer (1 .. 13) := "group_budgets";
6262             Name_Len := 13;
6263
6264             Selector_Entity := Make_Identifier (Loc, Name_Find);
6265
6266             Node :=
6267               Make_Selected_Component
6268                 (Sloc          => Loc,
6269                  Prefix        => Prefix_Node,
6270                  Selector_Name => Selector_Entity);
6271
6272             Set_Restriction_No_Dependence
6273               (Unit    => Node,
6274                Warn    => Treat_Restrictions_As_Warnings,
6275                Profile => Ravenscar);
6276
6277             Name_Buffer (1 .. 6) := "timers";
6278             Name_Len := 6;
6279
6280             Selector_Entity := Make_Identifier (Loc, Name_Find);
6281
6282             Node :=
6283               Make_Selected_Component
6284                 (Sloc          => Loc,
6285                  Prefix        => Prefix_Node,
6286                  Selector_Name => Selector_Entity);
6287
6288             Set_Restriction_No_Dependence
6289               (Unit    => Node,
6290                Warn    => Treat_Restrictions_As_Warnings,
6291                Profile => Ravenscar);
6292          end if;
6293
6294          --  Set the following restrictions which was added to Ada 2012 (see
6295          --  AI-0171):
6296          --    No_Dependence => System.Multiprocessors.Dispatching_Domains
6297
6298          if Ada_Version >= Ada_2012 then
6299             Name_Buffer (1 .. 6) := "system";
6300             Name_Len := 6;
6301
6302             Prefix_Entity := Make_Identifier (Loc, Name_Find);
6303
6304             Name_Buffer (1 .. 15) := "multiprocessors";
6305             Name_Len := 15;
6306
6307             Selector_Entity := Make_Identifier (Loc, Name_Find);
6308
6309             Prefix_Node :=
6310               Make_Selected_Component
6311                 (Sloc          => Loc,
6312                  Prefix        => Prefix_Entity,
6313                  Selector_Name => Selector_Entity);
6314
6315             Name_Buffer (1 .. 19) := "dispatching_domains";
6316             Name_Len := 19;
6317
6318             Selector_Entity := Make_Identifier (Loc, Name_Find);
6319
6320             Node :=
6321               Make_Selected_Component
6322                 (Sloc          => Loc,
6323                  Prefix        => Prefix_Node,
6324                  Selector_Name => Selector_Entity);
6325
6326             Set_Restriction_No_Dependence
6327               (Unit    => Node,
6328                Warn    => Treat_Restrictions_As_Warnings,
6329                Profile => Ravenscar);
6330          end if;
6331       end Set_Ravenscar_Profile;
6332
6333    --  Start of processing for Analyze_Pragma
6334
6335    begin
6336       --  The following code is a defense against recursion. Not clear that
6337       --  this can happen legitimately, but perhaps some error situations
6338       --  can cause it, and we did see this recursion during testing.
6339
6340       if Analyzed (N) then
6341          return;
6342       else
6343          Set_Analyzed (N, True);
6344       end if;
6345
6346       --  Deal with unrecognized pragma
6347
6348       Pname := Pragma_Name (N);
6349
6350       if not Is_Pragma_Name (Pname) then
6351          if Warn_On_Unrecognized_Pragma then
6352             Error_Msg_Name_1 := Pname;
6353             Error_Msg_N ("?unrecognized pragma%!", Pragma_Identifier (N));
6354
6355             for PN in First_Pragma_Name .. Last_Pragma_Name loop
6356                if Is_Bad_Spelling_Of (Pname, PN) then
6357                   Error_Msg_Name_1 := PN;
6358                   Error_Msg_N -- CODEFIX
6359                     ("\?possible misspelling of %!", Pragma_Identifier (N));
6360                   exit;
6361                end if;
6362             end loop;
6363          end if;
6364
6365          return;
6366       end if;
6367
6368       --  Here to start processing for recognized pragma
6369
6370       Prag_Id := Get_Pragma_Id (Pname);
6371
6372       if Present (Corresponding_Aspect (N)) then
6373          Pname := Chars (Identifier (Corresponding_Aspect (N)));
6374       end if;
6375
6376       --  Preset arguments
6377
6378       Arg_Count := 0;
6379       Arg1      := Empty;
6380       Arg2      := Empty;
6381       Arg3      := Empty;
6382       Arg4      := Empty;
6383
6384       if Present (Pragma_Argument_Associations (N)) then
6385          Arg_Count := List_Length (Pragma_Argument_Associations (N));
6386          Arg1 := First (Pragma_Argument_Associations (N));
6387
6388          if Present (Arg1) then
6389             Arg2 := Next (Arg1);
6390
6391             if Present (Arg2) then
6392                Arg3 := Next (Arg2);
6393
6394                if Present (Arg3) then
6395                   Arg4 := Next (Arg3);
6396                end if;
6397             end if;
6398          end if;
6399       end if;
6400
6401       --  An enumeration type defines the pragmas that are supported by the
6402       --  implementation. Get_Pragma_Id (in package Prag) transforms a name
6403       --  into the corresponding enumeration value for the following case.
6404
6405       case Prag_Id is
6406
6407          -----------------
6408          -- Abort_Defer --
6409          -----------------
6410
6411          --  pragma Abort_Defer;
6412
6413          when Pragma_Abort_Defer =>
6414             GNAT_Pragma;
6415             Check_Arg_Count (0);
6416
6417             --  The only required semantic processing is to check the
6418             --  placement. This pragma must appear at the start of the
6419             --  statement sequence of a handled sequence of statements.
6420
6421             if Nkind (Parent (N)) /= N_Handled_Sequence_Of_Statements
6422               or else N /= First (Statements (Parent (N)))
6423             then
6424                Pragma_Misplaced;
6425             end if;
6426
6427          ------------
6428          -- Ada_83 --
6429          ------------
6430
6431          --  pragma Ada_83;
6432
6433          --  Note: this pragma also has some specific processing in Par.Prag
6434          --  because we want to set the Ada version mode during parsing.
6435
6436          when Pragma_Ada_83 =>
6437             GNAT_Pragma;
6438             Check_Arg_Count (0);
6439
6440             --  We really should check unconditionally for proper configuration
6441             --  pragma placement, since we really don't want mixed Ada modes
6442             --  within a single unit, and the GNAT reference manual has always
6443             --  said this was a configuration pragma, but we did not check and
6444             --  are hesitant to add the check now.
6445
6446             --  However, we really cannot tolerate mixing Ada 2005 or Ada 2012
6447             --  with Ada 83 or Ada 95, so we must check if we are in Ada 2005
6448             --  or Ada 2012 mode.
6449
6450             if Ada_Version >= Ada_2005 then
6451                Check_Valid_Configuration_Pragma;
6452             end if;
6453
6454             --  Now set Ada 83 mode
6455
6456             Ada_Version := Ada_83;
6457             Ada_Version_Explicit := Ada_Version;
6458
6459          ------------
6460          -- Ada_95 --
6461          ------------
6462
6463          --  pragma Ada_95;
6464
6465          --  Note: this pragma also has some specific processing in Par.Prag
6466          --  because we want to set the Ada 83 version mode during parsing.
6467
6468          when Pragma_Ada_95 =>
6469             GNAT_Pragma;
6470             Check_Arg_Count (0);
6471
6472             --  We really should check unconditionally for proper configuration
6473             --  pragma placement, since we really don't want mixed Ada modes
6474             --  within a single unit, and the GNAT reference manual has always
6475             --  said this was a configuration pragma, but we did not check and
6476             --  are hesitant to add the check now.
6477
6478             --  However, we really cannot tolerate mixing Ada 2005 with Ada 83
6479             --  or Ada 95, so we must check if we are in Ada 2005 mode.
6480
6481             if Ada_Version >= Ada_2005 then
6482                Check_Valid_Configuration_Pragma;
6483             end if;
6484
6485             --  Now set Ada 95 mode
6486
6487             Ada_Version := Ada_95;
6488             Ada_Version_Explicit := Ada_Version;
6489
6490          ---------------------
6491          -- Ada_05/Ada_2005 --
6492          ---------------------
6493
6494          --  pragma Ada_05;
6495          --  pragma Ada_05 (LOCAL_NAME);
6496
6497          --  pragma Ada_2005;
6498          --  pragma Ada_2005 (LOCAL_NAME):
6499
6500          --  Note: these pragmas also have some specific processing in Par.Prag
6501          --  because we want to set the Ada 2005 version mode during parsing.
6502
6503          when Pragma_Ada_05 | Pragma_Ada_2005 => declare
6504             E_Id : Node_Id;
6505
6506          begin
6507             GNAT_Pragma;
6508
6509             if Arg_Count = 1 then
6510                Check_Arg_Is_Local_Name (Arg1);
6511                E_Id := Get_Pragma_Arg (Arg1);
6512
6513                if Etype (E_Id) = Any_Type then
6514                   return;
6515                end if;
6516
6517                Set_Is_Ada_2005_Only (Entity (E_Id));
6518
6519             else
6520                Check_Arg_Count (0);
6521
6522                --  For Ada_2005 we unconditionally enforce the documented
6523                --  configuration pragma placement, since we do not want to
6524                --  tolerate mixed modes in a unit involving Ada 2005. That
6525                --  would cause real difficulties for those cases where there
6526                --  are incompatibilities between Ada 95 and Ada 2005.
6527
6528                Check_Valid_Configuration_Pragma;
6529
6530                --  Now set appropriate Ada mode
6531
6532                Ada_Version          := Ada_2005;
6533                Ada_Version_Explicit := Ada_2005;
6534             end if;
6535          end;
6536
6537          ---------------------
6538          -- Ada_12/Ada_2012 --
6539          ---------------------
6540
6541          --  pragma Ada_12;
6542          --  pragma Ada_12 (LOCAL_NAME);
6543
6544          --  pragma Ada_2012;
6545          --  pragma Ada_2012 (LOCAL_NAME):
6546
6547          --  Note: these pragmas also have some specific processing in Par.Prag
6548          --  because we want to set the Ada 2012 version mode during parsing.
6549
6550          when Pragma_Ada_12 | Pragma_Ada_2012 => declare
6551             E_Id : Node_Id;
6552
6553          begin
6554             GNAT_Pragma;
6555
6556             if Arg_Count = 1 then
6557                Check_Arg_Is_Local_Name (Arg1);
6558                E_Id := Get_Pragma_Arg (Arg1);
6559
6560                if Etype (E_Id) = Any_Type then
6561                   return;
6562                end if;
6563
6564                Set_Is_Ada_2012_Only (Entity (E_Id));
6565
6566             else
6567                Check_Arg_Count (0);
6568
6569                --  For Ada_2012 we unconditionally enforce the documented
6570                --  configuration pragma placement, since we do not want to
6571                --  tolerate mixed modes in a unit involving Ada 2012. That
6572                --  would cause real difficulties for those cases where there
6573                --  are incompatibilities between Ada 95 and Ada 2012. We could
6574                --  allow mixing of Ada 2005 and Ada 2012 but it's not worth it.
6575
6576                Check_Valid_Configuration_Pragma;
6577
6578                --  Now set appropriate Ada mode
6579
6580                Ada_Version          := Ada_2012;
6581                Ada_Version_Explicit := Ada_2012;
6582             end if;
6583          end;
6584
6585          ----------------------
6586          -- All_Calls_Remote --
6587          ----------------------
6588
6589          --  pragma All_Calls_Remote [(library_package_NAME)];
6590
6591          when Pragma_All_Calls_Remote => All_Calls_Remote : declare
6592             Lib_Entity : Entity_Id;
6593
6594          begin
6595             Check_Ada_83_Warning;
6596             Check_Valid_Library_Unit_Pragma;
6597
6598             if Nkind (N) = N_Null_Statement then
6599                return;
6600             end if;
6601
6602             Lib_Entity := Find_Lib_Unit_Name;
6603
6604             --  This pragma should only apply to a RCI unit (RM E.2.3(23))
6605
6606             if Present (Lib_Entity)
6607               and then not Debug_Flag_U
6608             then
6609                if not Is_Remote_Call_Interface (Lib_Entity) then
6610                   Error_Pragma ("pragma% only apply to rci unit");
6611
6612                --  Set flag for entity of the library unit
6613
6614                else
6615                   Set_Has_All_Calls_Remote (Lib_Entity);
6616                end if;
6617
6618             end if;
6619          end All_Calls_Remote;
6620
6621          --------------
6622          -- Annotate --
6623          --------------
6624
6625          --  pragma Annotate (IDENTIFIER [, IDENTIFIER {, ARG}]);
6626          --  ARG ::= NAME | EXPRESSION
6627
6628          --  The first two arguments are by convention intended to refer to an
6629          --  external tool and a tool-specific function. These arguments are
6630          --  not analyzed.
6631
6632          when Pragma_Annotate => Annotate : declare
6633             Arg : Node_Id;
6634             Exp : Node_Id;
6635
6636          begin
6637             GNAT_Pragma;
6638             Check_At_Least_N_Arguments (1);
6639             Check_Arg_Is_Identifier (Arg1);
6640             Check_No_Identifiers;
6641             Store_Note (N);
6642
6643             --  Second parameter is optional, it is never analyzed
6644
6645             if No (Arg2) then
6646                null;
6647
6648             --  Here if we have a second parameter
6649
6650             else
6651                --  Second parameter must be identifier
6652
6653                Check_Arg_Is_Identifier (Arg2);
6654
6655                --  Process remaining parameters if any
6656
6657                Arg := Next (Arg2);
6658                while Present (Arg) loop
6659                   Exp := Get_Pragma_Arg (Arg);
6660                   Analyze (Exp);
6661
6662                   if Is_Entity_Name (Exp) then
6663                      null;
6664
6665                   --  For string literals, we assume Standard_String as the
6666                   --  type, unless the string contains wide or wide_wide
6667                   --  characters.
6668
6669                   elsif Nkind (Exp) = N_String_Literal then
6670                      if Has_Wide_Wide_Character (Exp) then
6671                         Resolve (Exp, Standard_Wide_Wide_String);
6672                      elsif Has_Wide_Character (Exp) then
6673                         Resolve (Exp, Standard_Wide_String);
6674                      else
6675                         Resolve (Exp, Standard_String);
6676                      end if;
6677
6678                   elsif Is_Overloaded (Exp) then
6679                         Error_Pragma_Arg
6680                           ("ambiguous argument for pragma%", Exp);
6681
6682                   else
6683                      Resolve (Exp);
6684                   end if;
6685
6686                   Next (Arg);
6687                end loop;
6688             end if;
6689          end Annotate;
6690
6691          ------------
6692          -- Assert --
6693          ------------
6694
6695          --  pragma Assert ([Check =>] Boolean_EXPRESSION
6696          --                 [, [Message =>] Static_String_EXPRESSION]);
6697
6698          when Pragma_Assert => Assert : declare
6699             Expr : Node_Id;
6700             Newa : List_Id;
6701
6702          begin
6703             Ada_2005_Pragma;
6704             Check_At_Least_N_Arguments (1);
6705             Check_At_Most_N_Arguments (2);
6706             Check_Arg_Order ((Name_Check, Name_Message));
6707             Check_Optional_Identifier (Arg1, Name_Check);
6708
6709             --  We treat pragma Assert as equivalent to:
6710
6711             --    pragma Check (Assertion, condition [, msg]);
6712
6713             --  So rewrite pragma in this manner, and analyze the result
6714
6715             Expr := Get_Pragma_Arg (Arg1);
6716             Newa := New_List (
6717               Make_Pragma_Argument_Association (Loc,
6718                 Expression => Make_Identifier (Loc, Name_Assertion)),
6719
6720               Make_Pragma_Argument_Association (Sloc (Expr),
6721                 Expression => Expr));
6722
6723             if Arg_Count > 1 then
6724                Check_Optional_Identifier (Arg2, Name_Message);
6725                Analyze_And_Resolve (Get_Pragma_Arg (Arg2), Standard_String);
6726                Append_To (Newa, Relocate_Node (Arg2));
6727             end if;
6728
6729             Rewrite (N,
6730               Make_Pragma (Loc,
6731                 Chars                        => Name_Check,
6732                 Pragma_Argument_Associations => Newa));
6733             Analyze (N);
6734          end Assert;
6735
6736          ----------------------
6737          -- Assertion_Policy --
6738          ----------------------
6739
6740          --  pragma Assertion_Policy (Check | Disable |Ignore)
6741
6742          when Pragma_Assertion_Policy => Assertion_Policy : declare
6743             Policy : Node_Id;
6744
6745          begin
6746             Ada_2005_Pragma;
6747             Check_Valid_Configuration_Pragma;
6748             Check_Arg_Count (1);
6749             Check_No_Identifiers;
6750             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Disable, Name_Ignore);
6751
6752             --  We treat pragma Assertion_Policy as equivalent to:
6753
6754             --    pragma Check_Policy (Assertion, policy)
6755
6756             --  So rewrite the pragma in that manner and link on to the chain
6757             --  of Check_Policy pragmas, marking the pragma as analyzed.
6758
6759             Policy := Get_Pragma_Arg (Arg1);
6760
6761             Rewrite (N,
6762               Make_Pragma (Loc,
6763                 Chars => Name_Check_Policy,
6764
6765                 Pragma_Argument_Associations => New_List (
6766                   Make_Pragma_Argument_Association (Loc,
6767                     Expression => Make_Identifier (Loc, Name_Assertion)),
6768
6769                   Make_Pragma_Argument_Association (Loc,
6770                     Expression =>
6771                       Make_Identifier (Sloc (Policy), Chars (Policy))))));
6772
6773             Set_Analyzed (N);
6774             Set_Next_Pragma (N, Opt.Check_Policy_List);
6775             Opt.Check_Policy_List := N;
6776          end Assertion_Policy;
6777
6778          ------------------------------
6779          -- Assume_No_Invalid_Values --
6780          ------------------------------
6781
6782          --  pragma Assume_No_Invalid_Values (On | Off);
6783
6784          when Pragma_Assume_No_Invalid_Values =>
6785             GNAT_Pragma;
6786             Check_Valid_Configuration_Pragma;
6787             Check_Arg_Count (1);
6788             Check_No_Identifiers;
6789             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
6790
6791             if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
6792                Assume_No_Invalid_Values := True;
6793             else
6794                Assume_No_Invalid_Values := False;
6795             end if;
6796
6797          ---------------
6798          -- AST_Entry --
6799          ---------------
6800
6801          --  pragma AST_Entry (entry_IDENTIFIER);
6802
6803          when Pragma_AST_Entry => AST_Entry : declare
6804             Ent : Node_Id;
6805
6806          begin
6807             GNAT_Pragma;
6808             Check_VMS (N);
6809             Check_Arg_Count (1);
6810             Check_No_Identifiers;
6811             Check_Arg_Is_Local_Name (Arg1);
6812             Ent := Entity (Get_Pragma_Arg (Arg1));
6813
6814             --  Note: the implementation of the AST_Entry pragma could handle
6815             --  the entry family case fine, but for now we are consistent with
6816             --  the DEC rules, and do not allow the pragma, which of course
6817             --  has the effect of also forbidding the attribute.
6818
6819             if Ekind (Ent) /= E_Entry then
6820                Error_Pragma_Arg
6821                  ("pragma% argument must be simple entry name", Arg1);
6822
6823             elsif Is_AST_Entry (Ent) then
6824                Error_Pragma_Arg
6825                  ("duplicate % pragma for entry", Arg1);
6826
6827             elsif Has_Homonym (Ent) then
6828                Error_Pragma_Arg
6829                  ("pragma% argument cannot specify overloaded entry", Arg1);
6830
6831             else
6832                declare
6833                   FF : constant Entity_Id := First_Formal (Ent);
6834
6835                begin
6836                   if Present (FF) then
6837                      if Present (Next_Formal (FF)) then
6838                         Error_Pragma_Arg
6839                           ("entry for pragma% can have only one argument",
6840                            Arg1);
6841
6842                      elsif Parameter_Mode (FF) /= E_In_Parameter then
6843                         Error_Pragma_Arg
6844                           ("entry parameter for pragma% must have mode IN",
6845                            Arg1);
6846                      end if;
6847                   end if;
6848                end;
6849
6850                Set_Is_AST_Entry (Ent);
6851             end if;
6852          end AST_Entry;
6853
6854          ------------------
6855          -- Asynchronous --
6856          ------------------
6857
6858          --  pragma Asynchronous (LOCAL_NAME);
6859
6860          when Pragma_Asynchronous => Asynchronous : declare
6861             Nm     : Entity_Id;
6862             C_Ent  : Entity_Id;
6863             L      : List_Id;
6864             S      : Node_Id;
6865             N      : Node_Id;
6866             Formal : Entity_Id;
6867
6868             procedure Process_Async_Pragma;
6869             --  Common processing for procedure and access-to-procedure case
6870
6871             --------------------------
6872             -- Process_Async_Pragma --
6873             --------------------------
6874
6875             procedure Process_Async_Pragma is
6876             begin
6877                if No (L) then
6878                   Set_Is_Asynchronous (Nm);
6879                   return;
6880                end if;
6881
6882                --  The formals should be of mode IN (RM E.4.1(6))
6883
6884                S := First (L);
6885                while Present (S) loop
6886                   Formal := Defining_Identifier (S);
6887
6888                   if Nkind (Formal) = N_Defining_Identifier
6889                     and then Ekind (Formal) /= E_In_Parameter
6890                   then
6891                      Error_Pragma_Arg
6892                        ("pragma% procedure can only have IN parameter",
6893                         Arg1);
6894                   end if;
6895
6896                   Next (S);
6897                end loop;
6898
6899                Set_Is_Asynchronous (Nm);
6900             end Process_Async_Pragma;
6901
6902          --  Start of processing for pragma Asynchronous
6903
6904          begin
6905             Check_Ada_83_Warning;
6906             Check_No_Identifiers;
6907             Check_Arg_Count (1);
6908             Check_Arg_Is_Local_Name (Arg1);
6909
6910             if Debug_Flag_U then
6911                return;
6912             end if;
6913
6914             C_Ent := Cunit_Entity (Current_Sem_Unit);
6915             Analyze (Get_Pragma_Arg (Arg1));
6916             Nm := Entity (Get_Pragma_Arg (Arg1));
6917
6918             if not Is_Remote_Call_Interface (C_Ent)
6919               and then not Is_Remote_Types (C_Ent)
6920             then
6921                --  This pragma should only appear in an RCI or Remote Types
6922                --  unit (RM E.4.1(4)).
6923
6924                Error_Pragma
6925                  ("pragma% not in Remote_Call_Interface or " &
6926                   "Remote_Types unit");
6927             end if;
6928
6929             if Ekind (Nm) = E_Procedure
6930               and then Nkind (Parent (Nm)) = N_Procedure_Specification
6931             then
6932                if not Is_Remote_Call_Interface (Nm) then
6933                   Error_Pragma_Arg
6934                     ("pragma% cannot be applied on non-remote procedure",
6935                      Arg1);
6936                end if;
6937
6938                L := Parameter_Specifications (Parent (Nm));
6939                Process_Async_Pragma;
6940                return;
6941
6942             elsif Ekind (Nm) = E_Function then
6943                Error_Pragma_Arg
6944                  ("pragma% cannot be applied to function", Arg1);
6945
6946             elsif Is_Remote_Access_To_Subprogram_Type (Nm) then
6947                   if Is_Record_Type (Nm) then
6948
6949                   --  A record type that is the Equivalent_Type for a remote
6950                   --  access-to-subprogram type.
6951
6952                      N := Declaration_Node (Corresponding_Remote_Type (Nm));
6953
6954                   else
6955                      --  A non-expanded RAS type (distribution is not enabled)
6956
6957                      N := Declaration_Node (Nm);
6958                   end if;
6959
6960                if Nkind (N) = N_Full_Type_Declaration
6961                  and then Nkind (Type_Definition (N)) =
6962                                      N_Access_Procedure_Definition
6963                then
6964                   L := Parameter_Specifications (Type_Definition (N));
6965                   Process_Async_Pragma;
6966
6967                   if Is_Asynchronous (Nm)
6968                     and then Expander_Active
6969                     and then Get_PCS_Name /= Name_No_DSA
6970                   then
6971                      RACW_Type_Is_Asynchronous (Underlying_RACW_Type (Nm));
6972                   end if;
6973
6974                else
6975                   Error_Pragma_Arg
6976                     ("pragma% cannot reference access-to-function type",
6977                     Arg1);
6978                end if;
6979
6980             --  Only other possibility is Access-to-class-wide type
6981
6982             elsif Is_Access_Type (Nm)
6983               and then Is_Class_Wide_Type (Designated_Type (Nm))
6984             then
6985                Check_First_Subtype (Arg1);
6986                Set_Is_Asynchronous (Nm);
6987                if Expander_Active then
6988                   RACW_Type_Is_Asynchronous (Nm);
6989                end if;
6990
6991             else
6992                Error_Pragma_Arg ("inappropriate argument for pragma%", Arg1);
6993             end if;
6994          end Asynchronous;
6995
6996          ------------
6997          -- Atomic --
6998          ------------
6999
7000          --  pragma Atomic (LOCAL_NAME);
7001
7002          when Pragma_Atomic =>
7003             Process_Atomic_Shared_Volatile;
7004
7005          -----------------------
7006          -- Atomic_Components --
7007          -----------------------
7008
7009          --  pragma Atomic_Components (array_LOCAL_NAME);
7010
7011          --  This processing is shared by Volatile_Components
7012
7013          when Pragma_Atomic_Components   |
7014               Pragma_Volatile_Components =>
7015
7016          Atomic_Components : declare
7017             E_Id : Node_Id;
7018             E    : Entity_Id;
7019             D    : Node_Id;
7020             K    : Node_Kind;
7021
7022          begin
7023             Check_Ada_83_Warning;
7024             Check_No_Identifiers;
7025             Check_Arg_Count (1);
7026             Check_Arg_Is_Local_Name (Arg1);
7027             E_Id := Get_Pragma_Arg (Arg1);
7028
7029             if Etype (E_Id) = Any_Type then
7030                return;
7031             end if;
7032
7033             E := Entity (E_Id);
7034
7035             Check_Duplicate_Pragma (E);
7036
7037             if Rep_Item_Too_Early (E, N)
7038                  or else
7039                Rep_Item_Too_Late (E, N)
7040             then
7041                return;
7042             end if;
7043
7044             D := Declaration_Node (E);
7045             K := Nkind (D);
7046
7047             if (K = N_Full_Type_Declaration and then Is_Array_Type (E))
7048               or else
7049                 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
7050                    and then Nkind (D) = N_Object_Declaration
7051                    and then Nkind (Object_Definition (D)) =
7052                                        N_Constrained_Array_Definition)
7053             then
7054                --  The flag is set on the object, or on the base type
7055
7056                if Nkind (D) /= N_Object_Declaration then
7057                   E := Base_Type (E);
7058                end if;
7059
7060                Set_Has_Volatile_Components (E);
7061
7062                if Prag_Id = Pragma_Atomic_Components then
7063                   Set_Has_Atomic_Components (E);
7064                end if;
7065
7066             else
7067                Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
7068             end if;
7069          end Atomic_Components;
7070          --------------------
7071          -- Attach_Handler --
7072          --------------------
7073
7074          --  pragma Attach_Handler (handler_NAME, EXPRESSION);
7075
7076          when Pragma_Attach_Handler =>
7077             Check_Ada_83_Warning;
7078             Check_No_Identifiers;
7079             Check_Arg_Count (2);
7080
7081             if No_Run_Time_Mode then
7082                Error_Msg_CRT ("Attach_Handler pragma", N);
7083             else
7084                Check_Interrupt_Or_Attach_Handler;
7085
7086                --  The expression that designates the attribute may depend on a
7087                --  discriminant, and is therefore a per-object expression, to
7088                --  be expanded in the init proc. If expansion is enabled, then
7089                --  perform semantic checks on a copy only.
7090
7091                if Expander_Active then
7092                   declare
7093                      Temp : constant Node_Id :=
7094                               New_Copy_Tree (Get_Pragma_Arg (Arg2));
7095                   begin
7096                      Set_Parent (Temp, N);
7097                      Preanalyze_And_Resolve (Temp, RTE (RE_Interrupt_ID));
7098                   end;
7099
7100                else
7101                   Analyze (Get_Pragma_Arg (Arg2));
7102                   Resolve (Get_Pragma_Arg (Arg2), RTE (RE_Interrupt_ID));
7103                end if;
7104
7105                Process_Interrupt_Or_Attach_Handler;
7106             end if;
7107
7108          --------------------
7109          -- C_Pass_By_Copy --
7110          --------------------
7111
7112          --  pragma C_Pass_By_Copy ([Max_Size =>] static_integer_EXPRESSION);
7113
7114          when Pragma_C_Pass_By_Copy => C_Pass_By_Copy : declare
7115             Arg : Node_Id;
7116             Val : Uint;
7117
7118          begin
7119             GNAT_Pragma;
7120             Check_Valid_Configuration_Pragma;
7121             Check_Arg_Count (1);
7122             Check_Optional_Identifier (Arg1, "max_size");
7123
7124             Arg := Get_Pragma_Arg (Arg1);
7125             Check_Arg_Is_Static_Expression (Arg, Any_Integer);
7126
7127             Val := Expr_Value (Arg);
7128
7129             if Val <= 0 then
7130                Error_Pragma_Arg
7131                  ("maximum size for pragma% must be positive", Arg1);
7132
7133             elsif UI_Is_In_Int_Range (Val) then
7134                Default_C_Record_Mechanism := UI_To_Int (Val);
7135
7136             --  If a giant value is given, Int'Last will do well enough.
7137             --  If sometime someone complains that a record larger than
7138             --  two gigabytes is not copied, we will worry about it then!
7139
7140             else
7141                Default_C_Record_Mechanism := Mechanism_Type'Last;
7142             end if;
7143          end C_Pass_By_Copy;
7144
7145          -----------
7146          -- Check --
7147          -----------
7148
7149          --  pragma Check ([Name    =>] IDENTIFIER,
7150          --                [Check   =>] Boolean_EXPRESSION
7151          --              [,[Message =>] String_EXPRESSION]);
7152
7153          when Pragma_Check => Check : declare
7154             Expr : Node_Id;
7155             Eloc : Source_Ptr;
7156
7157             Check_On : Boolean;
7158             --  Set True if category of assertions referenced by Name enabled
7159
7160          begin
7161             GNAT_Pragma;
7162             Check_At_Least_N_Arguments (2);
7163             Check_At_Most_N_Arguments (3);
7164             Check_Optional_Identifier (Arg1, Name_Name);
7165             Check_Optional_Identifier (Arg2, Name_Check);
7166
7167             if Arg_Count = 3 then
7168                Check_Optional_Identifier (Arg3, Name_Message);
7169                Analyze_And_Resolve (Get_Pragma_Arg (Arg3), Standard_String);
7170             end if;
7171
7172             Check_Arg_Is_Identifier (Arg1);
7173
7174             --  Completely ignore if disabled
7175
7176             if Check_Disabled (Chars (Get_Pragma_Arg (Arg1))) then
7177                Rewrite (N, Make_Null_Statement (Loc));
7178                Analyze (N);
7179                return;
7180             end if;
7181
7182             --  Indicate if pragma is enabled. The Original_Node reference here
7183             --  is to deal with pragma Assert rewritten as a Check pragma.
7184
7185             Check_On := Check_Enabled (Chars (Get_Pragma_Arg (Arg1)));
7186
7187             if Check_On then
7188                Set_SCO_Pragma_Enabled (Loc);
7189             end if;
7190
7191             --  If expansion is active and the check is not enabled then we
7192             --  rewrite the Check as:
7193
7194             --    if False and then condition then
7195             --       null;
7196             --    end if;
7197
7198             --  The reason we do this rewriting during semantic analysis rather
7199             --  than as part of normal expansion is that we cannot analyze and
7200             --  expand the code for the boolean expression directly, or it may
7201             --  cause insertion of actions that would escape the attempt to
7202             --  suppress the check code.
7203
7204             --  Note that the Sloc for the if statement corresponds to the
7205             --  argument condition, not the pragma itself. The reason for this
7206             --  is that we may generate a warning if the condition is False at
7207             --  compile time, and we do not want to delete this warning when we
7208             --  delete the if statement.
7209
7210             Expr := Get_Pragma_Arg (Arg2);
7211
7212             if Expander_Active and then not Check_On then
7213                Eloc := Sloc (Expr);
7214
7215                Rewrite (N,
7216                  Make_If_Statement (Eloc,
7217                    Condition =>
7218                      Make_And_Then (Eloc,
7219                        Left_Opnd  => New_Occurrence_Of (Standard_False, Eloc),
7220                        Right_Opnd => Expr),
7221                    Then_Statements => New_List (
7222                      Make_Null_Statement (Eloc))));
7223
7224                Analyze (N);
7225
7226             --  Check is active
7227
7228             else
7229                Analyze_And_Resolve (Expr, Any_Boolean);
7230             end if;
7231          end Check;
7232
7233          ----------------
7234          -- Check_Name --
7235          ----------------
7236
7237          --  pragma Check_Name (check_IDENTIFIER);
7238
7239          when Pragma_Check_Name =>
7240             Check_No_Identifiers;
7241             GNAT_Pragma;
7242             Check_Valid_Configuration_Pragma;
7243             Check_Arg_Count (1);
7244             Check_Arg_Is_Identifier (Arg1);
7245
7246             declare
7247                Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
7248
7249             begin
7250                for J in Check_Names.First .. Check_Names.Last loop
7251                   if Check_Names.Table (J) = Nam then
7252                      return;
7253                   end if;
7254                end loop;
7255
7256                Check_Names.Append (Nam);
7257             end;
7258
7259          ------------------
7260          -- Check_Policy --
7261          ------------------
7262
7263          --  pragma Check_Policy (
7264          --    [Name   =>] IDENTIFIER,
7265          --    [Policy =>] POLICY_IDENTIFIER);
7266
7267          --  POLICY_IDENTIFIER ::= ON | OFF | CHECK | DISABLE | IGNORE
7268
7269          --  Note: this is a configuration pragma, but it is allowed to appear
7270          --  anywhere else.
7271
7272          when Pragma_Check_Policy =>
7273             GNAT_Pragma;
7274             Check_Arg_Count (2);
7275             Check_Optional_Identifier (Arg1, Name_Name);
7276             Check_Optional_Identifier (Arg2, Name_Policy);
7277             Check_Arg_Is_One_Of
7278               (Arg2, Name_On, Name_Off, Name_Check, Name_Disable, Name_Ignore);
7279
7280             --  A Check_Policy pragma can appear either as a configuration
7281             --  pragma, or in a declarative part or a package spec (see RM
7282             --  11.5(5) for rules for Suppress/Unsuppress which are also
7283             --  followed for Check_Policy).
7284
7285             if not Is_Configuration_Pragma then
7286                Check_Is_In_Decl_Part_Or_Package_Spec;
7287             end if;
7288
7289             Set_Next_Pragma (N, Opt.Check_Policy_List);
7290             Opt.Check_Policy_List := N;
7291
7292          ---------------------
7293          -- CIL_Constructor --
7294          ---------------------
7295
7296          --  pragma CIL_Constructor ([Entity =>] LOCAL_NAME);
7297
7298          --  Processing for this pragma is shared with Java_Constructor
7299
7300          -------------
7301          -- Comment --
7302          -------------
7303
7304          --  pragma Comment (static_string_EXPRESSION)
7305
7306          --  Processing for pragma Comment shares the circuitry for pragma
7307          --  Ident. The only differences are that Ident enforces a limit of 31
7308          --  characters on its argument, and also enforces limitations on
7309          --  placement for DEC compatibility. Pragma Comment shares neither of
7310          --  these restrictions.
7311
7312          -------------------
7313          -- Common_Object --
7314          -------------------
7315
7316          --  pragma Common_Object (
7317          --        [Internal =>] LOCAL_NAME
7318          --     [, [External =>] EXTERNAL_SYMBOL]
7319          --     [, [Size     =>] EXTERNAL_SYMBOL]);
7320
7321          --  Processing for this pragma is shared with Psect_Object
7322
7323          ------------------------
7324          -- Compile_Time_Error --
7325          ------------------------
7326
7327          --  pragma Compile_Time_Error
7328          --    (boolean_EXPRESSION, static_string_EXPRESSION);
7329
7330          when Pragma_Compile_Time_Error =>
7331             GNAT_Pragma;
7332             Process_Compile_Time_Warning_Or_Error;
7333
7334          --------------------------
7335          -- Compile_Time_Warning --
7336          --------------------------
7337
7338          --  pragma Compile_Time_Warning
7339          --    (boolean_EXPRESSION, static_string_EXPRESSION);
7340
7341          when Pragma_Compile_Time_Warning =>
7342             GNAT_Pragma;
7343             Process_Compile_Time_Warning_Or_Error;
7344
7345          -------------------
7346          -- Compiler_Unit --
7347          -------------------
7348
7349          when Pragma_Compiler_Unit =>
7350             GNAT_Pragma;
7351             Check_Arg_Count (0);
7352             Set_Is_Compiler_Unit (Get_Source_Unit (N));
7353
7354          -----------------------------
7355          -- Complete_Representation --
7356          -----------------------------
7357
7358          --  pragma Complete_Representation;
7359
7360          when Pragma_Complete_Representation =>
7361             GNAT_Pragma;
7362             Check_Arg_Count (0);
7363
7364             if Nkind (Parent (N)) /= N_Record_Representation_Clause then
7365                Error_Pragma
7366                  ("pragma & must appear within record representation clause");
7367             end if;
7368
7369          ----------------------------
7370          -- Complex_Representation --
7371          ----------------------------
7372
7373          --  pragma Complex_Representation ([Entity =>] LOCAL_NAME);
7374
7375          when Pragma_Complex_Representation => Complex_Representation : declare
7376             E_Id : Entity_Id;
7377             E    : Entity_Id;
7378             Ent  : Entity_Id;
7379
7380          begin
7381             GNAT_Pragma;
7382             Check_Arg_Count (1);
7383             Check_Optional_Identifier (Arg1, Name_Entity);
7384             Check_Arg_Is_Local_Name (Arg1);
7385             E_Id := Get_Pragma_Arg (Arg1);
7386
7387             if Etype (E_Id) = Any_Type then
7388                return;
7389             end if;
7390
7391             E := Entity (E_Id);
7392
7393             if not Is_Record_Type (E) then
7394                Error_Pragma_Arg
7395                  ("argument for pragma% must be record type", Arg1);
7396             end if;
7397
7398             Ent := First_Entity (E);
7399
7400             if No (Ent)
7401               or else No (Next_Entity (Ent))
7402               or else Present (Next_Entity (Next_Entity (Ent)))
7403               or else not Is_Floating_Point_Type (Etype (Ent))
7404               or else Etype (Ent) /= Etype (Next_Entity (Ent))
7405             then
7406                Error_Pragma_Arg
7407                  ("record for pragma% must have two fields of the same "
7408                   & "floating-point type", Arg1);
7409
7410             else
7411                Set_Has_Complex_Representation (Base_Type (E));
7412
7413                --  We need to treat the type has having a non-standard
7414                --  representation, for back-end purposes, even though in
7415                --  general a complex will have the default representation
7416                --  of a record with two real components.
7417
7418                Set_Has_Non_Standard_Rep (Base_Type (E));
7419             end if;
7420          end Complex_Representation;
7421
7422          -------------------------
7423          -- Component_Alignment --
7424          -------------------------
7425
7426          --  pragma Component_Alignment (
7427          --        [Form =>] ALIGNMENT_CHOICE
7428          --     [, [Name =>] type_LOCAL_NAME]);
7429          --
7430          --   ALIGNMENT_CHOICE ::=
7431          --     Component_Size
7432          --   | Component_Size_4
7433          --   | Storage_Unit
7434          --   | Default
7435
7436          when Pragma_Component_Alignment => Component_AlignmentP : declare
7437             Args  : Args_List (1 .. 2);
7438             Names : constant Name_List (1 .. 2) := (
7439                       Name_Form,
7440                       Name_Name);
7441
7442             Form  : Node_Id renames Args (1);
7443             Name  : Node_Id renames Args (2);
7444
7445             Atype : Component_Alignment_Kind;
7446             Typ   : Entity_Id;
7447
7448          begin
7449             GNAT_Pragma;
7450             Gather_Associations (Names, Args);
7451
7452             if No (Form) then
7453                Error_Pragma ("missing Form argument for pragma%");
7454             end if;
7455
7456             Check_Arg_Is_Identifier (Form);
7457
7458             --  Get proper alignment, note that Default = Component_Size on all
7459             --  machines we have so far, and we want to set this value rather
7460             --  than the default value to indicate that it has been explicitly
7461             --  set (and thus will not get overridden by the default component
7462             --  alignment for the current scope)
7463
7464             if Chars (Form) = Name_Component_Size then
7465                Atype := Calign_Component_Size;
7466
7467             elsif Chars (Form) = Name_Component_Size_4 then
7468                Atype := Calign_Component_Size_4;
7469
7470             elsif Chars (Form) = Name_Default then
7471                Atype := Calign_Component_Size;
7472
7473             elsif Chars (Form) = Name_Storage_Unit then
7474                Atype := Calign_Storage_Unit;
7475
7476             else
7477                Error_Pragma_Arg
7478                  ("invalid Form parameter for pragma%", Form);
7479             end if;
7480
7481             --  Case with no name, supplied, affects scope table entry
7482
7483             if No (Name) then
7484                Scope_Stack.Table
7485                  (Scope_Stack.Last).Component_Alignment_Default := Atype;
7486
7487             --  Case of name supplied
7488
7489             else
7490                Check_Arg_Is_Local_Name (Name);
7491                Find_Type (Name);
7492                Typ := Entity (Name);
7493
7494                if Typ = Any_Type
7495                  or else Rep_Item_Too_Early (Typ, N)
7496                then
7497                   return;
7498                else
7499                   Typ := Underlying_Type (Typ);
7500                end if;
7501
7502                if not Is_Record_Type (Typ)
7503                  and then not Is_Array_Type (Typ)
7504                then
7505                   Error_Pragma_Arg
7506                     ("Name parameter of pragma% must identify record or " &
7507                      "array type", Name);
7508                end if;
7509
7510                --  An explicit Component_Alignment pragma overrides an
7511                --  implicit pragma Pack, but not an explicit one.
7512
7513                if not Has_Pragma_Pack (Base_Type (Typ)) then
7514                   Set_Is_Packed (Base_Type (Typ), False);
7515                   Set_Component_Alignment (Base_Type (Typ), Atype);
7516                end if;
7517             end if;
7518          end Component_AlignmentP;
7519
7520          ----------------
7521          -- Controlled --
7522          ----------------
7523
7524          --  pragma Controlled (first_subtype_LOCAL_NAME);
7525
7526          when Pragma_Controlled => Controlled : declare
7527             Arg : Node_Id;
7528
7529          begin
7530             Check_No_Identifiers;
7531             Check_Arg_Count (1);
7532             Check_Arg_Is_Local_Name (Arg1);
7533             Arg := Get_Pragma_Arg (Arg1);
7534
7535             if not Is_Entity_Name (Arg)
7536               or else not Is_Access_Type (Entity (Arg))
7537             then
7538                Error_Pragma_Arg ("pragma% requires access type", Arg1);
7539             else
7540                Set_Has_Pragma_Controlled (Base_Type (Entity (Arg)));
7541             end if;
7542          end Controlled;
7543
7544          ----------------
7545          -- Convention --
7546          ----------------
7547
7548          --  pragma Convention ([Convention =>] convention_IDENTIFIER,
7549          --    [Entity =>] LOCAL_NAME);
7550
7551          when Pragma_Convention => Convention : declare
7552             C : Convention_Id;
7553             E : Entity_Id;
7554             pragma Warnings (Off, C);
7555             pragma Warnings (Off, E);
7556          begin
7557             Check_Arg_Order ((Name_Convention, Name_Entity));
7558             Check_Ada_83_Warning;
7559             Check_Arg_Count (2);
7560             Process_Convention (C, E);
7561          end Convention;
7562
7563          ---------------------------
7564          -- Convention_Identifier --
7565          ---------------------------
7566
7567          --  pragma Convention_Identifier ([Name =>] IDENTIFIER,
7568          --    [Convention =>] convention_IDENTIFIER);
7569
7570          when Pragma_Convention_Identifier => Convention_Identifier : declare
7571             Idnam : Name_Id;
7572             Cname : Name_Id;
7573
7574          begin
7575             GNAT_Pragma;
7576             Check_Arg_Order ((Name_Name, Name_Convention));
7577             Check_Arg_Count (2);
7578             Check_Optional_Identifier (Arg1, Name_Name);
7579             Check_Optional_Identifier (Arg2, Name_Convention);
7580             Check_Arg_Is_Identifier (Arg1);
7581             Check_Arg_Is_Identifier (Arg2);
7582             Idnam := Chars (Get_Pragma_Arg (Arg1));
7583             Cname := Chars (Get_Pragma_Arg (Arg2));
7584
7585             if Is_Convention_Name (Cname) then
7586                Record_Convention_Identifier
7587                  (Idnam, Get_Convention_Id (Cname));
7588             else
7589                Error_Pragma_Arg
7590                  ("second arg for % pragma must be convention", Arg2);
7591             end if;
7592          end Convention_Identifier;
7593
7594          ---------------
7595          -- CPP_Class --
7596          ---------------
7597
7598          --  pragma CPP_Class ([Entity =>] local_NAME)
7599
7600          when Pragma_CPP_Class => CPP_Class : declare
7601             Arg : Node_Id;
7602             Typ : Entity_Id;
7603
7604          begin
7605             if Warn_On_Obsolescent_Feature then
7606                Error_Msg_N
7607                  ("'G'N'A'T pragma cpp'_class is now obsolete; replace it" &
7608                   " by pragma import?", N);
7609             end if;
7610
7611             GNAT_Pragma;
7612             Check_Arg_Count (1);
7613             Check_Optional_Identifier (Arg1, Name_Entity);
7614             Check_Arg_Is_Local_Name (Arg1);
7615
7616             Arg := Get_Pragma_Arg (Arg1);
7617             Analyze (Arg);
7618
7619             if Etype (Arg) = Any_Type then
7620                return;
7621             end if;
7622
7623             if not Is_Entity_Name (Arg)
7624               or else not Is_Type (Entity (Arg))
7625             then
7626                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
7627             end if;
7628
7629             Typ := Entity (Arg);
7630
7631             if not Is_Tagged_Type (Typ) then
7632                Error_Pragma_Arg ("pragma% applicable to tagged types ", Arg1);
7633             end if;
7634
7635             --  Types treated as CPP classes must be declared limited (note:
7636             --  this used to be a warning but there is no real benefit to it
7637             --  since we did effectively intend to treat the type as limited
7638             --  anyway).
7639
7640             if not Is_Limited_Type (Typ) then
7641                Error_Msg_N
7642                  ("imported 'C'P'P type must be limited",
7643                   Get_Pragma_Arg (Arg1));
7644             end if;
7645
7646             Set_Is_CPP_Class (Typ);
7647             Set_Convention (Typ, Convention_CPP);
7648
7649             --  Imported CPP types must not have discriminants (because C++
7650             --  classes do not have discriminants).
7651
7652             if Has_Discriminants (Typ) then
7653                Error_Msg_N
7654                  ("imported 'C'P'P type cannot have discriminants",
7655                   First (Discriminant_Specifications
7656                           (Declaration_Node (Typ))));
7657             end if;
7658
7659             --  Components of imported CPP types must not have default
7660             --  expressions because the constructor (if any) is in the
7661             --  C++ side.
7662
7663             if Is_Incomplete_Or_Private_Type (Typ)
7664               and then No (Underlying_Type (Typ))
7665             then
7666                --  It should be an error to apply pragma CPP to a private
7667                --  type if the underlying type is not visible (as it is
7668                --  for any representation item). For now, for backward
7669                --  compatibility we do nothing but we cannot check components
7670                --  because they are not available at this stage. All this code
7671                --  will be removed when we cleanup this obsolete GNAT pragma???
7672
7673                null;
7674
7675             else
7676                declare
7677                   Tdef  : constant Node_Id :=
7678                             Type_Definition (Declaration_Node (Typ));
7679                   Clist : Node_Id;
7680                   Comp  : Node_Id;
7681
7682                begin
7683                   if Nkind (Tdef) = N_Record_Definition then
7684                      Clist := Component_List (Tdef);
7685                   else
7686                      pragma Assert (Nkind (Tdef) = N_Derived_Type_Definition);
7687                      Clist := Component_List (Record_Extension_Part (Tdef));
7688                   end if;
7689
7690                   if Present (Clist) then
7691                      Comp := First (Component_Items (Clist));
7692                      while Present (Comp) loop
7693                         if Present (Expression (Comp)) then
7694                            Error_Msg_N
7695                              ("component of imported 'C'P'P type cannot have" &
7696                               " default expression", Expression (Comp));
7697                         end if;
7698
7699                         Next (Comp);
7700                      end loop;
7701                   end if;
7702                end;
7703             end if;
7704          end CPP_Class;
7705
7706          ---------------------
7707          -- CPP_Constructor --
7708          ---------------------
7709
7710          --  pragma CPP_Constructor ([Entity =>] LOCAL_NAME
7711          --    [, [External_Name =>] static_string_EXPRESSION ]
7712          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
7713
7714          when Pragma_CPP_Constructor => CPP_Constructor : declare
7715             Elmt    : Elmt_Id;
7716             Id      : Entity_Id;
7717             Def_Id  : Entity_Id;
7718             Tag_Typ : Entity_Id;
7719
7720          begin
7721             GNAT_Pragma;
7722             Check_At_Least_N_Arguments (1);
7723             Check_At_Most_N_Arguments (3);
7724             Check_Optional_Identifier (Arg1, Name_Entity);
7725             Check_Arg_Is_Local_Name (Arg1);
7726
7727             Id := Get_Pragma_Arg (Arg1);
7728             Find_Program_Unit_Name (Id);
7729
7730             --  If we did not find the name, we are done
7731
7732             if Etype (Id) = Any_Type then
7733                return;
7734             end if;
7735
7736             Def_Id := Entity (Id);
7737
7738             --  Check if already defined as constructor
7739
7740             if Is_Constructor (Def_Id) then
7741                Error_Msg_N
7742                  ("?duplicate argument for pragma 'C'P'P_Constructor", Arg1);
7743                return;
7744             end if;
7745
7746             if Ekind (Def_Id) = E_Function
7747               and then (Is_CPP_Class (Etype (Def_Id))
7748                          or else (Is_Class_Wide_Type (Etype (Def_Id))
7749                                    and then
7750                                   Is_CPP_Class (Root_Type (Etype (Def_Id)))))
7751             then
7752                if Arg_Count >= 2 then
7753                   Set_Imported (Def_Id);
7754                   Set_Is_Public (Def_Id);
7755                   Process_Interface_Name (Def_Id, Arg2, Arg3);
7756                end if;
7757
7758                Set_Has_Completion (Def_Id);
7759                Set_Is_Constructor (Def_Id);
7760
7761                --  Imported C++ constructors are not dispatching primitives
7762                --  because in C++ they don't have a dispatch table slot.
7763                --  However, in Ada the constructor has the profile of a
7764                --  function that returns a tagged type and therefore it has
7765                --  been treated as a primitive operation during semantic
7766                --  analysis. We now remove it from the list of primitive
7767                --  operations of the type.
7768
7769                if Is_Tagged_Type (Etype (Def_Id))
7770                  and then not Is_Class_Wide_Type (Etype (Def_Id))
7771                then
7772                   pragma Assert (Is_Dispatching_Operation (Def_Id));
7773                   Tag_Typ := Etype (Def_Id);
7774
7775                   Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
7776                   while Present (Elmt) and then Node (Elmt) /= Def_Id loop
7777                      Next_Elmt (Elmt);
7778                   end loop;
7779
7780                   Remove_Elmt (Primitive_Operations (Tag_Typ), Elmt);
7781                   Set_Is_Dispatching_Operation (Def_Id, False);
7782                end if;
7783
7784                --  For backward compatibility, if the constructor returns a
7785                --  class wide type, and we internally change the return type to
7786                --  the corresponding root type.
7787
7788                if Is_Class_Wide_Type (Etype (Def_Id)) then
7789                   Set_Etype (Def_Id, Root_Type (Etype (Def_Id)));
7790                end if;
7791             else
7792                Error_Pragma_Arg
7793                  ("pragma% requires function returning a 'C'P'P_Class type",
7794                    Arg1);
7795             end if;
7796          end CPP_Constructor;
7797
7798          -----------------
7799          -- CPP_Virtual --
7800          -----------------
7801
7802          when Pragma_CPP_Virtual => CPP_Virtual : declare
7803          begin
7804             GNAT_Pragma;
7805
7806             if Warn_On_Obsolescent_Feature then
7807                Error_Msg_N
7808                  ("'G'N'A'T pragma cpp'_virtual is now obsolete and has " &
7809                   "no effect?", N);
7810             end if;
7811          end CPP_Virtual;
7812
7813          ----------------
7814          -- CPP_Vtable --
7815          ----------------
7816
7817          when Pragma_CPP_Vtable => CPP_Vtable : 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'_vtable is now obsolete and has " &
7824                   "no effect?", N);
7825             end if;
7826          end CPP_Vtable;
7827
7828          ---------
7829          -- CPU --
7830          ---------
7831
7832          --  pragma CPU (EXPRESSION);
7833
7834          when Pragma_CPU => CPU : declare
7835             P   : constant Node_Id := Parent (N);
7836             Arg : Node_Id;
7837
7838          begin
7839             Ada_2012_Pragma;
7840             Check_No_Identifiers;
7841             Check_Arg_Count (1);
7842
7843             --  Subprogram case
7844
7845             if Nkind (P) = N_Subprogram_Body then
7846                Check_In_Main_Program;
7847
7848                Arg := Get_Pragma_Arg (Arg1);
7849                Analyze_And_Resolve (Arg, Any_Integer);
7850
7851                --  Must be static
7852
7853                if not Is_Static_Expression (Arg) then
7854                   Flag_Non_Static_Expr
7855                     ("main subprogram affinity is not static!", Arg);
7856                   raise Pragma_Exit;
7857
7858                --  If constraint error, then we already signalled an error
7859
7860                elsif Raises_Constraint_Error (Arg) then
7861                   null;
7862
7863                --  Otherwise check in range
7864
7865                else
7866                   declare
7867                      CPU_Id : constant Entity_Id := RTE (RE_CPU_Range);
7868                      --  This is the entity System.Multiprocessors.CPU_Range;
7869
7870                      Val : constant Uint := Expr_Value (Arg);
7871
7872                   begin
7873                      if Val < Expr_Value (Type_Low_Bound (CPU_Id))
7874                           or else
7875                         Val > Expr_Value (Type_High_Bound (CPU_Id))
7876                      then
7877                         Error_Pragma_Arg
7878                           ("main subprogram CPU is out of range", Arg1);
7879                      end if;
7880                   end;
7881                end if;
7882
7883                Set_Main_CPU
7884                     (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
7885
7886             --  Task case
7887
7888             elsif Nkind (P) = N_Task_Definition then
7889                Arg := Get_Pragma_Arg (Arg1);
7890
7891                --  The expression must be analyzed in the special manner
7892                --  described in "Handling of Default and Per-Object
7893                --  Expressions" in sem.ads.
7894
7895                Preanalyze_Spec_Expression (Arg, RTE (RE_CPU_Range));
7896
7897             --  Anything else is incorrect
7898
7899             else
7900                Pragma_Misplaced;
7901             end if;
7902
7903             if Has_Pragma_CPU (P) then
7904                Error_Pragma ("duplicate pragma% not allowed");
7905             else
7906                Set_Has_Pragma_CPU (P, True);
7907
7908                if Nkind (P) = N_Task_Definition then
7909                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
7910                end if;
7911             end if;
7912          end CPU;
7913
7914          -----------
7915          -- Debug --
7916          -----------
7917
7918          --  pragma Debug ([boolean_EXPRESSION,] PROCEDURE_CALL_STATEMENT);
7919
7920          when Pragma_Debug => Debug : declare
7921             Cond : Node_Id;
7922             Call : Node_Id;
7923
7924          begin
7925             GNAT_Pragma;
7926
7927             --  Skip analysis if disabled
7928
7929             if Debug_Pragmas_Disabled then
7930                Rewrite (N, Make_Null_Statement (Loc));
7931                Analyze (N);
7932                return;
7933             end if;
7934
7935             Cond :=
7936               New_Occurrence_Of
7937                 (Boolean_Literals (Debug_Pragmas_Enabled and Expander_Active),
7938                  Loc);
7939
7940             if Debug_Pragmas_Enabled then
7941                Set_SCO_Pragma_Enabled (Loc);
7942             end if;
7943
7944             if Arg_Count = 2 then
7945                Cond :=
7946                  Make_And_Then (Loc,
7947                    Left_Opnd  => Relocate_Node (Cond),
7948                    Right_Opnd => Get_Pragma_Arg (Arg1));
7949                Call := Get_Pragma_Arg (Arg2);
7950             else
7951                Call := Get_Pragma_Arg (Arg1);
7952             end if;
7953
7954             if Nkind_In (Call,
7955                  N_Indexed_Component,
7956                  N_Function_Call,
7957                  N_Identifier,
7958                  N_Expanded_Name,
7959                  N_Selected_Component)
7960             then
7961                --  If this pragma Debug comes from source, its argument was
7962                --  parsed as a name form (which is syntactically identical).
7963                --  In a generic context a parameterless call will be left as
7964                --  an expanded name (if global) or selected_component if local.
7965                --  Change it to a procedure call statement now.
7966
7967                Change_Name_To_Procedure_Call_Statement (Call);
7968
7969             elsif Nkind (Call) = N_Procedure_Call_Statement then
7970
7971                --  Already in the form of a procedure call statement: nothing
7972                --  to do (could happen in case of an internally generated
7973                --  pragma Debug).
7974
7975                null;
7976
7977             else
7978                --  All other cases: diagnose error
7979
7980                Error_Msg
7981                  ("argument of pragma ""Debug"" is not procedure call",
7982                   Sloc (Call));
7983                return;
7984             end if;
7985
7986             --  Rewrite into a conditional with an appropriate condition. We
7987             --  wrap the procedure call in a block so that overhead from e.g.
7988             --  use of the secondary stack does not generate execution overhead
7989             --  for suppressed conditions.
7990
7991             --  Normally the analysis that follows will freeze the subprogram
7992             --  being called. However, if the call is to a null procedure,
7993             --  we want to freeze it before creating the block, because the
7994             --  analysis that follows may be done with expansion disabled, in
7995             --  which case the body will not be generated, leading to spurious
7996             --  errors.
7997
7998             if Nkind (Call) = N_Procedure_Call_Statement
7999               and then Is_Entity_Name (Name (Call))
8000             then
8001                Analyze (Name (Call));
8002                Freeze_Before (N, Entity (Name (Call)));
8003             end if;
8004
8005             Rewrite (N, Make_Implicit_If_Statement (N,
8006               Condition => Cond,
8007                  Then_Statements => New_List (
8008                    Make_Block_Statement (Loc,
8009                      Handled_Statement_Sequence =>
8010                        Make_Handled_Sequence_Of_Statements (Loc,
8011                          Statements => New_List (Relocate_Node (Call)))))));
8012             Analyze (N);
8013          end Debug;
8014
8015          ------------------
8016          -- Debug_Policy --
8017          ------------------
8018
8019          --  pragma Debug_Policy (Check | Ignore)
8020
8021          when Pragma_Debug_Policy =>
8022             GNAT_Pragma;
8023             Check_Arg_Count (1);
8024             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Disable, Name_Ignore);
8025             Debug_Pragmas_Enabled :=
8026               Chars (Get_Pragma_Arg (Arg1)) = Name_Check;
8027             Debug_Pragmas_Disabled :=
8028               Chars (Get_Pragma_Arg (Arg1)) = Name_Disable;
8029
8030          ---------------------
8031          -- Detect_Blocking --
8032          ---------------------
8033
8034          --  pragma Detect_Blocking;
8035
8036          when Pragma_Detect_Blocking =>
8037             Ada_2005_Pragma;
8038             Check_Arg_Count (0);
8039             Check_Valid_Configuration_Pragma;
8040             Detect_Blocking := True;
8041
8042          --------------------------
8043          -- Default_Storage_Pool --
8044          --------------------------
8045
8046          --  pragma Default_Storage_Pool (storage_pool_NAME | null);
8047
8048          when Pragma_Default_Storage_Pool =>
8049             Ada_2012_Pragma;
8050             Check_Arg_Count (1);
8051
8052             --  Default_Storage_Pool can appear as a configuration pragma, or
8053             --  in a declarative part or a package spec.
8054
8055             if not Is_Configuration_Pragma then
8056                Check_Is_In_Decl_Part_Or_Package_Spec;
8057             end if;
8058
8059             --  Case of Default_Storage_Pool (null);
8060
8061             if Nkind (Expression (Arg1)) = N_Null then
8062                Analyze (Expression (Arg1));
8063
8064                --  This is an odd case, this is not really an expression, so
8065                --  we don't have a type for it. So just set the type to Empty.
8066
8067                Set_Etype (Expression (Arg1), Empty);
8068
8069             --  Case of Default_Storage_Pool (storage_pool_NAME);
8070
8071             else
8072                --  If it's a configuration pragma, then the only allowed
8073                --  argument is "null".
8074
8075                if Is_Configuration_Pragma then
8076                   Error_Pragma_Arg ("NULL expected", Arg1);
8077                end if;
8078
8079                --  The expected type for a non-"null" argument is
8080                --  Root_Storage_Pool'Class.
8081
8082                Analyze_And_Resolve
8083                  (Get_Pragma_Arg (Arg1),
8084                   Typ => Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
8085             end if;
8086
8087             --  Finally, record the pool name (or null). Freeze.Freeze_Entity
8088             --  for an access type will use this information to set the
8089             --  appropriate attributes of the access type.
8090
8091             Default_Pool := Expression (Arg1);
8092
8093          ------------------------------------
8094          -- Disable_Atomic_Synchronization --
8095          ------------------------------------
8096
8097          --  pragma Disable_Atomic_Synchronization [(Entity)];
8098
8099          when Pragma_Disable_Atomic_Synchronization =>
8100             Process_Disable_Enable_Atomic_Sync (Name_Suppress);
8101
8102          -------------------
8103          -- Discard_Names --
8104          -------------------
8105
8106          --  pragma Discard_Names [([On =>] LOCAL_NAME)];
8107
8108          when Pragma_Discard_Names => Discard_Names : declare
8109             E    : Entity_Id;
8110             E_Id : Entity_Id;
8111
8112          begin
8113             Check_Ada_83_Warning;
8114
8115             --  Deal with configuration pragma case
8116
8117             if Arg_Count = 0 and then Is_Configuration_Pragma then
8118                Global_Discard_Names := True;
8119                return;
8120
8121             --  Otherwise, check correct appropriate context
8122
8123             else
8124                Check_Is_In_Decl_Part_Or_Package_Spec;
8125
8126                if Arg_Count = 0 then
8127
8128                   --  If there is no parameter, then from now on this pragma
8129                   --  applies to any enumeration, exception or tagged type
8130                   --  defined in the current declarative part, and recursively
8131                   --  to any nested scope.
8132
8133                   Set_Discard_Names (Current_Scope);
8134                   return;
8135
8136                else
8137                   Check_Arg_Count (1);
8138                   Check_Optional_Identifier (Arg1, Name_On);
8139                   Check_Arg_Is_Local_Name (Arg1);
8140
8141                   E_Id := Get_Pragma_Arg (Arg1);
8142
8143                   if Etype (E_Id) = Any_Type then
8144                      return;
8145                   else
8146                      E := Entity (E_Id);
8147                   end if;
8148
8149                   if (Is_First_Subtype (E)
8150                       and then
8151                         (Is_Enumeration_Type (E) or else Is_Tagged_Type (E)))
8152                     or else Ekind (E) = E_Exception
8153                   then
8154                      Set_Discard_Names (E);
8155                   else
8156                      Error_Pragma_Arg
8157                        ("inappropriate entity for pragma%", Arg1);
8158                   end if;
8159
8160                end if;
8161             end if;
8162          end Discard_Names;
8163
8164          ------------------------
8165          -- Dispatching_Domain --
8166          ------------------------
8167
8168          --  pragma Dispatching_Domain (EXPRESSION);
8169
8170          when Pragma_Dispatching_Domain => Dispatching_Domain : declare
8171             P   : constant Node_Id := Parent (N);
8172             Arg : Node_Id;
8173
8174          begin
8175             Ada_2012_Pragma;
8176             Check_No_Identifiers;
8177             Check_Arg_Count (1);
8178
8179             --  This pragma is born obsolete, but not the aspect
8180
8181             if not From_Aspect_Specification (N) then
8182                Check_Restriction
8183                  (No_Obsolescent_Features, Pragma_Identifier (N));
8184             end if;
8185
8186             if Nkind (P) = N_Task_Definition then
8187                Arg := Get_Pragma_Arg (Arg1);
8188
8189                --  The expression must be analyzed in the special manner
8190                --  described in "Handling of Default and Per-Object
8191                --  Expressions" in sem.ads.
8192
8193                Preanalyze_Spec_Expression (Arg, RTE (RE_Dispatching_Domain));
8194
8195             --  Anything else is incorrect
8196
8197             else
8198                Pragma_Misplaced;
8199             end if;
8200
8201             if Has_Pragma_Dispatching_Domain (P) then
8202                Error_Pragma ("duplicate pragma% not allowed");
8203             else
8204                Set_Has_Pragma_Dispatching_Domain (P, True);
8205
8206                if Nkind (P) = N_Task_Definition then
8207                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
8208                end if;
8209             end if;
8210          end Dispatching_Domain;
8211
8212          ---------------
8213          -- Elaborate --
8214          ---------------
8215
8216          --  pragma Elaborate (library_unit_NAME {, library_unit_NAME});
8217
8218          when Pragma_Elaborate => Elaborate : declare
8219             Arg   : Node_Id;
8220             Citem : Node_Id;
8221
8222          begin
8223             --  Pragma must be in context items list of a compilation unit
8224
8225             if not Is_In_Context_Clause then
8226                Pragma_Misplaced;
8227             end if;
8228
8229             --  Must be at least one argument
8230
8231             if Arg_Count = 0 then
8232                Error_Pragma ("pragma% requires at least one argument");
8233             end if;
8234
8235             --  In Ada 83 mode, there can be no items following it in the
8236             --  context list except other pragmas and implicit with clauses
8237             --  (e.g. those added by use of Rtsfind). In Ada 95 mode, this
8238             --  placement rule does not apply.
8239
8240             if Ada_Version = Ada_83 and then Comes_From_Source (N) then
8241                Citem := Next (N);
8242                while Present (Citem) loop
8243                   if Nkind (Citem) = N_Pragma
8244                     or else (Nkind (Citem) = N_With_Clause
8245                               and then Implicit_With (Citem))
8246                   then
8247                      null;
8248                   else
8249                      Error_Pragma
8250                        ("(Ada 83) pragma% must be at end of context clause");
8251                   end if;
8252
8253                   Next (Citem);
8254                end loop;
8255             end if;
8256
8257             --  Finally, the arguments must all be units mentioned in a with
8258             --  clause in the same context clause. Note we already checked (in
8259             --  Par.Prag) that the arguments are all identifiers or selected
8260             --  components.
8261
8262             Arg := Arg1;
8263             Outer : while Present (Arg) loop
8264                Citem := First (List_Containing (N));
8265                Inner : while Citem /= N loop
8266                   if Nkind (Citem) = N_With_Clause
8267                     and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
8268                   then
8269                      Set_Elaborate_Present (Citem, True);
8270                      Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
8271                      Generate_Reference (Entity (Name (Citem)), Citem);
8272
8273                      --  With the pragma present, elaboration calls on
8274                      --  subprograms from the named unit need no further
8275                      --  checks, as long as the pragma appears in the current
8276                      --  compilation unit. If the pragma appears in some unit
8277                      --  in the context, there might still be a need for an
8278                      --  Elaborate_All_Desirable from the current compilation
8279                      --  to the named unit, so we keep the check enabled.
8280
8281                      if In_Extended_Main_Source_Unit (N) then
8282                         Set_Suppress_Elaboration_Warnings
8283                           (Entity (Name (Citem)));
8284                      end if;
8285
8286                      exit Inner;
8287                   end if;
8288
8289                   Next (Citem);
8290                end loop Inner;
8291
8292                if Citem = N then
8293                   Error_Pragma_Arg
8294                     ("argument of pragma% is not withed unit", Arg);
8295                end if;
8296
8297                Next (Arg);
8298             end loop Outer;
8299
8300             --  Give a warning if operating in static mode with -gnatwl
8301             --  (elaboration warnings enabled) switch set.
8302
8303             if Elab_Warnings and not Dynamic_Elaboration_Checks then
8304                Error_Msg_N
8305                  ("?use of pragma Elaborate may not be safe", N);
8306                Error_Msg_N
8307                  ("?use pragma Elaborate_All instead if possible", N);
8308             end if;
8309          end Elaborate;
8310
8311          -------------------
8312          -- Elaborate_All --
8313          -------------------
8314
8315          --  pragma Elaborate_All (library_unit_NAME {, library_unit_NAME});
8316
8317          when Pragma_Elaborate_All => Elaborate_All : declare
8318             Arg   : Node_Id;
8319             Citem : Node_Id;
8320
8321          begin
8322             Check_Ada_83_Warning;
8323
8324             --  Pragma must be in context items list of a compilation unit
8325
8326             if not Is_In_Context_Clause then
8327                Pragma_Misplaced;
8328             end if;
8329
8330             --  Must be at least one argument
8331
8332             if Arg_Count = 0 then
8333                Error_Pragma ("pragma% requires at least one argument");
8334             end if;
8335
8336             --  Note: unlike pragma Elaborate, pragma Elaborate_All does not
8337             --  have to appear at the end of the context clause, but may
8338             --  appear mixed in with other items, even in Ada 83 mode.
8339
8340             --  Final check: the arguments must all be units mentioned in
8341             --  a with clause in the same context clause. Note that we
8342             --  already checked (in Par.Prag) that all the arguments are
8343             --  either identifiers or selected components.
8344
8345             Arg := Arg1;
8346             Outr : while Present (Arg) loop
8347                Citem := First (List_Containing (N));
8348                Innr : while Citem /= N loop
8349                   if Nkind (Citem) = N_With_Clause
8350                     and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
8351                   then
8352                      Set_Elaborate_All_Present (Citem, True);
8353                      Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
8354
8355                      --  Suppress warnings and elaboration checks on the named
8356                      --  unit if the pragma is in the current compilation, as
8357                      --  for pragma Elaborate.
8358
8359                      if In_Extended_Main_Source_Unit (N) then
8360                         Set_Suppress_Elaboration_Warnings
8361                           (Entity (Name (Citem)));
8362                      end if;
8363                      exit Innr;
8364                   end if;
8365
8366                   Next (Citem);
8367                end loop Innr;
8368
8369                if Citem = N then
8370                   Set_Error_Posted (N);
8371                   Error_Pragma_Arg
8372                     ("argument of pragma% is not withed unit", Arg);
8373                end if;
8374
8375                Next (Arg);
8376             end loop Outr;
8377          end Elaborate_All;
8378
8379          --------------------
8380          -- Elaborate_Body --
8381          --------------------
8382
8383          --  pragma Elaborate_Body [( library_unit_NAME )];
8384
8385          when Pragma_Elaborate_Body => Elaborate_Body : declare
8386             Cunit_Node : Node_Id;
8387             Cunit_Ent  : Entity_Id;
8388
8389          begin
8390             Check_Ada_83_Warning;
8391             Check_Valid_Library_Unit_Pragma;
8392
8393             if Nkind (N) = N_Null_Statement then
8394                return;
8395             end if;
8396
8397             Cunit_Node := Cunit (Current_Sem_Unit);
8398             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
8399
8400             if Nkind_In (Unit (Cunit_Node), N_Package_Body,
8401                                             N_Subprogram_Body)
8402             then
8403                Error_Pragma ("pragma% must refer to a spec, not a body");
8404             else
8405                Set_Body_Required (Cunit_Node, True);
8406                Set_Has_Pragma_Elaborate_Body (Cunit_Ent);
8407
8408                --  If we are in dynamic elaboration mode, then we suppress
8409                --  elaboration warnings for the unit, since it is definitely
8410                --  fine NOT to do dynamic checks at the first level (and such
8411                --  checks will be suppressed because no elaboration boolean
8412                --  is created for Elaborate_Body packages).
8413
8414                --  But in the static model of elaboration, Elaborate_Body is
8415                --  definitely NOT good enough to ensure elaboration safety on
8416                --  its own, since the body may WITH other units that are not
8417                --  safe from an elaboration point of view, so a client must
8418                --  still do an Elaborate_All on such units.
8419
8420                --  Debug flag -gnatdD restores the old behavior of 3.13, where
8421                --  Elaborate_Body always suppressed elab warnings.
8422
8423                if Dynamic_Elaboration_Checks or Debug_Flag_DD then
8424                   Set_Suppress_Elaboration_Warnings (Cunit_Ent);
8425                end if;
8426             end if;
8427          end Elaborate_Body;
8428
8429          ------------------------
8430          -- Elaboration_Checks --
8431          ------------------------
8432
8433          --  pragma Elaboration_Checks (Static | Dynamic);
8434
8435          when Pragma_Elaboration_Checks =>
8436             GNAT_Pragma;
8437             Check_Arg_Count (1);
8438             Check_Arg_Is_One_Of (Arg1, Name_Static, Name_Dynamic);
8439             Dynamic_Elaboration_Checks :=
8440               (Chars (Get_Pragma_Arg (Arg1)) = Name_Dynamic);
8441
8442          ---------------
8443          -- Eliminate --
8444          ---------------
8445
8446          --  pragma Eliminate (
8447          --      [Unit_Name  =>] IDENTIFIER | SELECTED_COMPONENT,
8448          --    [,[Entity     =>] IDENTIFIER |
8449          --                      SELECTED_COMPONENT |
8450          --                      STRING_LITERAL]
8451          --    [,                OVERLOADING_RESOLUTION]);
8452
8453          --  OVERLOADING_RESOLUTION ::= PARAMETER_AND_RESULT_TYPE_PROFILE |
8454          --                             SOURCE_LOCATION
8455
8456          --  PARAMETER_AND_RESULT_TYPE_PROFILE ::= PROCEDURE_PROFILE |
8457          --                                        FUNCTION_PROFILE
8458
8459          --  PROCEDURE_PROFILE ::= Parameter_Types => PARAMETER_TYPES
8460
8461          --  FUNCTION_PROFILE ::= [Parameter_Types => PARAMETER_TYPES,]
8462          --                       Result_Type => result_SUBTYPE_NAME]
8463
8464          --  PARAMETER_TYPES ::= (SUBTYPE_NAME {, SUBTYPE_NAME})
8465          --  SUBTYPE_NAME    ::= STRING_LITERAL
8466
8467          --  SOURCE_LOCATION ::= Source_Location => SOURCE_TRACE
8468          --  SOURCE_TRACE    ::= STRING_LITERAL
8469
8470          when Pragma_Eliminate => Eliminate : declare
8471             Args  : Args_List (1 .. 5);
8472             Names : constant Name_List (1 .. 5) := (
8473                       Name_Unit_Name,
8474                       Name_Entity,
8475                       Name_Parameter_Types,
8476                       Name_Result_Type,
8477                       Name_Source_Location);
8478
8479             Unit_Name       : Node_Id renames Args (1);
8480             Entity          : Node_Id renames Args (2);
8481             Parameter_Types : Node_Id renames Args (3);
8482             Result_Type     : Node_Id renames Args (4);
8483             Source_Location : Node_Id renames Args (5);
8484
8485          begin
8486             GNAT_Pragma;
8487             Check_Valid_Configuration_Pragma;
8488             Gather_Associations (Names, Args);
8489
8490             if No (Unit_Name) then
8491                Error_Pragma ("missing Unit_Name argument for pragma%");
8492             end if;
8493
8494             if No (Entity)
8495               and then (Present (Parameter_Types)
8496                           or else
8497                         Present (Result_Type)
8498                           or else
8499                         Present (Source_Location))
8500             then
8501                Error_Pragma ("missing Entity argument for pragma%");
8502             end if;
8503
8504             if (Present (Parameter_Types)
8505                   or else
8506                 Present (Result_Type))
8507               and then
8508                 Present (Source_Location)
8509             then
8510                Error_Pragma
8511                  ("parameter profile and source location cannot " &
8512                   "be used together in pragma%");
8513             end if;
8514
8515             Process_Eliminate_Pragma
8516               (N,
8517                Unit_Name,
8518                Entity,
8519                Parameter_Types,
8520                Result_Type,
8521                Source_Location);
8522          end Eliminate;
8523
8524          -----------------------------------
8525          -- Enable_Atomic_Synchronization --
8526          -----------------------------------
8527
8528          --  pragma Enable_Atomic_Synchronization [(Entity)];
8529
8530          when Pragma_Enable_Atomic_Synchronization =>
8531             Process_Disable_Enable_Atomic_Sync (Name_Unsuppress);
8532
8533          ------------
8534          -- Export --
8535          ------------
8536
8537          --  pragma Export (
8538          --    [   Convention    =>] convention_IDENTIFIER,
8539          --    [   Entity        =>] local_NAME
8540          --    [, [External_Name =>] static_string_EXPRESSION ]
8541          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
8542
8543          when Pragma_Export => Export : declare
8544             C      : Convention_Id;
8545             Def_Id : Entity_Id;
8546
8547             pragma Warnings (Off, C);
8548
8549          begin
8550             Check_Ada_83_Warning;
8551             Check_Arg_Order
8552               ((Name_Convention,
8553                 Name_Entity,
8554                 Name_External_Name,
8555                 Name_Link_Name));
8556             Check_At_Least_N_Arguments (2);
8557             Check_At_Most_N_Arguments  (4);
8558             Process_Convention (C, Def_Id);
8559
8560             if Ekind (Def_Id) /= E_Constant then
8561                Note_Possible_Modification
8562                  (Get_Pragma_Arg (Arg2), Sure => False);
8563             end if;
8564
8565             Process_Interface_Name (Def_Id, Arg3, Arg4);
8566             Set_Exported (Def_Id, Arg2);
8567
8568             --  If the entity is a deferred constant, propagate the information
8569             --  to the full view, because gigi elaborates the full view only.
8570
8571             if Ekind (Def_Id) = E_Constant
8572               and then Present (Full_View (Def_Id))
8573             then
8574                declare
8575                   Id2 : constant Entity_Id := Full_View (Def_Id);
8576                begin
8577                   Set_Is_Exported    (Id2, Is_Exported          (Def_Id));
8578                   Set_First_Rep_Item (Id2, First_Rep_Item       (Def_Id));
8579                   Set_Interface_Name (Id2, Einfo.Interface_Name (Def_Id));
8580                end;
8581             end if;
8582          end Export;
8583
8584          ----------------------
8585          -- Export_Exception --
8586          ----------------------
8587
8588          --  pragma Export_Exception (
8589          --        [Internal         =>] LOCAL_NAME
8590          --     [, [External         =>] EXTERNAL_SYMBOL]
8591          --     [, [Form     =>] Ada | VMS]
8592          --     [, [Code     =>] static_integer_EXPRESSION]);
8593
8594          when Pragma_Export_Exception => Export_Exception : declare
8595             Args  : Args_List (1 .. 4);
8596             Names : constant Name_List (1 .. 4) := (
8597                       Name_Internal,
8598                       Name_External,
8599                       Name_Form,
8600                       Name_Code);
8601
8602             Internal : Node_Id renames Args (1);
8603             External : Node_Id renames Args (2);
8604             Form     : Node_Id renames Args (3);
8605             Code     : Node_Id renames Args (4);
8606
8607          begin
8608             GNAT_Pragma;
8609
8610             if Inside_A_Generic then
8611                Error_Pragma ("pragma% cannot be used for generic entities");
8612             end if;
8613
8614             Gather_Associations (Names, Args);
8615             Process_Extended_Import_Export_Exception_Pragma (
8616               Arg_Internal => Internal,
8617               Arg_External => External,
8618               Arg_Form     => Form,
8619               Arg_Code     => Code);
8620
8621             if not Is_VMS_Exception (Entity (Internal)) then
8622                Set_Exported (Entity (Internal), Internal);
8623             end if;
8624          end Export_Exception;
8625
8626          ---------------------
8627          -- Export_Function --
8628          ---------------------
8629
8630          --  pragma Export_Function (
8631          --        [Internal         =>] LOCAL_NAME
8632          --     [, [External         =>] EXTERNAL_SYMBOL]
8633          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8634          --     [, [Result_Type      =>] TYPE_DESIGNATOR]
8635          --     [, [Mechanism        =>] MECHANISM]
8636          --     [, [Result_Mechanism =>] MECHANISM_NAME]);
8637
8638          --  EXTERNAL_SYMBOL ::=
8639          --    IDENTIFIER
8640          --  | static_string_EXPRESSION
8641
8642          --  PARAMETER_TYPES ::=
8643          --    null
8644          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8645
8646          --  TYPE_DESIGNATOR ::=
8647          --    subtype_NAME
8648          --  | subtype_Name ' Access
8649
8650          --  MECHANISM ::=
8651          --    MECHANISM_NAME
8652          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8653
8654          --  MECHANISM_ASSOCIATION ::=
8655          --    [formal_parameter_NAME =>] MECHANISM_NAME
8656
8657          --  MECHANISM_NAME ::=
8658          --    Value
8659          --  | Reference
8660          --  | Descriptor [([Class =>] CLASS_NAME)]
8661
8662          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8663
8664          when Pragma_Export_Function => Export_Function : declare
8665             Args  : Args_List (1 .. 6);
8666             Names : constant Name_List (1 .. 6) := (
8667                       Name_Internal,
8668                       Name_External,
8669                       Name_Parameter_Types,
8670                       Name_Result_Type,
8671                       Name_Mechanism,
8672                       Name_Result_Mechanism);
8673
8674             Internal         : Node_Id renames Args (1);
8675             External         : Node_Id renames Args (2);
8676             Parameter_Types  : Node_Id renames Args (3);
8677             Result_Type      : Node_Id renames Args (4);
8678             Mechanism        : Node_Id renames Args (5);
8679             Result_Mechanism : Node_Id renames Args (6);
8680
8681          begin
8682             GNAT_Pragma;
8683             Gather_Associations (Names, Args);
8684             Process_Extended_Import_Export_Subprogram_Pragma (
8685               Arg_Internal         => Internal,
8686               Arg_External         => External,
8687               Arg_Parameter_Types  => Parameter_Types,
8688               Arg_Result_Type      => Result_Type,
8689               Arg_Mechanism        => Mechanism,
8690               Arg_Result_Mechanism => Result_Mechanism);
8691          end Export_Function;
8692
8693          -------------------
8694          -- Export_Object --
8695          -------------------
8696
8697          --  pragma Export_Object (
8698          --        [Internal =>] LOCAL_NAME
8699          --     [, [External =>] EXTERNAL_SYMBOL]
8700          --     [, [Size     =>] EXTERNAL_SYMBOL]);
8701
8702          --  EXTERNAL_SYMBOL ::=
8703          --    IDENTIFIER
8704          --  | static_string_EXPRESSION
8705
8706          --  PARAMETER_TYPES ::=
8707          --    null
8708          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8709
8710          --  TYPE_DESIGNATOR ::=
8711          --    subtype_NAME
8712          --  | subtype_Name ' Access
8713
8714          --  MECHANISM ::=
8715          --    MECHANISM_NAME
8716          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8717
8718          --  MECHANISM_ASSOCIATION ::=
8719          --    [formal_parameter_NAME =>] MECHANISM_NAME
8720
8721          --  MECHANISM_NAME ::=
8722          --    Value
8723          --  | Reference
8724          --  | Descriptor [([Class =>] CLASS_NAME)]
8725
8726          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8727
8728          when Pragma_Export_Object => Export_Object : declare
8729             Args  : Args_List (1 .. 3);
8730             Names : constant Name_List (1 .. 3) := (
8731                       Name_Internal,
8732                       Name_External,
8733                       Name_Size);
8734
8735             Internal : Node_Id renames Args (1);
8736             External : Node_Id renames Args (2);
8737             Size     : Node_Id renames Args (3);
8738
8739          begin
8740             GNAT_Pragma;
8741             Gather_Associations (Names, Args);
8742             Process_Extended_Import_Export_Object_Pragma (
8743               Arg_Internal => Internal,
8744               Arg_External => External,
8745               Arg_Size     => Size);
8746          end Export_Object;
8747
8748          ----------------------
8749          -- Export_Procedure --
8750          ----------------------
8751
8752          --  pragma Export_Procedure (
8753          --        [Internal         =>] LOCAL_NAME
8754          --     [, [External         =>] EXTERNAL_SYMBOL]
8755          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8756          --     [, [Mechanism        =>] MECHANISM]);
8757
8758          --  EXTERNAL_SYMBOL ::=
8759          --    IDENTIFIER
8760          --  | static_string_EXPRESSION
8761
8762          --  PARAMETER_TYPES ::=
8763          --    null
8764          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8765
8766          --  TYPE_DESIGNATOR ::=
8767          --    subtype_NAME
8768          --  | subtype_Name ' Access
8769
8770          --  MECHANISM ::=
8771          --    MECHANISM_NAME
8772          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8773
8774          --  MECHANISM_ASSOCIATION ::=
8775          --    [formal_parameter_NAME =>] MECHANISM_NAME
8776
8777          --  MECHANISM_NAME ::=
8778          --    Value
8779          --  | Reference
8780          --  | Descriptor [([Class =>] CLASS_NAME)]
8781
8782          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8783
8784          when Pragma_Export_Procedure => Export_Procedure : declare
8785             Args  : Args_List (1 .. 4);
8786             Names : constant Name_List (1 .. 4) := (
8787                       Name_Internal,
8788                       Name_External,
8789                       Name_Parameter_Types,
8790                       Name_Mechanism);
8791
8792             Internal        : Node_Id renames Args (1);
8793             External        : Node_Id renames Args (2);
8794             Parameter_Types : Node_Id renames Args (3);
8795             Mechanism       : Node_Id renames Args (4);
8796
8797          begin
8798             GNAT_Pragma;
8799             Gather_Associations (Names, Args);
8800             Process_Extended_Import_Export_Subprogram_Pragma (
8801               Arg_Internal        => Internal,
8802               Arg_External        => External,
8803               Arg_Parameter_Types => Parameter_Types,
8804               Arg_Mechanism       => Mechanism);
8805          end Export_Procedure;
8806
8807          ------------------
8808          -- Export_Value --
8809          ------------------
8810
8811          --  pragma Export_Value (
8812          --     [Value     =>] static_integer_EXPRESSION,
8813          --     [Link_Name =>] static_string_EXPRESSION);
8814
8815          when Pragma_Export_Value =>
8816             GNAT_Pragma;
8817             Check_Arg_Order ((Name_Value, Name_Link_Name));
8818             Check_Arg_Count (2);
8819
8820             Check_Optional_Identifier (Arg1, Name_Value);
8821             Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
8822
8823             Check_Optional_Identifier (Arg2, Name_Link_Name);
8824             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
8825
8826          -----------------------------
8827          -- Export_Valued_Procedure --
8828          -----------------------------
8829
8830          --  pragma Export_Valued_Procedure (
8831          --        [Internal         =>] LOCAL_NAME
8832          --     [, [External         =>] EXTERNAL_SYMBOL,]
8833          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8834          --     [, [Mechanism        =>] MECHANISM]);
8835
8836          --  EXTERNAL_SYMBOL ::=
8837          --    IDENTIFIER
8838          --  | static_string_EXPRESSION
8839
8840          --  PARAMETER_TYPES ::=
8841          --    null
8842          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8843
8844          --  TYPE_DESIGNATOR ::=
8845          --    subtype_NAME
8846          --  | subtype_Name ' Access
8847
8848          --  MECHANISM ::=
8849          --    MECHANISM_NAME
8850          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8851
8852          --  MECHANISM_ASSOCIATION ::=
8853          --    [formal_parameter_NAME =>] MECHANISM_NAME
8854
8855          --  MECHANISM_NAME ::=
8856          --    Value
8857          --  | Reference
8858          --  | Descriptor [([Class =>] CLASS_NAME)]
8859
8860          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8861
8862          when Pragma_Export_Valued_Procedure =>
8863          Export_Valued_Procedure : declare
8864             Args  : Args_List (1 .. 4);
8865             Names : constant Name_List (1 .. 4) := (
8866                       Name_Internal,
8867                       Name_External,
8868                       Name_Parameter_Types,
8869                       Name_Mechanism);
8870
8871             Internal        : Node_Id renames Args (1);
8872             External        : Node_Id renames Args (2);
8873             Parameter_Types : Node_Id renames Args (3);
8874             Mechanism       : Node_Id renames Args (4);
8875
8876          begin
8877             GNAT_Pragma;
8878             Gather_Associations (Names, Args);
8879             Process_Extended_Import_Export_Subprogram_Pragma (
8880               Arg_Internal        => Internal,
8881               Arg_External        => External,
8882               Arg_Parameter_Types => Parameter_Types,
8883               Arg_Mechanism       => Mechanism);
8884          end Export_Valued_Procedure;
8885
8886          -------------------
8887          -- Extend_System --
8888          -------------------
8889
8890          --  pragma Extend_System ([Name =>] Identifier);
8891
8892          when Pragma_Extend_System => Extend_System : declare
8893          begin
8894             GNAT_Pragma;
8895             Check_Valid_Configuration_Pragma;
8896             Check_Arg_Count (1);
8897             Check_Optional_Identifier (Arg1, Name_Name);
8898             Check_Arg_Is_Identifier (Arg1);
8899
8900             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
8901
8902             if Name_Len > 4
8903               and then Name_Buffer (1 .. 4) = "aux_"
8904             then
8905                if Present (System_Extend_Pragma_Arg) then
8906                   if Chars (Get_Pragma_Arg (Arg1)) =
8907                      Chars (Expression (System_Extend_Pragma_Arg))
8908                   then
8909                      null;
8910                   else
8911                      Error_Msg_Sloc := Sloc (System_Extend_Pragma_Arg);
8912                      Error_Pragma ("pragma% conflicts with that #");
8913                   end if;
8914
8915                else
8916                   System_Extend_Pragma_Arg := Arg1;
8917
8918                   if not GNAT_Mode then
8919                      System_Extend_Unit := Arg1;
8920                   end if;
8921                end if;
8922             else
8923                Error_Pragma ("incorrect name for pragma%, must be Aux_xxx");
8924             end if;
8925          end Extend_System;
8926
8927          ------------------------
8928          -- Extensions_Allowed --
8929          ------------------------
8930
8931          --  pragma Extensions_Allowed (ON | OFF);
8932
8933          when Pragma_Extensions_Allowed =>
8934             GNAT_Pragma;
8935             Check_Arg_Count (1);
8936             Check_No_Identifiers;
8937             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
8938
8939             if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
8940                Extensions_Allowed := True;
8941                Ada_Version := Ada_Version_Type'Last;
8942
8943             else
8944                Extensions_Allowed := False;
8945                Ada_Version := Ada_Version_Explicit;
8946             end if;
8947
8948          --------------
8949          -- External --
8950          --------------
8951
8952          --  pragma External (
8953          --    [   Convention    =>] convention_IDENTIFIER,
8954          --    [   Entity        =>] local_NAME
8955          --    [, [External_Name =>] static_string_EXPRESSION ]
8956          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
8957
8958          when Pragma_External => External : declare
8959                Def_Id : Entity_Id;
8960
8961                C : Convention_Id;
8962                pragma Warnings (Off, C);
8963
8964          begin
8965             GNAT_Pragma;
8966             Check_Arg_Order
8967               ((Name_Convention,
8968                 Name_Entity,
8969                 Name_External_Name,
8970                 Name_Link_Name));
8971             Check_At_Least_N_Arguments (2);
8972             Check_At_Most_N_Arguments  (4);
8973             Process_Convention (C, Def_Id);
8974             Note_Possible_Modification
8975               (Get_Pragma_Arg (Arg2), Sure => False);
8976             Process_Interface_Name (Def_Id, Arg3, Arg4);
8977             Set_Exported (Def_Id, Arg2);
8978          end External;
8979
8980          --------------------------
8981          -- External_Name_Casing --
8982          --------------------------
8983
8984          --  pragma External_Name_Casing (
8985          --    UPPERCASE | LOWERCASE
8986          --    [, AS_IS | UPPERCASE | LOWERCASE]);
8987
8988          when Pragma_External_Name_Casing => External_Name_Casing : declare
8989          begin
8990             GNAT_Pragma;
8991             Check_No_Identifiers;
8992
8993             if Arg_Count = 2 then
8994                Check_Arg_Is_One_Of
8995                  (Arg2, Name_As_Is, Name_Uppercase, Name_Lowercase);
8996
8997                case Chars (Get_Pragma_Arg (Arg2)) is
8998                   when Name_As_Is     =>
8999                      Opt.External_Name_Exp_Casing := As_Is;
9000
9001                   when Name_Uppercase =>
9002                      Opt.External_Name_Exp_Casing := Uppercase;
9003
9004                   when Name_Lowercase =>
9005                      Opt.External_Name_Exp_Casing := Lowercase;
9006
9007                   when others =>
9008                      null;
9009                end case;
9010
9011             else
9012                Check_Arg_Count (1);
9013             end if;
9014
9015             Check_Arg_Is_One_Of (Arg1, Name_Uppercase, Name_Lowercase);
9016
9017             case Chars (Get_Pragma_Arg (Arg1)) is
9018                when Name_Uppercase =>
9019                   Opt.External_Name_Imp_Casing := Uppercase;
9020
9021                when Name_Lowercase =>
9022                   Opt.External_Name_Imp_Casing := Lowercase;
9023
9024                when others =>
9025                   null;
9026             end case;
9027          end External_Name_Casing;
9028
9029          --------------------------
9030          -- Favor_Top_Level --
9031          --------------------------
9032
9033          --  pragma Favor_Top_Level (type_NAME);
9034
9035          when Pragma_Favor_Top_Level => Favor_Top_Level : declare
9036                Named_Entity : Entity_Id;
9037
9038          begin
9039             GNAT_Pragma;
9040             Check_No_Identifiers;
9041             Check_Arg_Count (1);
9042             Check_Arg_Is_Local_Name (Arg1);
9043             Named_Entity := Entity (Get_Pragma_Arg (Arg1));
9044
9045             --  If it's an access-to-subprogram type (in particular, not a
9046             --  subtype), set the flag on that type.
9047
9048             if Is_Access_Subprogram_Type (Named_Entity) then
9049                Set_Can_Use_Internal_Rep (Named_Entity, False);
9050
9051             --  Otherwise it's an error (name denotes the wrong sort of entity)
9052
9053             else
9054                Error_Pragma_Arg
9055                  ("access-to-subprogram type expected",
9056                   Get_Pragma_Arg (Arg1));
9057             end if;
9058          end Favor_Top_Level;
9059
9060          ---------------
9061          -- Fast_Math --
9062          ---------------
9063
9064          --  pragma Fast_Math;
9065
9066          when Pragma_Fast_Math =>
9067             GNAT_Pragma;
9068             Check_No_Identifiers;
9069             Check_Valid_Configuration_Pragma;
9070             Fast_Math := True;
9071
9072          ---------------------------
9073          -- Finalize_Storage_Only --
9074          ---------------------------
9075
9076          --  pragma Finalize_Storage_Only (first_subtype_LOCAL_NAME);
9077
9078          when Pragma_Finalize_Storage_Only => Finalize_Storage : declare
9079             Assoc   : constant Node_Id := Arg1;
9080             Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
9081             Typ     : Entity_Id;
9082
9083          begin
9084             GNAT_Pragma;
9085             Check_No_Identifiers;
9086             Check_Arg_Count (1);
9087             Check_Arg_Is_Local_Name (Arg1);
9088
9089             Find_Type (Type_Id);
9090             Typ := Entity (Type_Id);
9091
9092             if Typ = Any_Type
9093               or else Rep_Item_Too_Early (Typ, N)
9094             then
9095                return;
9096             else
9097                Typ := Underlying_Type (Typ);
9098             end if;
9099
9100             if not Is_Controlled (Typ) then
9101                Error_Pragma ("pragma% must specify controlled type");
9102             end if;
9103
9104             Check_First_Subtype (Arg1);
9105
9106             if Finalize_Storage_Only (Typ) then
9107                Error_Pragma ("duplicate pragma%, only one allowed");
9108
9109             elsif not Rep_Item_Too_Late (Typ, N) then
9110                Set_Finalize_Storage_Only (Base_Type (Typ), True);
9111             end if;
9112          end Finalize_Storage;
9113
9114          --------------------------
9115          -- Float_Representation --
9116          --------------------------
9117
9118          --  pragma Float_Representation (FLOAT_REP[, float_type_LOCAL_NAME]);
9119
9120          --  FLOAT_REP ::= VAX_Float | IEEE_Float
9121
9122          when Pragma_Float_Representation => Float_Representation : declare
9123             Argx : Node_Id;
9124             Digs : Nat;
9125             Ent  : Entity_Id;
9126
9127          begin
9128             GNAT_Pragma;
9129
9130             if Arg_Count = 1 then
9131                Check_Valid_Configuration_Pragma;
9132             else
9133                Check_Arg_Count (2);
9134                Check_Optional_Identifier (Arg2, Name_Entity);
9135                Check_Arg_Is_Local_Name (Arg2);
9136             end if;
9137
9138             Check_No_Identifier (Arg1);
9139             Check_Arg_Is_One_Of (Arg1, Name_VAX_Float, Name_IEEE_Float);
9140
9141             if not OpenVMS_On_Target then
9142                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9143                   Error_Pragma
9144                     ("?pragma% ignored (applies only to Open'V'M'S)");
9145                end if;
9146
9147                return;
9148             end if;
9149
9150             --  One argument case
9151
9152             if Arg_Count = 1 then
9153                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9154                   if Opt.Float_Format = 'I' then
9155                      Error_Pragma ("'I'E'E'E format previously specified");
9156                   end if;
9157
9158                   Opt.Float_Format := 'V';
9159
9160                else
9161                   if Opt.Float_Format = 'V' then
9162                      Error_Pragma ("'V'A'X format previously specified");
9163                   end if;
9164
9165                   Opt.Float_Format := 'I';
9166                end if;
9167
9168                Set_Standard_Fpt_Formats;
9169
9170             --  Two argument case
9171
9172             else
9173                Argx := Get_Pragma_Arg (Arg2);
9174
9175                if not Is_Entity_Name (Argx)
9176                  or else not Is_Floating_Point_Type (Entity (Argx))
9177                then
9178                   Error_Pragma_Arg
9179                     ("second argument of% pragma must be floating-point type",
9180                      Arg2);
9181                end if;
9182
9183                Ent  := Entity (Argx);
9184                Digs := UI_To_Int (Digits_Value (Ent));
9185
9186                --  Two arguments, VAX_Float case
9187
9188                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9189                   case Digs is
9190                      when  6 => Set_F_Float (Ent);
9191                      when  9 => Set_D_Float (Ent);
9192                      when 15 => Set_G_Float (Ent);
9193
9194                      when others =>
9195                         Error_Pragma_Arg
9196                           ("wrong digits value, must be 6,9 or 15", Arg2);
9197                   end case;
9198
9199                --  Two arguments, IEEE_Float case
9200
9201                else
9202                   case Digs is
9203                      when  6 => Set_IEEE_Short (Ent);
9204                      when 15 => Set_IEEE_Long  (Ent);
9205
9206                      when others =>
9207                         Error_Pragma_Arg
9208                           ("wrong digits value, must be 6 or 15", Arg2);
9209                   end case;
9210                end if;
9211             end if;
9212          end Float_Representation;
9213
9214          -----------
9215          -- Ident --
9216          -----------
9217
9218          --  pragma Ident (static_string_EXPRESSION)
9219
9220          --  Note: pragma Comment shares this processing. Pragma Comment is
9221          --  identical to Ident, except that the restriction of the argument to
9222          --  31 characters and the placement restrictions are not enforced for
9223          --  pragma Comment.
9224
9225          when Pragma_Ident | Pragma_Comment => Ident : declare
9226             Str : Node_Id;
9227
9228          begin
9229             GNAT_Pragma;
9230             Check_Arg_Count (1);
9231             Check_No_Identifiers;
9232             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
9233             Store_Note (N);
9234
9235             --  For pragma Ident, preserve DEC compatibility by requiring the
9236             --  pragma to appear in a declarative part or package spec.
9237
9238             if Prag_Id = Pragma_Ident then
9239                Check_Is_In_Decl_Part_Or_Package_Spec;
9240             end if;
9241
9242             Str := Expr_Value_S (Get_Pragma_Arg (Arg1));
9243
9244             declare
9245                CS : Node_Id;
9246                GP : Node_Id;
9247
9248             begin
9249                GP := Parent (Parent (N));
9250
9251                if Nkind_In (GP, N_Package_Declaration,
9252                                 N_Generic_Package_Declaration)
9253                then
9254                   GP := Parent (GP);
9255                end if;
9256
9257                --  If we have a compilation unit, then record the ident value,
9258                --  checking for improper duplication.
9259
9260                if Nkind (GP) = N_Compilation_Unit then
9261                   CS := Ident_String (Current_Sem_Unit);
9262
9263                   if Present (CS) then
9264
9265                      --  For Ident, we do not permit multiple instances
9266
9267                      if Prag_Id = Pragma_Ident then
9268                         Error_Pragma ("duplicate% pragma not permitted");
9269
9270                      --  For Comment, we concatenate the string, unless we want
9271                      --  to preserve the tree structure for ASIS.
9272
9273                      elsif not ASIS_Mode then
9274                         Start_String (Strval (CS));
9275                         Store_String_Char (' ');
9276                         Store_String_Chars (Strval (Str));
9277                         Set_Strval (CS, End_String);
9278                      end if;
9279
9280                   else
9281                      --  In VMS, the effect of IDENT is achieved by passing
9282                      --  --identification=name as a --for-linker switch.
9283
9284                      if OpenVMS_On_Target then
9285                         Start_String;
9286                         Store_String_Chars
9287                           ("--for-linker=--identification=");
9288                         String_To_Name_Buffer (Strval (Str));
9289                         Store_String_Chars (Name_Buffer (1 .. Name_Len));
9290
9291                         --  Only the last processed IDENT is saved. The main
9292                         --  purpose is so an IDENT associated with a main
9293                         --  procedure will be used in preference to an IDENT
9294                         --  associated with a with'd package.
9295
9296                         Replace_Linker_Option_String
9297                           (End_String, "--for-linker=--identification=");
9298                      end if;
9299
9300                      Set_Ident_String (Current_Sem_Unit, Str);
9301                   end if;
9302
9303                --  For subunits, we just ignore the Ident, since in GNAT these
9304                --  are not separate object files, and hence not separate units
9305                --  in the unit table.
9306
9307                elsif Nkind (GP) = N_Subunit then
9308                   null;
9309
9310                --  Otherwise we have a misplaced pragma Ident, but we ignore
9311                --  this if we are in an instantiation, since it comes from
9312                --  a generic, and has no relevance to the instantiation.
9313
9314                elsif Prag_Id = Pragma_Ident then
9315                   if Instantiation_Location (Loc) = No_Location then
9316                      Error_Pragma ("pragma% only allowed at outer level");
9317                   end if;
9318                end if;
9319             end;
9320          end Ident;
9321
9322          ----------------------------
9323          -- Implementation_Defined --
9324          ----------------------------
9325
9326          --  pragma Implementation_Defined (local_NAME);
9327
9328          --  Marks previously declared entity as implementation defined. For
9329          --  an overloaded entity, applies to the most recent homonym.
9330
9331          --  pragma Implementation_Defined;
9332
9333          --  The form with no arguments appears anywhere within a scope, most
9334          --  typically a package spec, and indicates that all entities that are
9335          --  defined within the package spec are Implementation_Defined.
9336
9337          when Pragma_Implementation_Defined => Implementation_Defined : declare
9338             Ent : Entity_Id;
9339
9340          begin
9341             Check_No_Identifiers;
9342
9343             --  Form with no arguments
9344
9345             if Arg_Count = 0 then
9346                Set_Is_Implementation_Defined (Current_Scope);
9347
9348             --  Form with one argument
9349
9350             else
9351                Check_Arg_Count (1);
9352                Check_Arg_Is_Local_Name (Arg1);
9353                Ent := Entity (Get_Pragma_Arg (Arg1));
9354                Set_Is_Implementation_Defined (Ent);
9355             end if;
9356          end Implementation_Defined;
9357
9358          -----------------
9359          -- Implemented --
9360          -----------------
9361
9362          --  pragma Implemented (procedure_LOCAL_NAME, implementation_kind);
9363          --  implementation_kind ::=
9364          --    By_Entry | By_Protected_Procedure | By_Any | Optional
9365
9366          --  "By_Any" and "Optional" are treated as synonyms in order to
9367          --  support Ada 2012 aspect Synchronization.
9368
9369          when Pragma_Implemented => Implemented : declare
9370             Proc_Id : Entity_Id;
9371             Typ     : Entity_Id;
9372
9373          begin
9374             Ada_2012_Pragma;
9375             Check_Arg_Count (2);
9376             Check_No_Identifiers;
9377             Check_Arg_Is_Identifier (Arg1);
9378             Check_Arg_Is_Local_Name (Arg1);
9379             Check_Arg_Is_One_Of (Arg2,
9380               Name_By_Any,
9381               Name_By_Entry,
9382               Name_By_Protected_Procedure,
9383               Name_Optional);
9384
9385             --  Extract the name of the local procedure
9386
9387             Proc_Id := Entity (Get_Pragma_Arg (Arg1));
9388
9389             --  Ada 2012 (AI05-0030): The procedure_LOCAL_NAME must denote a
9390             --  primitive procedure of a synchronized tagged type.
9391
9392             if Ekind (Proc_Id) = E_Procedure
9393               and then Is_Primitive (Proc_Id)
9394               and then Present (First_Formal (Proc_Id))
9395             then
9396                Typ := Etype (First_Formal (Proc_Id));
9397
9398                if Is_Tagged_Type (Typ)
9399                  and then
9400
9401                   --  Check for a protected, a synchronized or a task interface
9402
9403                    ((Is_Interface (Typ)
9404                        and then Is_Synchronized_Interface (Typ))
9405
9406                   --  Check for a protected type or a task type that implements
9407                   --  an interface.
9408
9409                    or else
9410                     (Is_Concurrent_Record_Type (Typ)
9411                        and then Present (Interfaces (Typ)))
9412
9413                   --  Check for a private record extension with keyword
9414                   --  "synchronized".
9415
9416                    or else
9417                     (Ekind_In (Typ, E_Record_Type_With_Private,
9418                                     E_Record_Subtype_With_Private)
9419                        and then Synchronized_Present (Parent (Typ))))
9420                then
9421                   null;
9422                else
9423                   Error_Pragma_Arg
9424                     ("controlling formal must be of synchronized " &
9425                      "tagged type", Arg1);
9426                   return;
9427                end if;
9428
9429             --  Procedures declared inside a protected type must be accepted
9430
9431             elsif Ekind (Proc_Id) = E_Procedure
9432               and then Is_Protected_Type (Scope (Proc_Id))
9433             then
9434                null;
9435
9436             --  The first argument is not a primitive procedure
9437
9438             else
9439                Error_Pragma_Arg
9440                  ("pragma % must be applied to a primitive procedure", Arg1);
9441                return;
9442             end if;
9443
9444             --  Ada 2012 (AI05-0030): Cannot apply the implementation_kind
9445             --  By_Protected_Procedure to the primitive procedure of a task
9446             --  interface.
9447
9448             if Chars (Arg2) = Name_By_Protected_Procedure
9449               and then Is_Interface (Typ)
9450               and then Is_Task_Interface (Typ)
9451             then
9452                Error_Pragma_Arg
9453                  ("implementation kind By_Protected_Procedure cannot be " &
9454                   "applied to a task interface primitive", Arg2);
9455                return;
9456             end if;
9457
9458             Record_Rep_Item (Proc_Id, N);
9459          end Implemented;
9460
9461          ----------------------
9462          -- Implicit_Packing --
9463          ----------------------
9464
9465          --  pragma Implicit_Packing;
9466
9467          when Pragma_Implicit_Packing =>
9468             GNAT_Pragma;
9469             Check_Arg_Count (0);
9470             Implicit_Packing := True;
9471
9472          ------------
9473          -- Import --
9474          ------------
9475
9476          --  pragma Import (
9477          --       [Convention    =>] convention_IDENTIFIER,
9478          --       [Entity        =>] local_NAME
9479          --    [, [External_Name =>] static_string_EXPRESSION ]
9480          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
9481
9482          when Pragma_Import =>
9483             Check_Ada_83_Warning;
9484             Check_Arg_Order
9485               ((Name_Convention,
9486                 Name_Entity,
9487                 Name_External_Name,
9488                 Name_Link_Name));
9489             Check_At_Least_N_Arguments (2);
9490             Check_At_Most_N_Arguments  (4);
9491             Process_Import_Or_Interface;
9492
9493          ----------------------
9494          -- Import_Exception --
9495          ----------------------
9496
9497          --  pragma Import_Exception (
9498          --        [Internal         =>] LOCAL_NAME
9499          --     [, [External         =>] EXTERNAL_SYMBOL]
9500          --     [, [Form     =>] Ada | VMS]
9501          --     [, [Code     =>] static_integer_EXPRESSION]);
9502
9503          when Pragma_Import_Exception => Import_Exception : declare
9504             Args  : Args_List (1 .. 4);
9505             Names : constant Name_List (1 .. 4) := (
9506                       Name_Internal,
9507                       Name_External,
9508                       Name_Form,
9509                       Name_Code);
9510
9511             Internal : Node_Id renames Args (1);
9512             External : Node_Id renames Args (2);
9513             Form     : Node_Id renames Args (3);
9514             Code     : Node_Id renames Args (4);
9515
9516          begin
9517             GNAT_Pragma;
9518             Gather_Associations (Names, Args);
9519
9520             if Present (External) and then Present (Code) then
9521                Error_Pragma
9522                  ("cannot give both External and Code options for pragma%");
9523             end if;
9524
9525             Process_Extended_Import_Export_Exception_Pragma (
9526               Arg_Internal => Internal,
9527               Arg_External => External,
9528               Arg_Form     => Form,
9529               Arg_Code     => Code);
9530
9531             if not Is_VMS_Exception (Entity (Internal)) then
9532                Set_Imported (Entity (Internal));
9533             end if;
9534          end Import_Exception;
9535
9536          ---------------------
9537          -- Import_Function --
9538          ---------------------
9539
9540          --  pragma Import_Function (
9541          --        [Internal                 =>] LOCAL_NAME,
9542          --     [, [External                 =>] EXTERNAL_SYMBOL]
9543          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9544          --     [, [Result_Type              =>] SUBTYPE_MARK]
9545          --     [, [Mechanism                =>] MECHANISM]
9546          --     [, [Result_Mechanism         =>] MECHANISM_NAME]
9547          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9548
9549          --  EXTERNAL_SYMBOL ::=
9550          --    IDENTIFIER
9551          --  | static_string_EXPRESSION
9552
9553          --  PARAMETER_TYPES ::=
9554          --    null
9555          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9556
9557          --  TYPE_DESIGNATOR ::=
9558          --    subtype_NAME
9559          --  | subtype_Name ' Access
9560
9561          --  MECHANISM ::=
9562          --    MECHANISM_NAME
9563          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9564
9565          --  MECHANISM_ASSOCIATION ::=
9566          --    [formal_parameter_NAME =>] MECHANISM_NAME
9567
9568          --  MECHANISM_NAME ::=
9569          --    Value
9570          --  | Reference
9571          --  | Descriptor [([Class =>] CLASS_NAME)]
9572
9573          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9574
9575          when Pragma_Import_Function => Import_Function : declare
9576             Args  : Args_List (1 .. 7);
9577             Names : constant Name_List (1 .. 7) := (
9578                       Name_Internal,
9579                       Name_External,
9580                       Name_Parameter_Types,
9581                       Name_Result_Type,
9582                       Name_Mechanism,
9583                       Name_Result_Mechanism,
9584                       Name_First_Optional_Parameter);
9585
9586             Internal                 : Node_Id renames Args (1);
9587             External                 : Node_Id renames Args (2);
9588             Parameter_Types          : Node_Id renames Args (3);
9589             Result_Type              : Node_Id renames Args (4);
9590             Mechanism                : Node_Id renames Args (5);
9591             Result_Mechanism         : Node_Id renames Args (6);
9592             First_Optional_Parameter : Node_Id renames Args (7);
9593
9594          begin
9595             GNAT_Pragma;
9596             Gather_Associations (Names, Args);
9597             Process_Extended_Import_Export_Subprogram_Pragma (
9598               Arg_Internal                 => Internal,
9599               Arg_External                 => External,
9600               Arg_Parameter_Types          => Parameter_Types,
9601               Arg_Result_Type              => Result_Type,
9602               Arg_Mechanism                => Mechanism,
9603               Arg_Result_Mechanism         => Result_Mechanism,
9604               Arg_First_Optional_Parameter => First_Optional_Parameter);
9605          end Import_Function;
9606
9607          -------------------
9608          -- Import_Object --
9609          -------------------
9610
9611          --  pragma Import_Object (
9612          --        [Internal =>] LOCAL_NAME
9613          --     [, [External =>] EXTERNAL_SYMBOL]
9614          --     [, [Size     =>] EXTERNAL_SYMBOL]);
9615
9616          --  EXTERNAL_SYMBOL ::=
9617          --    IDENTIFIER
9618          --  | static_string_EXPRESSION
9619
9620          when Pragma_Import_Object => Import_Object : declare
9621             Args  : Args_List (1 .. 3);
9622             Names : constant Name_List (1 .. 3) := (
9623                       Name_Internal,
9624                       Name_External,
9625                       Name_Size);
9626
9627             Internal : Node_Id renames Args (1);
9628             External : Node_Id renames Args (2);
9629             Size     : Node_Id renames Args (3);
9630
9631          begin
9632             GNAT_Pragma;
9633             Gather_Associations (Names, Args);
9634             Process_Extended_Import_Export_Object_Pragma (
9635               Arg_Internal => Internal,
9636               Arg_External => External,
9637               Arg_Size     => Size);
9638          end Import_Object;
9639
9640          ----------------------
9641          -- Import_Procedure --
9642          ----------------------
9643
9644          --  pragma Import_Procedure (
9645          --        [Internal                 =>] LOCAL_NAME
9646          --     [, [External                 =>] EXTERNAL_SYMBOL]
9647          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9648          --     [, [Mechanism                =>] MECHANISM]
9649          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9650
9651          --  EXTERNAL_SYMBOL ::=
9652          --    IDENTIFIER
9653          --  | static_string_EXPRESSION
9654
9655          --  PARAMETER_TYPES ::=
9656          --    null
9657          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9658
9659          --  TYPE_DESIGNATOR ::=
9660          --    subtype_NAME
9661          --  | subtype_Name ' Access
9662
9663          --  MECHANISM ::=
9664          --    MECHANISM_NAME
9665          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9666
9667          --  MECHANISM_ASSOCIATION ::=
9668          --    [formal_parameter_NAME =>] MECHANISM_NAME
9669
9670          --  MECHANISM_NAME ::=
9671          --    Value
9672          --  | Reference
9673          --  | Descriptor [([Class =>] CLASS_NAME)]
9674
9675          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9676
9677          when Pragma_Import_Procedure => Import_Procedure : declare
9678             Args  : Args_List (1 .. 5);
9679             Names : constant Name_List (1 .. 5) := (
9680                       Name_Internal,
9681                       Name_External,
9682                       Name_Parameter_Types,
9683                       Name_Mechanism,
9684                       Name_First_Optional_Parameter);
9685
9686             Internal                 : Node_Id renames Args (1);
9687             External                 : Node_Id renames Args (2);
9688             Parameter_Types          : Node_Id renames Args (3);
9689             Mechanism                : Node_Id renames Args (4);
9690             First_Optional_Parameter : Node_Id renames Args (5);
9691
9692          begin
9693             GNAT_Pragma;
9694             Gather_Associations (Names, Args);
9695             Process_Extended_Import_Export_Subprogram_Pragma (
9696               Arg_Internal                 => Internal,
9697               Arg_External                 => External,
9698               Arg_Parameter_Types          => Parameter_Types,
9699               Arg_Mechanism                => Mechanism,
9700               Arg_First_Optional_Parameter => First_Optional_Parameter);
9701          end Import_Procedure;
9702
9703          -----------------------------
9704          -- Import_Valued_Procedure --
9705          -----------------------------
9706
9707          --  pragma Import_Valued_Procedure (
9708          --        [Internal                 =>] LOCAL_NAME
9709          --     [, [External                 =>] EXTERNAL_SYMBOL]
9710          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9711          --     [, [Mechanism                =>] MECHANISM]
9712          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9713
9714          --  EXTERNAL_SYMBOL ::=
9715          --    IDENTIFIER
9716          --  | static_string_EXPRESSION
9717
9718          --  PARAMETER_TYPES ::=
9719          --    null
9720          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9721
9722          --  TYPE_DESIGNATOR ::=
9723          --    subtype_NAME
9724          --  | subtype_Name ' Access
9725
9726          --  MECHANISM ::=
9727          --    MECHANISM_NAME
9728          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9729
9730          --  MECHANISM_ASSOCIATION ::=
9731          --    [formal_parameter_NAME =>] MECHANISM_NAME
9732
9733          --  MECHANISM_NAME ::=
9734          --    Value
9735          --  | Reference
9736          --  | Descriptor [([Class =>] CLASS_NAME)]
9737
9738          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9739
9740          when Pragma_Import_Valued_Procedure =>
9741          Import_Valued_Procedure : declare
9742             Args  : Args_List (1 .. 5);
9743             Names : constant Name_List (1 .. 5) := (
9744                       Name_Internal,
9745                       Name_External,
9746                       Name_Parameter_Types,
9747                       Name_Mechanism,
9748                       Name_First_Optional_Parameter);
9749
9750             Internal                 : Node_Id renames Args (1);
9751             External                 : Node_Id renames Args (2);
9752             Parameter_Types          : Node_Id renames Args (3);
9753             Mechanism                : Node_Id renames Args (4);
9754             First_Optional_Parameter : Node_Id renames Args (5);
9755
9756          begin
9757             GNAT_Pragma;
9758             Gather_Associations (Names, Args);
9759             Process_Extended_Import_Export_Subprogram_Pragma (
9760               Arg_Internal                 => Internal,
9761               Arg_External                 => External,
9762               Arg_Parameter_Types          => Parameter_Types,
9763               Arg_Mechanism                => Mechanism,
9764               Arg_First_Optional_Parameter => First_Optional_Parameter);
9765          end Import_Valued_Procedure;
9766
9767          -----------------
9768          -- Independent --
9769          -----------------
9770
9771          --  pragma Independent (LOCAL_NAME);
9772
9773          when Pragma_Independent => Independent : declare
9774             E_Id : Node_Id;
9775             E    : Entity_Id;
9776             D    : Node_Id;
9777             K    : Node_Kind;
9778
9779          begin
9780             Check_Ada_83_Warning;
9781             Ada_2012_Pragma;
9782             Check_No_Identifiers;
9783             Check_Arg_Count (1);
9784             Check_Arg_Is_Local_Name (Arg1);
9785             E_Id := Get_Pragma_Arg (Arg1);
9786
9787             if Etype (E_Id) = Any_Type then
9788                return;
9789             end if;
9790
9791             E := Entity (E_Id);
9792             D := Declaration_Node (E);
9793             K := Nkind (D);
9794
9795             --  Check duplicate before we chain ourselves!
9796
9797             Check_Duplicate_Pragma (E);
9798
9799             --  Check appropriate entity
9800
9801             if Is_Type (E) then
9802                if Rep_Item_Too_Early (E, N)
9803                     or else
9804                   Rep_Item_Too_Late (E, N)
9805                then
9806                   return;
9807                else
9808                   Check_First_Subtype (Arg1);
9809                end if;
9810
9811             elsif K = N_Object_Declaration
9812               or else (K = N_Component_Declaration
9813                        and then Original_Record_Component (E) = E)
9814             then
9815                if Rep_Item_Too_Late (E, N) then
9816                   return;
9817                end if;
9818
9819             else
9820                Error_Pragma_Arg
9821                  ("inappropriate entity for pragma%", Arg1);
9822             end if;
9823
9824             Independence_Checks.Append ((N, E));
9825          end Independent;
9826
9827          ----------------------------
9828          -- Independent_Components --
9829          ----------------------------
9830
9831          --  pragma Atomic_Components (array_LOCAL_NAME);
9832
9833          --  This processing is shared by Volatile_Components
9834
9835          when Pragma_Independent_Components => Independent_Components : declare
9836             E_Id : Node_Id;
9837             E    : Entity_Id;
9838             D    : Node_Id;
9839             K    : Node_Kind;
9840
9841          begin
9842             Check_Ada_83_Warning;
9843             Ada_2012_Pragma;
9844             Check_No_Identifiers;
9845             Check_Arg_Count (1);
9846             Check_Arg_Is_Local_Name (Arg1);
9847             E_Id := Get_Pragma_Arg (Arg1);
9848
9849             if Etype (E_Id) = Any_Type then
9850                return;
9851             end if;
9852
9853             E := Entity (E_Id);
9854
9855             --  Check duplicate before we chain ourselves!
9856
9857             Check_Duplicate_Pragma (E);
9858
9859             --  Check appropriate entity
9860
9861             if Rep_Item_Too_Early (E, N)
9862                  or else
9863                Rep_Item_Too_Late (E, N)
9864             then
9865                return;
9866             end if;
9867
9868             D := Declaration_Node (E);
9869             K := Nkind (D);
9870
9871             if (K = N_Full_Type_Declaration
9872                  and then (Is_Array_Type (E) or else Is_Record_Type (E)))
9873               or else
9874                 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
9875                    and then Nkind (D) = N_Object_Declaration
9876                    and then Nkind (Object_Definition (D)) =
9877                                        N_Constrained_Array_Definition)
9878             then
9879                Independence_Checks.Append ((N, E));
9880
9881             else
9882                Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
9883             end if;
9884          end Independent_Components;
9885
9886          ------------------------
9887          -- Initialize_Scalars --
9888          ------------------------
9889
9890          --  pragma Initialize_Scalars;
9891
9892          when Pragma_Initialize_Scalars =>
9893             GNAT_Pragma;
9894             Check_Arg_Count (0);
9895             Check_Valid_Configuration_Pragma;
9896             Check_Restriction (No_Initialize_Scalars, N);
9897
9898             --  Initialize_Scalars creates false positives in CodePeer, and
9899             --  incorrect negative results in Alfa mode, so ignore this pragma
9900             --  in these modes.
9901
9902             if not Restriction_Active (No_Initialize_Scalars)
9903               and then not (CodePeer_Mode or Alfa_Mode)
9904             then
9905                Init_Or_Norm_Scalars := True;
9906                Initialize_Scalars := True;
9907             end if;
9908
9909          ------------
9910          -- Inline --
9911          ------------
9912
9913          --  pragma Inline ( NAME {, NAME} );
9914
9915          when Pragma_Inline =>
9916
9917             --  Pragma is active if inlining option is active
9918
9919             Process_Inline (Inline_Active);
9920
9921          -------------------
9922          -- Inline_Always --
9923          -------------------
9924
9925          --  pragma Inline_Always ( NAME {, NAME} );
9926
9927          when Pragma_Inline_Always =>
9928             GNAT_Pragma;
9929
9930             --  Pragma always active unless in CodePeer or Alfa mode, since
9931             --  this causes walk order issues.
9932
9933             if not (CodePeer_Mode or Alfa_Mode) then
9934                Process_Inline (True);
9935             end if;
9936
9937          --------------------
9938          -- Inline_Generic --
9939          --------------------
9940
9941          --  pragma Inline_Generic (NAME {, NAME});
9942
9943          when Pragma_Inline_Generic =>
9944             GNAT_Pragma;
9945             Process_Generic_List;
9946
9947          ----------------------
9948          -- Inspection_Point --
9949          ----------------------
9950
9951          --  pragma Inspection_Point [(object_NAME {, object_NAME})];
9952
9953          when Pragma_Inspection_Point => Inspection_Point : declare
9954             Arg : Node_Id;
9955             Exp : Node_Id;
9956
9957          begin
9958             if Arg_Count > 0 then
9959                Arg := Arg1;
9960                loop
9961                   Exp := Get_Pragma_Arg (Arg);
9962                   Analyze (Exp);
9963
9964                   if not Is_Entity_Name (Exp)
9965                     or else not Is_Object (Entity (Exp))
9966                   then
9967                      Error_Pragma_Arg ("object name required", Arg);
9968                   end if;
9969
9970                   Next (Arg);
9971                   exit when No (Arg);
9972                end loop;
9973             end if;
9974          end Inspection_Point;
9975
9976          ---------------
9977          -- Interface --
9978          ---------------
9979
9980          --  pragma Interface (
9981          --    [   Convention    =>] convention_IDENTIFIER,
9982          --    [   Entity        =>] local_NAME
9983          --    [, [External_Name =>] static_string_EXPRESSION ]
9984          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
9985
9986          when Pragma_Interface =>
9987             GNAT_Pragma;
9988             Check_Arg_Order
9989               ((Name_Convention,
9990                 Name_Entity,
9991                 Name_External_Name,
9992                 Name_Link_Name));
9993             Check_At_Least_N_Arguments (2);
9994             Check_At_Most_N_Arguments  (4);
9995             Process_Import_Or_Interface;
9996
9997             --  In Ada 2005, the permission to use Interface (a reserved word)
9998             --  as a pragma name is considered an obsolescent feature.
9999
10000             if Ada_Version >= Ada_2005 then
10001                Check_Restriction
10002                  (No_Obsolescent_Features, Pragma_Identifier (N));
10003             end if;
10004
10005          --------------------
10006          -- Interface_Name --
10007          --------------------
10008
10009          --  pragma Interface_Name (
10010          --    [  Entity        =>] local_NAME
10011          --    [,[External_Name =>] static_string_EXPRESSION ]
10012          --    [,[Link_Name     =>] static_string_EXPRESSION ]);
10013
10014          when Pragma_Interface_Name => Interface_Name : declare
10015             Id     : Node_Id;
10016             Def_Id : Entity_Id;
10017             Hom_Id : Entity_Id;
10018             Found  : Boolean;
10019
10020          begin
10021             GNAT_Pragma;
10022             Check_Arg_Order
10023               ((Name_Entity, Name_External_Name, Name_Link_Name));
10024             Check_At_Least_N_Arguments (2);
10025             Check_At_Most_N_Arguments  (3);
10026             Id := Get_Pragma_Arg (Arg1);
10027             Analyze (Id);
10028
10029             if not Is_Entity_Name (Id) then
10030                Error_Pragma_Arg
10031                  ("first argument for pragma% must be entity name", Arg1);
10032             elsif Etype (Id) = Any_Type then
10033                return;
10034             else
10035                Def_Id := Entity (Id);
10036             end if;
10037
10038             --  Special DEC-compatible processing for the object case, forces
10039             --  object to be imported.
10040
10041             if Ekind (Def_Id) = E_Variable then
10042                Kill_Size_Check_Code (Def_Id);
10043                Note_Possible_Modification (Id, Sure => False);
10044
10045                --  Initialization is not allowed for imported variable
10046
10047                if Present (Expression (Parent (Def_Id)))
10048                  and then Comes_From_Source (Expression (Parent (Def_Id)))
10049                then
10050                   Error_Msg_Sloc := Sloc (Def_Id);
10051                   Error_Pragma_Arg
10052                     ("no initialization allowed for declaration of& #",
10053                      Arg2);
10054
10055                else
10056                   --  For compatibility, support VADS usage of providing both
10057                   --  pragmas Interface and Interface_Name to obtain the effect
10058                   --  of a single Import pragma.
10059
10060                   if Is_Imported (Def_Id)
10061                     and then Present (First_Rep_Item (Def_Id))
10062                     and then Nkind (First_Rep_Item (Def_Id)) = N_Pragma
10063                     and then
10064                       Pragma_Name (First_Rep_Item (Def_Id)) = Name_Interface
10065                   then
10066                      null;
10067                   else
10068                      Set_Imported (Def_Id);
10069                   end if;
10070
10071                   Set_Is_Public (Def_Id);
10072                   Process_Interface_Name (Def_Id, Arg2, Arg3);
10073                end if;
10074
10075             --  Otherwise must be subprogram
10076
10077             elsif not Is_Subprogram (Def_Id) then
10078                Error_Pragma_Arg
10079                  ("argument of pragma% is not subprogram", Arg1);
10080
10081             else
10082                Check_At_Most_N_Arguments (3);
10083                Hom_Id := Def_Id;
10084                Found := False;
10085
10086                --  Loop through homonyms
10087
10088                loop
10089                   Def_Id := Get_Base_Subprogram (Hom_Id);
10090
10091                   if Is_Imported (Def_Id) then
10092                      Process_Interface_Name (Def_Id, Arg2, Arg3);
10093                      Found := True;
10094                   end if;
10095
10096                   exit when From_Aspect_Specification (N);
10097                   Hom_Id := Homonym (Hom_Id);
10098
10099                   exit when No (Hom_Id)
10100                     or else Scope (Hom_Id) /= Current_Scope;
10101                end loop;
10102
10103                if not Found then
10104                   Error_Pragma_Arg
10105                     ("argument of pragma% is not imported subprogram",
10106                      Arg1);
10107                end if;
10108             end if;
10109          end Interface_Name;
10110
10111          -----------------------
10112          -- Interrupt_Handler --
10113          -----------------------
10114
10115          --  pragma Interrupt_Handler (handler_NAME);
10116
10117          when Pragma_Interrupt_Handler =>
10118             Check_Ada_83_Warning;
10119             Check_Arg_Count (1);
10120             Check_No_Identifiers;
10121
10122             if No_Run_Time_Mode then
10123                Error_Msg_CRT ("Interrupt_Handler pragma", N);
10124             else
10125                Check_Interrupt_Or_Attach_Handler;
10126                Process_Interrupt_Or_Attach_Handler;
10127             end if;
10128
10129          ------------------------
10130          -- Interrupt_Priority --
10131          ------------------------
10132
10133          --  pragma Interrupt_Priority [(EXPRESSION)];
10134
10135          when Pragma_Interrupt_Priority => Interrupt_Priority : declare
10136             P   : constant Node_Id := Parent (N);
10137             Arg : Node_Id;
10138
10139          begin
10140             Check_Ada_83_Warning;
10141
10142             if Arg_Count /= 0 then
10143                Arg := Get_Pragma_Arg (Arg1);
10144                Check_Arg_Count (1);
10145                Check_No_Identifiers;
10146
10147                --  The expression must be analyzed in the special manner
10148                --  described in "Handling of Default and Per-Object
10149                --  Expressions" in sem.ads.
10150
10151                Preanalyze_Spec_Expression (Arg, RTE (RE_Interrupt_Priority));
10152             end if;
10153
10154             if not Nkind_In (P, N_Task_Definition, N_Protected_Definition) then
10155                Pragma_Misplaced;
10156                return;
10157
10158             elsif Has_Pragma_Priority (P) then
10159                Error_Pragma ("duplicate pragma% not allowed");
10160
10161             else
10162                Set_Has_Pragma_Priority (P, True);
10163                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
10164             end if;
10165          end Interrupt_Priority;
10166
10167          ---------------------
10168          -- Interrupt_State --
10169          ---------------------
10170
10171          --  pragma Interrupt_State (
10172          --    [Name  =>] INTERRUPT_ID,
10173          --    [State =>] INTERRUPT_STATE);
10174
10175          --  INTERRUPT_ID => IDENTIFIER | static_integer_EXPRESSION
10176          --  INTERRUPT_STATE => System | Runtime | User
10177
10178          --  Note: if the interrupt id is given as an identifier, then it must
10179          --  be one of the identifiers in Ada.Interrupts.Names. Otherwise it is
10180          --  given as a static integer expression which must be in the range of
10181          --  Ada.Interrupts.Interrupt_ID.
10182
10183          when Pragma_Interrupt_State => Interrupt_State : declare
10184
10185             Int_Id : constant Entity_Id := RTE (RE_Interrupt_ID);
10186             --  This is the entity Ada.Interrupts.Interrupt_ID;
10187
10188             State_Type : Character;
10189             --  Set to 's'/'r'/'u' for System/Runtime/User
10190
10191             IST_Num : Pos;
10192             --  Index to entry in Interrupt_States table
10193
10194             Int_Val : Uint;
10195             --  Value of interrupt
10196
10197             Arg1X : constant Node_Id := Get_Pragma_Arg (Arg1);
10198             --  The first argument to the pragma
10199
10200             Int_Ent : Entity_Id;
10201             --  Interrupt entity in Ada.Interrupts.Names
10202
10203          begin
10204             GNAT_Pragma;
10205             Check_Arg_Order ((Name_Name, Name_State));
10206             Check_Arg_Count (2);
10207
10208             Check_Optional_Identifier (Arg1, Name_Name);
10209             Check_Optional_Identifier (Arg2, Name_State);
10210             Check_Arg_Is_Identifier (Arg2);
10211
10212             --  First argument is identifier
10213
10214             if Nkind (Arg1X) = N_Identifier then
10215
10216                --  Search list of names in Ada.Interrupts.Names
10217
10218                Int_Ent := First_Entity (RTE (RE_Names));
10219                loop
10220                   if No (Int_Ent) then
10221                      Error_Pragma_Arg ("invalid interrupt name", Arg1);
10222
10223                   elsif Chars (Int_Ent) = Chars (Arg1X) then
10224                      Int_Val := Expr_Value (Constant_Value (Int_Ent));
10225                      exit;
10226                   end if;
10227
10228                   Next_Entity (Int_Ent);
10229                end loop;
10230
10231             --  First argument is not an identifier, so it must be a static
10232             --  expression of type Ada.Interrupts.Interrupt_ID.
10233
10234             else
10235                Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
10236                Int_Val := Expr_Value (Arg1X);
10237
10238                if Int_Val < Expr_Value (Type_Low_Bound (Int_Id))
10239                     or else
10240                   Int_Val > Expr_Value (Type_High_Bound (Int_Id))
10241                then
10242                   Error_Pragma_Arg
10243                     ("value not in range of type " &
10244                      """Ada.Interrupts.Interrupt_'I'D""", Arg1);
10245                end if;
10246             end if;
10247
10248             --  Check OK state
10249
10250             case Chars (Get_Pragma_Arg (Arg2)) is
10251                when Name_Runtime => State_Type := 'r';
10252                when Name_System  => State_Type := 's';
10253                when Name_User    => State_Type := 'u';
10254
10255                when others =>
10256                   Error_Pragma_Arg ("invalid interrupt state", Arg2);
10257             end case;
10258
10259             --  Check if entry is already stored
10260
10261             IST_Num := Interrupt_States.First;
10262             loop
10263                --  If entry not found, add it
10264
10265                if IST_Num > Interrupt_States.Last then
10266                   Interrupt_States.Append
10267                     ((Interrupt_Number => UI_To_Int (Int_Val),
10268                       Interrupt_State  => State_Type,
10269                       Pragma_Loc       => Loc));
10270                   exit;
10271
10272                --  Case of entry for the same entry
10273
10274                elsif Int_Val = Interrupt_States.Table (IST_Num).
10275                                                            Interrupt_Number
10276                then
10277                   --  If state matches, done, no need to make redundant entry
10278
10279                   exit when
10280                     State_Type = Interrupt_States.Table (IST_Num).
10281                                                            Interrupt_State;
10282
10283                   --  Otherwise if state does not match, error
10284
10285                   Error_Msg_Sloc :=
10286                     Interrupt_States.Table (IST_Num).Pragma_Loc;
10287                   Error_Pragma_Arg
10288                     ("state conflicts with that given #", Arg2);
10289                   exit;
10290                end if;
10291
10292                IST_Num := IST_Num + 1;
10293             end loop;
10294          end Interrupt_State;
10295
10296          ---------------
10297          -- Invariant --
10298          ---------------
10299
10300          --  pragma Invariant
10301          --    ([Entity =>]    type_LOCAL_NAME,
10302          --     [Check  =>]    EXPRESSION
10303          --     [,[Message =>] String_Expression]);
10304
10305          when Pragma_Invariant => Invariant : declare
10306             Type_Id : Node_Id;
10307             Typ     : Entity_Id;
10308
10309             Discard : Boolean;
10310             pragma Unreferenced (Discard);
10311
10312          begin
10313             GNAT_Pragma;
10314             Check_At_Least_N_Arguments (2);
10315             Check_At_Most_N_Arguments (3);
10316             Check_Optional_Identifier (Arg1, Name_Entity);
10317             Check_Optional_Identifier (Arg2, Name_Check);
10318
10319             if Arg_Count = 3 then
10320                Check_Optional_Identifier (Arg3, Name_Message);
10321                Check_Arg_Is_Static_Expression (Arg3, Standard_String);
10322             end if;
10323
10324             Check_Arg_Is_Local_Name (Arg1);
10325
10326             Type_Id := Get_Pragma_Arg (Arg1);
10327             Find_Type (Type_Id);
10328             Typ := Entity (Type_Id);
10329
10330             if Typ = Any_Type then
10331                return;
10332
10333             --  An invariant must apply to a private type, or appear in the
10334             --  private part of a package spec and apply to a completion.
10335
10336             elsif Ekind_In (Typ, E_Private_Type,
10337                                  E_Record_Type_With_Private,
10338                                  E_Limited_Private_Type)
10339             then
10340                null;
10341
10342             elsif In_Private_Part (Current_Scope)
10343               and then Has_Private_Declaration (Typ)
10344             then
10345                null;
10346
10347             elsif In_Private_Part (Current_Scope) then
10348                Error_Pragma_Arg
10349                  ("pragma% only allowed for private type " &
10350                   "declared in visible part", Arg1);
10351
10352             else
10353                Error_Pragma_Arg
10354                  ("pragma% only allowed for private type", Arg1);
10355             end if;
10356
10357             --  Note that the type has at least one invariant, and also that
10358             --  it has inheritable invariants if we have Invariant'Class.
10359
10360             Set_Has_Invariants (Typ);
10361
10362             if Class_Present (N) then
10363                Set_Has_Inheritable_Invariants (Typ);
10364             end if;
10365
10366             --  The remaining processing is simply to link the pragma on to
10367             --  the rep item chain, for processing when the type is frozen.
10368             --  This is accomplished by a call to Rep_Item_Too_Late.
10369
10370             Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
10371          end Invariant;
10372
10373          ----------------------
10374          -- Java_Constructor --
10375          ----------------------
10376
10377          --  pragma Java_Constructor ([Entity =>] LOCAL_NAME);
10378
10379          --  Also handles pragma CIL_Constructor
10380
10381          when Pragma_CIL_Constructor | Pragma_Java_Constructor =>
10382          Java_Constructor : declare
10383             Convention  : Convention_Id;
10384             Def_Id      : Entity_Id;
10385             Hom_Id      : Entity_Id;
10386             Id          : Entity_Id;
10387             This_Formal : Entity_Id;
10388
10389          begin
10390             GNAT_Pragma;
10391             Check_Arg_Count (1);
10392             Check_Optional_Identifier (Arg1, Name_Entity);
10393             Check_Arg_Is_Local_Name (Arg1);
10394
10395             Id := Get_Pragma_Arg (Arg1);
10396             Find_Program_Unit_Name (Id);
10397
10398             --  If we did not find the name, we are done
10399
10400             if Etype (Id) = Any_Type then
10401                return;
10402             end if;
10403
10404             --  Check wrong use of pragma in wrong VM target
10405
10406             if VM_Target = No_VM then
10407                return;
10408
10409             elsif VM_Target = CLI_Target
10410               and then Prag_Id = Pragma_Java_Constructor
10411             then
10412                Error_Pragma ("must use pragma 'C'I'L_'Constructor");
10413
10414             elsif VM_Target = JVM_Target
10415               and then Prag_Id = Pragma_CIL_Constructor
10416             then
10417                Error_Pragma ("must use pragma 'Java_'Constructor");
10418             end if;
10419
10420             case Prag_Id is
10421                when Pragma_CIL_Constructor  => Convention := Convention_CIL;
10422                when Pragma_Java_Constructor => Convention := Convention_Java;
10423                when others                  => null;
10424             end case;
10425
10426             Hom_Id := Entity (Id);
10427
10428             --  Loop through homonyms
10429
10430             loop
10431                Def_Id := Get_Base_Subprogram (Hom_Id);
10432
10433                --  The constructor is required to be a function
10434
10435                if Ekind (Def_Id) /= E_Function then
10436                   if VM_Target = JVM_Target then
10437                      Error_Pragma_Arg
10438                        ("pragma% requires function returning a " &
10439                         "'Java access type", Def_Id);
10440                   else
10441                      Error_Pragma_Arg
10442                        ("pragma% requires function returning a " &
10443                         "'C'I'L access type", Def_Id);
10444                   end if;
10445                end if;
10446
10447                --  Check arguments: For tagged type the first formal must be
10448                --  named "this" and its type must be a named access type
10449                --  designating a class-wide tagged type that has convention
10450                --  CIL/Java. The first formal must also have a null default
10451                --  value. For example:
10452
10453                --      type Typ is tagged ...
10454                --      type Ref is access all Typ;
10455                --      pragma Convention (CIL, Typ);
10456
10457                --      function New_Typ (This : Ref) return Ref;
10458                --      function New_Typ (This : Ref; I : Integer) return Ref;
10459                --      pragma Cil_Constructor (New_Typ);
10460
10461                --  Reason: The first formal must NOT be a primitive of the
10462                --  tagged type.
10463
10464                --  This rule also applies to constructors of delegates used
10465                --  to interface with standard target libraries. For example:
10466
10467                --      type Delegate is access procedure ...
10468                --      pragma Import (CIL, Delegate, ...);
10469
10470                --      function new_Delegate
10471                --        (This : Delegate := null; ... ) return Delegate;
10472
10473                --  For value-types this rule does not apply.
10474
10475                if not Is_Value_Type (Etype (Def_Id)) then
10476                   if No (First_Formal (Def_Id)) then
10477                      Error_Msg_Name_1 := Pname;
10478                      Error_Msg_N ("% function must have parameters", Def_Id);
10479                      return;
10480                   end if;
10481
10482                   --  In the JRE library we have several occurrences in which
10483                   --  the "this" parameter is not the first formal.
10484
10485                   This_Formal := First_Formal (Def_Id);
10486
10487                   --  In the JRE library we have several occurrences in which
10488                   --  the "this" parameter is not the first formal. Search for
10489                   --  it.
10490
10491                   if VM_Target = JVM_Target then
10492                      while Present (This_Formal)
10493                        and then Get_Name_String (Chars (This_Formal)) /= "this"
10494                      loop
10495                         Next_Formal (This_Formal);
10496                      end loop;
10497
10498                      if No (This_Formal) then
10499                         This_Formal := First_Formal (Def_Id);
10500                      end if;
10501                   end if;
10502
10503                   --  Warning: The first parameter should be named "this".
10504                   --  We temporarily allow it because we have the following
10505                   --  case in the Java runtime (file s-osinte.ads) ???
10506
10507                   --    function new_Thread
10508                   --      (Self_Id : System.Address) return Thread_Id;
10509                   --    pragma Java_Constructor (new_Thread);
10510
10511                   if VM_Target = JVM_Target
10512                     and then Get_Name_String (Chars (First_Formal (Def_Id)))
10513                                = "self_id"
10514                     and then Etype (First_Formal (Def_Id)) = RTE (RE_Address)
10515                   then
10516                      null;
10517
10518                   elsif Get_Name_String (Chars (This_Formal)) /= "this" then
10519                      Error_Msg_Name_1 := Pname;
10520                      Error_Msg_N
10521                        ("first formal of % function must be named `this`",
10522                         Parent (This_Formal));
10523
10524                   elsif not Is_Access_Type (Etype (This_Formal)) then
10525                      Error_Msg_Name_1 := Pname;
10526                      Error_Msg_N
10527                        ("first formal of % function must be an access type",
10528                         Parameter_Type (Parent (This_Formal)));
10529
10530                   --  For delegates the type of the first formal must be a
10531                   --  named access-to-subprogram type (see previous example)
10532
10533                   elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type
10534                     and then Ekind (Etype (This_Formal))
10535                                /= E_Access_Subprogram_Type
10536                   then
10537                      Error_Msg_Name_1 := Pname;
10538                      Error_Msg_N
10539                        ("first formal of % function must be a named access" &
10540                         " to subprogram type",
10541                         Parameter_Type (Parent (This_Formal)));
10542
10543                   --  Warning: We should reject anonymous access types because
10544                   --  the constructor must not be handled as a primitive of the
10545                   --  tagged type. We temporarily allow it because this profile
10546                   --  is currently generated by cil2ada???
10547
10548                   elsif Ekind (Etype (Def_Id)) /= E_Access_Subprogram_Type
10549                     and then not Ekind_In (Etype (This_Formal),
10550                                              E_Access_Type,
10551                                              E_General_Access_Type,
10552                                              E_Anonymous_Access_Type)
10553                   then
10554                      Error_Msg_Name_1 := Pname;
10555                      Error_Msg_N
10556                        ("first formal of % function must be a named access" &
10557                         " type",
10558                         Parameter_Type (Parent (This_Formal)));
10559
10560                   elsif Atree.Convention
10561                          (Designated_Type (Etype (This_Formal))) /= Convention
10562                   then
10563                      Error_Msg_Name_1 := Pname;
10564
10565                      if Convention = Convention_Java then
10566                         Error_Msg_N
10567                           ("pragma% requires convention 'Cil in designated" &
10568                            " type",
10569                            Parameter_Type (Parent (This_Formal)));
10570                      else
10571                         Error_Msg_N
10572                           ("pragma% requires convention 'Java in designated" &
10573                            " type",
10574                            Parameter_Type (Parent (This_Formal)));
10575                      end if;
10576
10577                   elsif No (Expression (Parent (This_Formal)))
10578                     or else Nkind (Expression (Parent (This_Formal))) /= N_Null
10579                   then
10580                      Error_Msg_Name_1 := Pname;
10581                      Error_Msg_N
10582                        ("pragma% requires first formal with default `null`",
10583                         Parameter_Type (Parent (This_Formal)));
10584                   end if;
10585                end if;
10586
10587                --  Check result type: the constructor must be a function
10588                --  returning:
10589                --   * a value type (only allowed in the CIL compiler)
10590                --   * an access-to-subprogram type with convention Java/CIL
10591                --   * an access-type designating a type that has convention
10592                --     Java/CIL.
10593
10594                if Is_Value_Type (Etype (Def_Id)) then
10595                   null;
10596
10597                --  Access-to-subprogram type with convention Java/CIL
10598
10599                elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type then
10600                   if Atree.Convention (Etype (Def_Id)) /= Convention then
10601                      if Convention = Convention_Java then
10602                         Error_Pragma_Arg
10603                           ("pragma% requires function returning a " &
10604                            "'Java access type", Arg1);
10605                      else
10606                         pragma Assert (Convention = Convention_CIL);
10607                         Error_Pragma_Arg
10608                           ("pragma% requires function returning a " &
10609                            "'C'I'L access type", Arg1);
10610                      end if;
10611                   end if;
10612
10613                elsif Ekind (Etype (Def_Id)) in Access_Kind then
10614                   if not Ekind_In (Etype (Def_Id), E_Access_Type,
10615                                                    E_General_Access_Type)
10616                     or else
10617                       Atree.Convention
10618                         (Designated_Type (Etype (Def_Id))) /= Convention
10619                   then
10620                      Error_Msg_Name_1 := Pname;
10621
10622                      if Convention = Convention_Java then
10623                         Error_Pragma_Arg
10624                           ("pragma% requires function returning a named" &
10625                            "'Java access type", Arg1);
10626                      else
10627                         Error_Pragma_Arg
10628                           ("pragma% requires function returning a named" &
10629                            "'C'I'L access type", Arg1);
10630                      end if;
10631                   end if;
10632                end if;
10633
10634                Set_Is_Constructor (Def_Id);
10635                Set_Convention     (Def_Id, Convention);
10636                Set_Is_Imported    (Def_Id);
10637
10638                exit when From_Aspect_Specification (N);
10639                Hom_Id := Homonym (Hom_Id);
10640
10641                exit when No (Hom_Id) or else Scope (Hom_Id) /= Current_Scope;
10642             end loop;
10643          end Java_Constructor;
10644
10645          ----------------------
10646          -- Java_Interface --
10647          ----------------------
10648
10649          --  pragma Java_Interface ([Entity =>] LOCAL_NAME);
10650
10651          when Pragma_Java_Interface => Java_Interface : declare
10652             Arg : Node_Id;
10653             Typ : Entity_Id;
10654
10655          begin
10656             GNAT_Pragma;
10657             Check_Arg_Count (1);
10658             Check_Optional_Identifier (Arg1, Name_Entity);
10659             Check_Arg_Is_Local_Name (Arg1);
10660
10661             Arg := Get_Pragma_Arg (Arg1);
10662             Analyze (Arg);
10663
10664             if Etype (Arg) = Any_Type then
10665                return;
10666             end if;
10667
10668             if not Is_Entity_Name (Arg)
10669               or else not Is_Type (Entity (Arg))
10670             then
10671                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
10672             end if;
10673
10674             Typ := Underlying_Type (Entity (Arg));
10675
10676             --  For now simply check some of the semantic constraints on the
10677             --  type. This currently leaves out some restrictions on interface
10678             --  types, namely that the parent type must be java.lang.Object.Typ
10679             --  and that all primitives of the type should be declared
10680             --  abstract. ???
10681
10682             if not Is_Tagged_Type (Typ) or else not Is_Abstract_Type (Typ) then
10683                Error_Pragma_Arg ("pragma% requires an abstract "
10684                  & "tagged type", Arg1);
10685
10686             elsif not Has_Discriminants (Typ)
10687               or else Ekind (Etype (First_Discriminant (Typ)))
10688                         /= E_Anonymous_Access_Type
10689               or else
10690                 not Is_Class_Wide_Type
10691                       (Designated_Type (Etype (First_Discriminant (Typ))))
10692             then
10693                Error_Pragma_Arg
10694                  ("type must have a class-wide access discriminant", Arg1);
10695             end if;
10696          end Java_Interface;
10697
10698          ----------------
10699          -- Keep_Names --
10700          ----------------
10701
10702          --  pragma Keep_Names ([On => ] local_NAME);
10703
10704          when Pragma_Keep_Names => Keep_Names : declare
10705             Arg : Node_Id;
10706
10707          begin
10708             GNAT_Pragma;
10709             Check_Arg_Count (1);
10710             Check_Optional_Identifier (Arg1, Name_On);
10711             Check_Arg_Is_Local_Name (Arg1);
10712
10713             Arg := Get_Pragma_Arg (Arg1);
10714             Analyze (Arg);
10715
10716             if Etype (Arg) = Any_Type then
10717                return;
10718             end if;
10719
10720             if not Is_Entity_Name (Arg)
10721               or else Ekind (Entity (Arg)) /= E_Enumeration_Type
10722             then
10723                Error_Pragma_Arg
10724                  ("pragma% requires a local enumeration type", Arg1);
10725             end if;
10726
10727             Set_Discard_Names (Entity (Arg), False);
10728          end Keep_Names;
10729
10730          -------------
10731          -- License --
10732          -------------
10733
10734          --  pragma License (RESTRICTED | UNRESTRICTED | GPL | MODIFIED_GPL);
10735
10736          when Pragma_License =>
10737             GNAT_Pragma;
10738             Check_Arg_Count (1);
10739             Check_No_Identifiers;
10740             Check_Valid_Configuration_Pragma;
10741             Check_Arg_Is_Identifier (Arg1);
10742
10743             declare
10744                Sind : constant Source_File_Index :=
10745                         Source_Index (Current_Sem_Unit);
10746
10747             begin
10748                case Chars (Get_Pragma_Arg (Arg1)) is
10749                   when Name_GPL =>
10750                      Set_License (Sind, GPL);
10751
10752                   when Name_Modified_GPL =>
10753                      Set_License (Sind, Modified_GPL);
10754
10755                   when Name_Restricted =>
10756                      Set_License (Sind, Restricted);
10757
10758                   when Name_Unrestricted =>
10759                      Set_License (Sind, Unrestricted);
10760
10761                   when others =>
10762                      Error_Pragma_Arg ("invalid license name", Arg1);
10763                end case;
10764             end;
10765
10766          ---------------
10767          -- Link_With --
10768          ---------------
10769
10770          --  pragma Link_With (string_EXPRESSION {, string_EXPRESSION});
10771
10772          when Pragma_Link_With => Link_With : declare
10773             Arg : Node_Id;
10774
10775          begin
10776             GNAT_Pragma;
10777
10778             if Operating_Mode = Generate_Code
10779               and then In_Extended_Main_Source_Unit (N)
10780             then
10781                Check_At_Least_N_Arguments (1);
10782                Check_No_Identifiers;
10783                Check_Is_In_Decl_Part_Or_Package_Spec;
10784                Check_Arg_Is_Static_Expression (Arg1, Standard_String);
10785                Start_String;
10786
10787                Arg := Arg1;
10788                while Present (Arg) loop
10789                   Check_Arg_Is_Static_Expression (Arg, Standard_String);
10790
10791                   --  Store argument, converting sequences of spaces to a
10792                   --  single null character (this is one of the differences
10793                   --  in processing between Link_With and Linker_Options).
10794
10795                   Arg_Store : declare
10796                      C : constant Char_Code := Get_Char_Code (' ');
10797                      S : constant String_Id :=
10798                            Strval (Expr_Value_S (Get_Pragma_Arg (Arg)));
10799                      L : constant Nat := String_Length (S);
10800                      F : Nat := 1;
10801
10802                      procedure Skip_Spaces;
10803                      --  Advance F past any spaces
10804
10805                      -----------------
10806                      -- Skip_Spaces --
10807                      -----------------
10808
10809                      procedure Skip_Spaces is
10810                      begin
10811                         while F <= L and then Get_String_Char (S, F) = C loop
10812                            F := F + 1;
10813                         end loop;
10814                      end Skip_Spaces;
10815
10816                   --  Start of processing for Arg_Store
10817
10818                   begin
10819                      Skip_Spaces; -- skip leading spaces
10820
10821                      --  Loop through characters, changing any embedded
10822                      --  sequence of spaces to a single null character (this
10823                      --  is how Link_With/Linker_Options differ)
10824
10825                      while F <= L loop
10826                         if Get_String_Char (S, F) = C then
10827                            Skip_Spaces;
10828                            exit when F > L;
10829                            Store_String_Char (ASCII.NUL);
10830
10831                         else
10832                            Store_String_Char (Get_String_Char (S, F));
10833                            F := F + 1;
10834                         end if;
10835                      end loop;
10836                   end Arg_Store;
10837
10838                   Arg := Next (Arg);
10839
10840                   if Present (Arg) then
10841                      Store_String_Char (ASCII.NUL);
10842                   end if;
10843                end loop;
10844
10845                Store_Linker_Option_String (End_String);
10846             end if;
10847          end Link_With;
10848
10849          ------------------
10850          -- Linker_Alias --
10851          ------------------
10852
10853          --  pragma Linker_Alias (
10854          --      [Entity =>]  LOCAL_NAME
10855          --      [Target =>]  static_string_EXPRESSION);
10856
10857          when Pragma_Linker_Alias =>
10858             GNAT_Pragma;
10859             Check_Arg_Order ((Name_Entity, Name_Target));
10860             Check_Arg_Count (2);
10861             Check_Optional_Identifier (Arg1, Name_Entity);
10862             Check_Optional_Identifier (Arg2, Name_Target);
10863             Check_Arg_Is_Library_Level_Local_Name (Arg1);
10864             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10865
10866             --  The only processing required is to link this item on to the
10867             --  list of rep items for the given entity. This is accomplished
10868             --  by the call to Rep_Item_Too_Late (when no error is detected
10869             --  and False is returned).
10870
10871             if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
10872                return;
10873             else
10874                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10875             end if;
10876
10877          ------------------------
10878          -- Linker_Constructor --
10879          ------------------------
10880
10881          --  pragma Linker_Constructor (procedure_LOCAL_NAME);
10882
10883          --  Code is shared with Linker_Destructor
10884
10885          -----------------------
10886          -- Linker_Destructor --
10887          -----------------------
10888
10889          --  pragma Linker_Destructor (procedure_LOCAL_NAME);
10890
10891          when Pragma_Linker_Constructor |
10892               Pragma_Linker_Destructor =>
10893          Linker_Constructor : declare
10894             Arg1_X : Node_Id;
10895             Proc   : Entity_Id;
10896
10897          begin
10898             GNAT_Pragma;
10899             Check_Arg_Count (1);
10900             Check_No_Identifiers;
10901             Check_Arg_Is_Local_Name (Arg1);
10902             Arg1_X := Get_Pragma_Arg (Arg1);
10903             Analyze (Arg1_X);
10904             Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
10905
10906             if not Is_Library_Level_Entity (Proc) then
10907                Error_Pragma_Arg
10908                 ("argument for pragma% must be library level entity", Arg1);
10909             end if;
10910
10911             --  The only processing required is to link this item on to the
10912             --  list of rep items for the given entity. This is accomplished
10913             --  by the call to Rep_Item_Too_Late (when no error is detected
10914             --  and False is returned).
10915
10916             if Rep_Item_Too_Late (Proc, N) then
10917                return;
10918             else
10919                Set_Has_Gigi_Rep_Item (Proc);
10920             end if;
10921          end Linker_Constructor;
10922
10923          --------------------
10924          -- Linker_Options --
10925          --------------------
10926
10927          --  pragma Linker_Options (string_EXPRESSION {, string_EXPRESSION});
10928
10929          when Pragma_Linker_Options => Linker_Options : declare
10930             Arg : Node_Id;
10931
10932          begin
10933             Check_Ada_83_Warning;
10934             Check_No_Identifiers;
10935             Check_Arg_Count (1);
10936             Check_Is_In_Decl_Part_Or_Package_Spec;
10937             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
10938             Start_String (Strval (Expr_Value_S (Get_Pragma_Arg (Arg1))));
10939
10940             Arg := Arg2;
10941             while Present (Arg) loop
10942                Check_Arg_Is_Static_Expression (Arg, Standard_String);
10943                Store_String_Char (ASCII.NUL);
10944                Store_String_Chars
10945                  (Strval (Expr_Value_S (Get_Pragma_Arg (Arg))));
10946                Arg := Next (Arg);
10947             end loop;
10948
10949             if Operating_Mode = Generate_Code
10950               and then In_Extended_Main_Source_Unit (N)
10951             then
10952                Store_Linker_Option_String (End_String);
10953             end if;
10954          end Linker_Options;
10955
10956          --------------------
10957          -- Linker_Section --
10958          --------------------
10959
10960          --  pragma Linker_Section (
10961          --      [Entity  =>]  LOCAL_NAME
10962          --      [Section =>]  static_string_EXPRESSION);
10963
10964          when Pragma_Linker_Section =>
10965             GNAT_Pragma;
10966             Check_Arg_Order ((Name_Entity, Name_Section));
10967             Check_Arg_Count (2);
10968             Check_Optional_Identifier (Arg1, Name_Entity);
10969             Check_Optional_Identifier (Arg2, Name_Section);
10970             Check_Arg_Is_Library_Level_Local_Name (Arg1);
10971             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10972
10973             --  This pragma applies only to objects
10974
10975             if not Is_Object (Entity (Get_Pragma_Arg (Arg1))) then
10976                Error_Pragma_Arg ("pragma% applies only to objects", Arg1);
10977             end if;
10978
10979             --  The only processing required is to link this item on to the
10980             --  list of rep items for the given entity. This is accomplished
10981             --  by the call to Rep_Item_Too_Late (when no error is detected
10982             --  and False is returned).
10983
10984             if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
10985                return;
10986             else
10987                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10988             end if;
10989
10990          ----------
10991          -- List --
10992          ----------
10993
10994          --  pragma List (On | Off)
10995
10996          --  There is nothing to do here, since we did all the processing for
10997          --  this pragma in Par.Prag (so that it works properly even in syntax
10998          --  only mode).
10999
11000          when Pragma_List =>
11001             null;
11002
11003          --------------------
11004          -- Locking_Policy --
11005          --------------------
11006
11007          --  pragma Locking_Policy (policy_IDENTIFIER);
11008
11009          when Pragma_Locking_Policy => declare
11010             subtype LP_Range is Name_Id
11011               range First_Locking_Policy_Name .. Last_Locking_Policy_Name;
11012             LP_Val : LP_Range;
11013             LP     : Character;
11014          begin
11015             Check_Ada_83_Warning;
11016             Check_Arg_Count (1);
11017             Check_No_Identifiers;
11018             Check_Arg_Is_Locking_Policy (Arg1);
11019             Check_Valid_Configuration_Pragma;
11020             LP_Val := Chars (Get_Pragma_Arg (Arg1));
11021
11022             case LP_Val is
11023                when Name_Ceiling_Locking            => LP := 'C';
11024                when Name_Inheritance_Locking        => LP := 'I';
11025                when Name_Concurrent_Readers_Locking => LP := 'R';
11026             end case;
11027
11028             if Locking_Policy /= ' '
11029               and then Locking_Policy /= LP
11030             then
11031                Error_Msg_Sloc := Locking_Policy_Sloc;
11032                Error_Pragma ("locking policy incompatible with policy#");
11033
11034             --  Set new policy, but always preserve System_Location since we
11035             --  like the error message with the run time name.
11036
11037             else
11038                Locking_Policy := LP;
11039
11040                if Locking_Policy_Sloc /= System_Location then
11041                   Locking_Policy_Sloc := Loc;
11042                end if;
11043             end if;
11044          end;
11045
11046          ----------------
11047          -- Long_Float --
11048          ----------------
11049
11050          --  pragma Long_Float (D_Float | G_Float);
11051
11052          when Pragma_Long_Float => Long_Float : declare
11053          begin
11054             GNAT_Pragma;
11055             Check_Valid_Configuration_Pragma;
11056             Check_Arg_Count (1);
11057             Check_No_Identifier (Arg1);
11058             Check_Arg_Is_One_Of (Arg1, Name_D_Float, Name_G_Float);
11059
11060             if not OpenVMS_On_Target then
11061                Error_Pragma ("?pragma% ignored (applies only to Open'V'M'S)");
11062             end if;
11063
11064             --  D_Float case
11065
11066             if Chars (Get_Pragma_Arg (Arg1)) = Name_D_Float then
11067                if Opt.Float_Format_Long = 'G' then
11068                   Error_Pragma_Arg
11069                     ("G_Float previously specified", Arg1);
11070
11071                elsif Current_Sem_Unit /= Main_Unit
11072                  and then Opt.Float_Format_Long /= 'D'
11073                then
11074                   Error_Pragma_Arg
11075                     ("main unit not compiled with pragma Long_Float (D_Float)",
11076                      "\pragma% must be used consistently for whole partition",
11077                      Arg1);
11078
11079                else
11080                   Opt.Float_Format_Long := 'D';
11081                end if;
11082
11083             --  G_Float case (this is the default, does not need overriding)
11084
11085             else
11086                if Opt.Float_Format_Long = 'D' then
11087                   Error_Pragma ("D_Float previously specified");
11088
11089                elsif Current_Sem_Unit /= Main_Unit
11090                  and then Opt.Float_Format_Long /= 'G'
11091                then
11092                   Error_Pragma_Arg
11093                     ("main unit not compiled with pragma Long_Float (G_Float)",
11094                      "\pragma% must be used consistently for whole partition",
11095                      Arg1);
11096
11097                else
11098                   Opt.Float_Format_Long := 'G';
11099                end if;
11100             end if;
11101
11102             Set_Standard_Fpt_Formats;
11103          end Long_Float;
11104
11105          -----------------------
11106          -- Machine_Attribute --
11107          -----------------------
11108
11109          --  pragma Machine_Attribute (
11110          --       [Entity         =>] LOCAL_NAME,
11111          --       [Attribute_Name =>] static_string_EXPRESSION
11112          --    [, [Info           =>] static_EXPRESSION] );
11113
11114          when Pragma_Machine_Attribute => Machine_Attribute : declare
11115             Def_Id : Entity_Id;
11116
11117          begin
11118             GNAT_Pragma;
11119             Check_Arg_Order ((Name_Entity, Name_Attribute_Name, Name_Info));
11120
11121             if Arg_Count = 3 then
11122                Check_Optional_Identifier (Arg3, Name_Info);
11123                Check_Arg_Is_Static_Expression (Arg3);
11124             else
11125                Check_Arg_Count (2);
11126             end if;
11127
11128             Check_Optional_Identifier (Arg1, Name_Entity);
11129             Check_Optional_Identifier (Arg2, Name_Attribute_Name);
11130             Check_Arg_Is_Local_Name (Arg1);
11131             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
11132             Def_Id := Entity (Get_Pragma_Arg (Arg1));
11133
11134             if Is_Access_Type (Def_Id) then
11135                Def_Id := Designated_Type (Def_Id);
11136             end if;
11137
11138             if Rep_Item_Too_Early (Def_Id, N) then
11139                return;
11140             end if;
11141
11142             Def_Id := Underlying_Type (Def_Id);
11143
11144             --  The only processing required is to link this item on to the
11145             --  list of rep items for the given entity. This is accomplished
11146             --  by the call to Rep_Item_Too_Late (when no error is detected
11147             --  and False is returned).
11148
11149             if Rep_Item_Too_Late (Def_Id, N) then
11150                return;
11151             else
11152                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
11153             end if;
11154          end Machine_Attribute;
11155
11156          ----------
11157          -- Main --
11158          ----------
11159
11160          --  pragma Main
11161          --   (MAIN_OPTION [, MAIN_OPTION]);
11162
11163          --  MAIN_OPTION ::=
11164          --    [STACK_SIZE              =>] static_integer_EXPRESSION
11165          --  | [TASK_STACK_SIZE_DEFAULT =>] static_integer_EXPRESSION
11166          --  | [TIME_SLICING_ENABLED    =>] static_boolean_EXPRESSION
11167
11168          when Pragma_Main => Main : declare
11169             Args  : Args_List (1 .. 3);
11170             Names : constant Name_List (1 .. 3) := (
11171                       Name_Stack_Size,
11172                       Name_Task_Stack_Size_Default,
11173                       Name_Time_Slicing_Enabled);
11174
11175             Nod : Node_Id;
11176
11177          begin
11178             GNAT_Pragma;
11179             Gather_Associations (Names, Args);
11180
11181             for J in 1 .. 2 loop
11182                if Present (Args (J)) then
11183                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
11184                end if;
11185             end loop;
11186
11187             if Present (Args (3)) then
11188                Check_Arg_Is_Static_Expression (Args (3), Standard_Boolean);
11189             end if;
11190
11191             Nod := Next (N);
11192             while Present (Nod) loop
11193                if Nkind (Nod) = N_Pragma
11194                  and then Pragma_Name (Nod) = Name_Main
11195                then
11196                   Error_Msg_Name_1 := Pname;
11197                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
11198                end if;
11199
11200                Next (Nod);
11201             end loop;
11202          end Main;
11203
11204          ------------------
11205          -- Main_Storage --
11206          ------------------
11207
11208          --  pragma Main_Storage
11209          --   (MAIN_STORAGE_OPTION [, MAIN_STORAGE_OPTION]);
11210
11211          --  MAIN_STORAGE_OPTION ::=
11212          --    [WORKING_STORAGE =>] static_SIMPLE_EXPRESSION
11213          --  | [TOP_GUARD =>] static_SIMPLE_EXPRESSION
11214
11215          when Pragma_Main_Storage => Main_Storage : declare
11216             Args  : Args_List (1 .. 2);
11217             Names : constant Name_List (1 .. 2) := (
11218                       Name_Working_Storage,
11219                       Name_Top_Guard);
11220
11221             Nod : Node_Id;
11222
11223          begin
11224             GNAT_Pragma;
11225             Gather_Associations (Names, Args);
11226
11227             for J in 1 .. 2 loop
11228                if Present (Args (J)) then
11229                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
11230                end if;
11231             end loop;
11232
11233             Check_In_Main_Program;
11234
11235             Nod := Next (N);
11236             while Present (Nod) loop
11237                if Nkind (Nod) = N_Pragma
11238                  and then Pragma_Name (Nod) = Name_Main_Storage
11239                then
11240                   Error_Msg_Name_1 := Pname;
11241                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
11242                end if;
11243
11244                Next (Nod);
11245             end loop;
11246          end Main_Storage;
11247
11248          -----------------
11249          -- Memory_Size --
11250          -----------------
11251
11252          --  pragma Memory_Size (NUMERIC_LITERAL)
11253
11254          when Pragma_Memory_Size =>
11255             GNAT_Pragma;
11256
11257             --  Memory size is simply ignored
11258
11259             Check_No_Identifiers;
11260             Check_Arg_Count (1);
11261             Check_Arg_Is_Integer_Literal (Arg1);
11262
11263          -------------
11264          -- No_Body --
11265          -------------
11266
11267          --  pragma No_Body;
11268
11269          --  The only correct use of this pragma is on its own in a file, in
11270          --  which case it is specially processed (see Gnat1drv.Check_Bad_Body
11271          --  and Frontend, which use Sinput.L.Source_File_Is_Pragma_No_Body to
11272          --  check for a file containing nothing but a No_Body pragma). If we
11273          --  attempt to process it during normal semantics processing, it means
11274          --  it was misplaced.
11275
11276          when Pragma_No_Body =>
11277             GNAT_Pragma;
11278             Pragma_Misplaced;
11279
11280          ---------------
11281          -- No_Return --
11282          ---------------
11283
11284          --  pragma No_Return (procedure_LOCAL_NAME {, procedure_Local_Name});
11285
11286          when Pragma_No_Return => No_Return : declare
11287             Id    : Node_Id;
11288             E     : Entity_Id;
11289             Found : Boolean;
11290             Arg   : Node_Id;
11291
11292          begin
11293             Ada_2005_Pragma;
11294             Check_At_Least_N_Arguments (1);
11295
11296             --  Loop through arguments of pragma
11297
11298             Arg := Arg1;
11299             while Present (Arg) loop
11300                Check_Arg_Is_Local_Name (Arg);
11301                Id := Get_Pragma_Arg (Arg);
11302                Analyze (Id);
11303
11304                if not Is_Entity_Name (Id) then
11305                   Error_Pragma_Arg ("entity name required", Arg);
11306                end if;
11307
11308                if Etype (Id) = Any_Type then
11309                   raise Pragma_Exit;
11310                end if;
11311
11312                --  Loop to find matching procedures
11313
11314                E := Entity (Id);
11315                Found := False;
11316                while Present (E)
11317                  and then Scope (E) = Current_Scope
11318                loop
11319                   if Ekind_In (E, E_Procedure, E_Generic_Procedure) then
11320                      Set_No_Return (E);
11321
11322                      --  Set flag on any alias as well
11323
11324                      if Is_Overloadable (E) and then Present (Alias (E)) then
11325                         Set_No_Return (Alias (E));
11326                      end if;
11327
11328                      Found := True;
11329                   end if;
11330
11331                   exit when From_Aspect_Specification (N);
11332                   E := Homonym (E);
11333                end loop;
11334
11335                if not Found then
11336                   Error_Pragma_Arg ("no procedure & found for pragma%", Arg);
11337                end if;
11338
11339                Next (Arg);
11340             end loop;
11341          end No_Return;
11342
11343          -----------------
11344          -- No_Run_Time --
11345          -----------------
11346
11347          --  pragma No_Run_Time;
11348
11349          --  Note: this pragma is retained for backwards compatibility. See
11350          --  body of Rtsfind for full details on its handling.
11351
11352          when Pragma_No_Run_Time =>
11353             GNAT_Pragma;
11354             Check_Valid_Configuration_Pragma;
11355             Check_Arg_Count (0);
11356
11357             No_Run_Time_Mode           := True;
11358             Configurable_Run_Time_Mode := True;
11359
11360             --  Set Duration to 32 bits if word size is 32
11361
11362             if Ttypes.System_Word_Size = 32 then
11363                Duration_32_Bits_On_Target := True;
11364             end if;
11365
11366             --  Set appropriate restrictions
11367
11368             Set_Restriction (No_Finalization, N);
11369             Set_Restriction (No_Exception_Handlers, N);
11370             Set_Restriction (Max_Tasks, N, 0);
11371             Set_Restriction (No_Tasking, N);
11372
11373          ------------------------
11374          -- No_Strict_Aliasing --
11375          ------------------------
11376
11377          --  pragma No_Strict_Aliasing [([Entity =>] type_LOCAL_NAME)];
11378
11379          when Pragma_No_Strict_Aliasing => No_Strict_Aliasing : declare
11380             E_Id : Entity_Id;
11381
11382          begin
11383             GNAT_Pragma;
11384             Check_At_Most_N_Arguments (1);
11385
11386             if Arg_Count = 0 then
11387                Check_Valid_Configuration_Pragma;
11388                Opt.No_Strict_Aliasing := True;
11389
11390             else
11391                Check_Optional_Identifier (Arg2, Name_Entity);
11392                Check_Arg_Is_Local_Name (Arg1);
11393                E_Id := Entity (Get_Pragma_Arg (Arg1));
11394
11395                if E_Id = Any_Type then
11396                   return;
11397                elsif No (E_Id) or else not Is_Access_Type (E_Id) then
11398                   Error_Pragma_Arg ("pragma% requires access type", Arg1);
11399                end if;
11400
11401                Set_No_Strict_Aliasing (Implementation_Base_Type (E_Id));
11402             end if;
11403          end No_Strict_Aliasing;
11404
11405          -----------------------
11406          -- Normalize_Scalars --
11407          -----------------------
11408
11409          --  pragma Normalize_Scalars;
11410
11411          when Pragma_Normalize_Scalars =>
11412             Check_Ada_83_Warning;
11413             Check_Arg_Count (0);
11414             Check_Valid_Configuration_Pragma;
11415
11416             --  Normalize_Scalars creates false positives in CodePeer, and
11417             --  incorrect negative results in Alfa mode, so ignore this pragma
11418             --  in these modes.
11419
11420             if not (CodePeer_Mode or Alfa_Mode) then
11421                Normalize_Scalars := True;
11422                Init_Or_Norm_Scalars := True;
11423             end if;
11424
11425          -----------------
11426          -- Obsolescent --
11427          -----------------
11428
11429          --  pragma Obsolescent;
11430
11431          --  pragma Obsolescent (
11432          --    [Message =>] static_string_EXPRESSION
11433          --  [,[Version =>] Ada_05]]);
11434
11435          --  pragma Obsolescent (
11436          --    [Entity  =>] NAME
11437          --  [,[Message =>] static_string_EXPRESSION
11438          --  [,[Version =>] Ada_05]] );
11439
11440          when Pragma_Obsolescent => Obsolescent : declare
11441             Ename : Node_Id;
11442             Decl  : Node_Id;
11443
11444             procedure Set_Obsolescent (E : Entity_Id);
11445             --  Given an entity Ent, mark it as obsolescent if appropriate
11446
11447             ---------------------
11448             -- Set_Obsolescent --
11449             ---------------------
11450
11451             procedure Set_Obsolescent (E : Entity_Id) is
11452                Active : Boolean;
11453                Ent    : Entity_Id;
11454                S      : String_Id;
11455
11456             begin
11457                Active := True;
11458                Ent    := E;
11459
11460                --  Entity name was given
11461
11462                if Present (Ename) then
11463
11464                   --  If entity name matches, we are fine. Save entity in
11465                   --  pragma argument, for ASIS use.
11466
11467                   if Chars (Ename) = Chars (Ent) then
11468                      Set_Entity (Ename, Ent);
11469                      Generate_Reference (Ent, Ename);
11470
11471                   --  If entity name does not match, only possibility is an
11472                   --  enumeration literal from an enumeration type declaration.
11473
11474                   elsif Ekind (Ent) /= E_Enumeration_Type then
11475                      Error_Pragma
11476                        ("pragma % entity name does not match declaration");
11477
11478                   else
11479                      Ent := First_Literal (E);
11480                      loop
11481                         if No (Ent) then
11482                            Error_Pragma
11483                              ("pragma % entity name does not match any " &
11484                               "enumeration literal");
11485
11486                         elsif Chars (Ent) = Chars (Ename) then
11487                            Set_Entity (Ename, Ent);
11488                            Generate_Reference (Ent, Ename);
11489                            exit;
11490
11491                         else
11492                            Ent := Next_Literal (Ent);
11493                         end if;
11494                      end loop;
11495                   end if;
11496                end if;
11497
11498                --  Ent points to entity to be marked
11499
11500                if Arg_Count >= 1 then
11501
11502                   --  Deal with static string argument
11503
11504                   Check_Arg_Is_Static_Expression (Arg1, Standard_String);
11505                   S := Strval (Get_Pragma_Arg (Arg1));
11506
11507                   for J in 1 .. String_Length (S) loop
11508                      if not In_Character_Range (Get_String_Char (S, J)) then
11509                         Error_Pragma_Arg
11510                           ("pragma% argument does not allow wide characters",
11511                            Arg1);
11512                      end if;
11513                   end loop;
11514
11515                   Obsolescent_Warnings.Append
11516                     ((Ent => Ent, Msg => Strval (Get_Pragma_Arg (Arg1))));
11517
11518                   --  Check for Ada_05 parameter
11519
11520                   if Arg_Count /= 1 then
11521                      Check_Arg_Count (2);
11522
11523                      declare
11524                         Argx : constant Node_Id := Get_Pragma_Arg (Arg2);
11525
11526                      begin
11527                         Check_Arg_Is_Identifier (Argx);
11528
11529                         if Chars (Argx) /= Name_Ada_05 then
11530                            Error_Msg_Name_2 := Name_Ada_05;
11531                            Error_Pragma_Arg
11532                              ("only allowed argument for pragma% is %", Argx);
11533                         end if;
11534
11535                         if Ada_Version_Explicit < Ada_2005
11536                           or else not Warn_On_Ada_2005_Compatibility
11537                         then
11538                            Active := False;
11539                         end if;
11540                      end;
11541                   end if;
11542                end if;
11543
11544                --  Set flag if pragma active
11545
11546                if Active then
11547                   Set_Is_Obsolescent (Ent);
11548                end if;
11549
11550                return;
11551             end Set_Obsolescent;
11552
11553          --  Start of processing for pragma Obsolescent
11554
11555          begin
11556             GNAT_Pragma;
11557
11558             Check_At_Most_N_Arguments (3);
11559
11560             --  See if first argument specifies an entity name
11561
11562             if Arg_Count >= 1
11563               and then
11564                 (Chars (Arg1) = Name_Entity
11565                    or else
11566                      Nkind_In (Get_Pragma_Arg (Arg1), N_Character_Literal,
11567                                                       N_Identifier,
11568                                                       N_Operator_Symbol))
11569             then
11570                Ename := Get_Pragma_Arg (Arg1);
11571
11572                --  Eliminate first argument, so we can share processing
11573
11574                Arg1 := Arg2;
11575                Arg2 := Arg3;
11576                Arg_Count := Arg_Count - 1;
11577
11578             --  No Entity name argument given
11579
11580             else
11581                Ename := Empty;
11582             end if;
11583
11584             if Arg_Count >= 1 then
11585                Check_Optional_Identifier (Arg1, Name_Message);
11586
11587                if Arg_Count = 2 then
11588                   Check_Optional_Identifier (Arg2, Name_Version);
11589                end if;
11590             end if;
11591
11592             --  Get immediately preceding declaration
11593
11594             Decl := Prev (N);
11595             while Present (Decl) and then Nkind (Decl) = N_Pragma loop
11596                Prev (Decl);
11597             end loop;
11598
11599             --  Cases where we do not follow anything other than another pragma
11600
11601             if No (Decl) then
11602
11603                --  First case: library level compilation unit declaration with
11604                --  the pragma immediately following the declaration.
11605
11606                if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
11607                   Set_Obsolescent
11608                     (Defining_Entity (Unit (Parent (Parent (N)))));
11609                   return;
11610
11611                --  Case 2: library unit placement for package
11612
11613                else
11614                   declare
11615                      Ent : constant Entity_Id := Find_Lib_Unit_Name;
11616                   begin
11617                      if Is_Package_Or_Generic_Package (Ent) then
11618                         Set_Obsolescent (Ent);
11619                         return;
11620                      end if;
11621                   end;
11622                end if;
11623
11624             --  Cases where we must follow a declaration
11625
11626             else
11627                if         Nkind (Decl) not in N_Declaration
11628                  and then Nkind (Decl) not in N_Later_Decl_Item
11629                  and then Nkind (Decl) not in N_Generic_Declaration
11630                  and then Nkind (Decl) not in N_Renaming_Declaration
11631                then
11632                   Error_Pragma
11633                     ("pragma% misplaced, "
11634                      & "must immediately follow a declaration");
11635
11636                else
11637                   Set_Obsolescent (Defining_Entity (Decl));
11638                   return;
11639                end if;
11640             end if;
11641          end Obsolescent;
11642
11643          --------------
11644          -- Optimize --
11645          --------------
11646
11647          --  pragma Optimize (Time | Space | Off);
11648
11649          --  The actual check for optimize is done in Gigi. Note that this
11650          --  pragma does not actually change the optimization setting, it
11651          --  simply checks that it is consistent with the pragma.
11652
11653          when Pragma_Optimize =>
11654             Check_No_Identifiers;
11655             Check_Arg_Count (1);
11656             Check_Arg_Is_One_Of (Arg1, Name_Time, Name_Space, Name_Off);
11657
11658          ------------------------
11659          -- Optimize_Alignment --
11660          ------------------------
11661
11662          --  pragma Optimize_Alignment (Time | Space | Off);
11663
11664          when Pragma_Optimize_Alignment => Optimize_Alignment : begin
11665             GNAT_Pragma;
11666             Check_No_Identifiers;
11667             Check_Arg_Count (1);
11668             Check_Valid_Configuration_Pragma;
11669
11670             declare
11671                Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
11672             begin
11673                case Nam is
11674                   when Name_Time =>
11675                      Opt.Optimize_Alignment := 'T';
11676                   when Name_Space =>
11677                      Opt.Optimize_Alignment := 'S';
11678                   when Name_Off =>
11679                      Opt.Optimize_Alignment := 'O';
11680                   when others =>
11681                      Error_Pragma_Arg ("invalid argument for pragma%", Arg1);
11682                end case;
11683             end;
11684
11685             --  Set indication that mode is set locally. If we are in fact in a
11686             --  configuration pragma file, this setting is harmless since the
11687             --  switch will get reset anyway at the start of each unit.
11688
11689             Optimize_Alignment_Local := True;
11690          end Optimize_Alignment;
11691
11692          -------------
11693          -- Ordered --
11694          -------------
11695
11696          --  pragma Ordered (first_enumeration_subtype_LOCAL_NAME);
11697
11698          when Pragma_Ordered => Ordered : declare
11699             Assoc   : constant Node_Id := Arg1;
11700             Type_Id : Node_Id;
11701             Typ     : Entity_Id;
11702
11703          begin
11704             GNAT_Pragma;
11705             Check_No_Identifiers;
11706             Check_Arg_Count (1);
11707             Check_Arg_Is_Local_Name (Arg1);
11708
11709             Type_Id := Get_Pragma_Arg (Assoc);
11710             Find_Type (Type_Id);
11711             Typ := Entity (Type_Id);
11712
11713             if Typ = Any_Type then
11714                return;
11715             else
11716                Typ := Underlying_Type (Typ);
11717             end if;
11718
11719             if not Is_Enumeration_Type (Typ) then
11720                Error_Pragma ("pragma% must specify enumeration type");
11721             end if;
11722
11723             Check_First_Subtype (Arg1);
11724             Set_Has_Pragma_Ordered (Base_Type (Typ));
11725          end Ordered;
11726
11727          ----------
11728          -- Pack --
11729          ----------
11730
11731          --  pragma Pack (first_subtype_LOCAL_NAME);
11732
11733          when Pragma_Pack => Pack : declare
11734             Assoc   : constant Node_Id := Arg1;
11735             Type_Id : Node_Id;
11736             Typ     : Entity_Id;
11737             Ctyp    : Entity_Id;
11738             Ignore  : Boolean := False;
11739
11740          begin
11741             Check_No_Identifiers;
11742             Check_Arg_Count (1);
11743             Check_Arg_Is_Local_Name (Arg1);
11744
11745             Type_Id := Get_Pragma_Arg (Assoc);
11746             Find_Type (Type_Id);
11747             Typ := Entity (Type_Id);
11748
11749             if Typ = Any_Type
11750               or else Rep_Item_Too_Early (Typ, N)
11751             then
11752                return;
11753             else
11754                Typ := Underlying_Type (Typ);
11755             end if;
11756
11757             if not Is_Array_Type (Typ) and then not Is_Record_Type (Typ) then
11758                Error_Pragma ("pragma% must specify array or record type");
11759             end if;
11760
11761             Check_First_Subtype (Arg1);
11762             Check_Duplicate_Pragma (Typ);
11763
11764             --  Array type
11765
11766             if Is_Array_Type (Typ) then
11767                Ctyp := Component_Type (Typ);
11768
11769                --  Ignore pack that does nothing
11770
11771                if Known_Static_Esize (Ctyp)
11772                  and then Known_Static_RM_Size (Ctyp)
11773                  and then Esize (Ctyp) = RM_Size (Ctyp)
11774                  and then Addressable (Esize (Ctyp))
11775                then
11776                   Ignore := True;
11777                end if;
11778
11779                --  Process OK pragma Pack. Note that if there is a separate
11780                --  component clause present, the Pack will be cancelled. This
11781                --  processing is in Freeze.
11782
11783                if not Rep_Item_Too_Late (Typ, N) then
11784
11785                   --  In the context of static code analysis, we do not need
11786                   --  complex front-end expansions related to pragma Pack,
11787                   --  so disable handling of pragma Pack in these cases.
11788
11789                   if CodePeer_Mode or Alfa_Mode then
11790                      null;
11791
11792                   --  Don't attempt any packing for VM targets. We possibly
11793                   --  could deal with some cases of array bit-packing, but we
11794                   --  don't bother, since this is not a typical kind of
11795                   --  representation in the VM context anyway (and would not
11796                   --  for example work nicely with the debugger).
11797
11798                   elsif VM_Target /= No_VM then
11799                      if not GNAT_Mode then
11800                         Error_Pragma
11801                           ("?pragma% ignored in this configuration");
11802                      end if;
11803
11804                   --  Normal case where we do the pack action
11805
11806                   else
11807                      if not Ignore then
11808                         Set_Is_Packed            (Base_Type (Typ));
11809                         Set_Has_Non_Standard_Rep (Base_Type (Typ));
11810                      end if;
11811
11812                      Set_Has_Pragma_Pack (Base_Type (Typ));
11813                   end if;
11814                end if;
11815
11816             --  For record types, the pack is always effective
11817
11818             else pragma Assert (Is_Record_Type (Typ));
11819                if not Rep_Item_Too_Late (Typ, N) then
11820
11821                   --  Ignore pack request with warning in VM mode (skip warning
11822                   --  if we are compiling GNAT run time library).
11823
11824                   if VM_Target /= No_VM then
11825                      if not GNAT_Mode then
11826                         Error_Pragma
11827                           ("?pragma% ignored in this configuration");
11828                      end if;
11829
11830                   --  Normal case of pack request active
11831
11832                   else
11833                      Set_Is_Packed            (Base_Type (Typ));
11834                      Set_Has_Pragma_Pack      (Base_Type (Typ));
11835                      Set_Has_Non_Standard_Rep (Base_Type (Typ));
11836                   end if;
11837                end if;
11838             end if;
11839          end Pack;
11840
11841          ----------
11842          -- Page --
11843          ----------
11844
11845          --  pragma Page;
11846
11847          --  There is nothing to do here, since we did all the processing for
11848          --  this pragma in Par.Prag (so that it works properly even in syntax
11849          --  only mode).
11850
11851          when Pragma_Page =>
11852             null;
11853
11854          -------------
11855          -- Passive --
11856          -------------
11857
11858          --  pragma Passive [(PASSIVE_FORM)];
11859
11860          --  PASSIVE_FORM ::= Semaphore | No
11861
11862          when Pragma_Passive =>
11863             GNAT_Pragma;
11864
11865             if Nkind (Parent (N)) /= N_Task_Definition then
11866                Error_Pragma ("pragma% must be within task definition");
11867             end if;
11868
11869             if Arg_Count /= 0 then
11870                Check_Arg_Count (1);
11871                Check_Arg_Is_One_Of (Arg1, Name_Semaphore, Name_No);
11872             end if;
11873
11874          ----------------------------------
11875          -- Preelaborable_Initialization --
11876          ----------------------------------
11877
11878          --  pragma Preelaborable_Initialization (DIRECT_NAME);
11879
11880          when Pragma_Preelaborable_Initialization => Preelab_Init : declare
11881             Ent : Entity_Id;
11882
11883          begin
11884             Ada_2005_Pragma;
11885             Check_Arg_Count (1);
11886             Check_No_Identifiers;
11887             Check_Arg_Is_Identifier (Arg1);
11888             Check_Arg_Is_Local_Name (Arg1);
11889             Check_First_Subtype (Arg1);
11890             Ent := Entity (Get_Pragma_Arg (Arg1));
11891
11892             if not (Is_Private_Type (Ent)
11893                       or else
11894                     Is_Protected_Type (Ent)
11895                       or else
11896                     (Is_Generic_Type (Ent) and then Is_Derived_Type (Ent)))
11897             then
11898                Error_Pragma_Arg
11899                  ("pragma % can only be applied to private, formal derived or "
11900                   & "protected type",
11901                   Arg1);
11902             end if;
11903
11904             --  Give an error if the pragma is applied to a protected type that
11905             --  does not qualify (due to having entries, or due to components
11906             --  that do not qualify).
11907
11908             if Is_Protected_Type (Ent)
11909               and then not Has_Preelaborable_Initialization (Ent)
11910             then
11911                Error_Msg_N
11912                  ("protected type & does not have preelaborable " &
11913                   "initialization", Ent);
11914
11915             --  Otherwise mark the type as definitely having preelaborable
11916             --  initialization.
11917
11918             else
11919                Set_Known_To_Have_Preelab_Init (Ent);
11920             end if;
11921
11922             if Has_Pragma_Preelab_Init (Ent)
11923               and then Warn_On_Redundant_Constructs
11924             then
11925                Error_Pragma ("?duplicate pragma%!");
11926             else
11927                Set_Has_Pragma_Preelab_Init (Ent);
11928             end if;
11929          end Preelab_Init;
11930
11931          --------------------
11932          -- Persistent_BSS --
11933          --------------------
11934
11935          --  pragma Persistent_BSS [(object_NAME)];
11936
11937          when Pragma_Persistent_BSS => Persistent_BSS :  declare
11938             Decl : Node_Id;
11939             Ent  : Entity_Id;
11940             Prag : Node_Id;
11941
11942          begin
11943             GNAT_Pragma;
11944             Check_At_Most_N_Arguments (1);
11945
11946             --  Case of application to specific object (one argument)
11947
11948             if Arg_Count = 1 then
11949                Check_Arg_Is_Library_Level_Local_Name (Arg1);
11950
11951                if not Is_Entity_Name (Get_Pragma_Arg (Arg1))
11952                  or else not
11953                   Ekind_In (Entity (Get_Pragma_Arg (Arg1)), E_Variable,
11954                                                             E_Constant)
11955                then
11956                   Error_Pragma_Arg ("pragma% only applies to objects", Arg1);
11957                end if;
11958
11959                Ent := Entity (Get_Pragma_Arg (Arg1));
11960                Decl := Parent (Ent);
11961
11962                if Rep_Item_Too_Late (Ent, N) then
11963                   return;
11964                end if;
11965
11966                if Present (Expression (Decl)) then
11967                   Error_Pragma_Arg
11968                     ("object for pragma% cannot have initialization", Arg1);
11969                end if;
11970
11971                if not Is_Potentially_Persistent_Type (Etype (Ent)) then
11972                   Error_Pragma_Arg
11973                     ("object type for pragma% is not potentially persistent",
11974                      Arg1);
11975                end if;
11976
11977                Check_Duplicate_Pragma (Ent);
11978
11979                Prag :=
11980                  Make_Linker_Section_Pragma
11981                    (Ent, Sloc (N), ".persistent.bss");
11982                Insert_After (N, Prag);
11983                Analyze (Prag);
11984
11985             --  Case of use as configuration pragma with no arguments
11986
11987             else
11988                Check_Valid_Configuration_Pragma;
11989                Persistent_BSS_Mode := True;
11990             end if;
11991          end Persistent_BSS;
11992
11993          -------------
11994          -- Polling --
11995          -------------
11996
11997          --  pragma Polling (ON | OFF);
11998
11999          when Pragma_Polling =>
12000             GNAT_Pragma;
12001             Check_Arg_Count (1);
12002             Check_No_Identifiers;
12003             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
12004             Polling_Required := (Chars (Get_Pragma_Arg (Arg1)) = Name_On);
12005
12006          -------------------
12007          -- Postcondition --
12008          -------------------
12009
12010          --  pragma Postcondition ([Check   =>] Boolean_EXPRESSION
12011          --                      [,[Message =>] String_EXPRESSION]);
12012
12013          when Pragma_Postcondition => Postcondition : declare
12014             In_Body : Boolean;
12015             pragma Warnings (Off, In_Body);
12016
12017          begin
12018             GNAT_Pragma;
12019             Check_At_Least_N_Arguments (1);
12020             Check_At_Most_N_Arguments (2);
12021             Check_Optional_Identifier (Arg1, Name_Check);
12022
12023             --  All we need to do here is call the common check procedure,
12024             --  the remainder of the processing is found in Sem_Ch6/Sem_Ch7.
12025
12026             Check_Precondition_Postcondition (In_Body);
12027          end Postcondition;
12028
12029          ------------------
12030          -- Precondition --
12031          ------------------
12032
12033          --  pragma Precondition ([Check   =>] Boolean_EXPRESSION
12034          --                     [,[Message =>] String_EXPRESSION]);
12035
12036          when Pragma_Precondition => Precondition : declare
12037             In_Body : Boolean;
12038
12039          begin
12040             GNAT_Pragma;
12041             Check_At_Least_N_Arguments (1);
12042             Check_At_Most_N_Arguments (2);
12043             Check_Optional_Identifier (Arg1, Name_Check);
12044             Check_Precondition_Postcondition (In_Body);
12045
12046             --  If in spec, nothing more to do. If in body, then we convert the
12047             --  pragma to pragma Check (Precondition, cond [, msg]). Note we do
12048             --  this whether or not precondition checks are enabled. That works
12049             --  fine since pragma Check will do this check, and will also
12050             --  analyze the condition itself in the proper context.
12051
12052             if In_Body then
12053                Rewrite (N,
12054                  Make_Pragma (Loc,
12055                    Chars => Name_Check,
12056                    Pragma_Argument_Associations => New_List (
12057                      Make_Pragma_Argument_Association (Loc,
12058                        Expression => Make_Identifier (Loc, Name_Precondition)),
12059
12060                      Make_Pragma_Argument_Association (Sloc (Arg1),
12061                        Expression => Relocate_Node (Get_Pragma_Arg (Arg1))))));
12062
12063                if Arg_Count = 2 then
12064                   Append_To (Pragma_Argument_Associations (N),
12065                     Make_Pragma_Argument_Association (Sloc (Arg2),
12066                       Expression => Relocate_Node (Get_Pragma_Arg (Arg2))));
12067                end if;
12068
12069                Analyze (N);
12070             end if;
12071          end Precondition;
12072
12073          ---------------
12074          -- Predicate --
12075          ---------------
12076
12077          --  pragma Predicate
12078          --    ([Entity =>] type_LOCAL_NAME,
12079          --     [Check  =>] EXPRESSION);
12080
12081          when Pragma_Predicate => Predicate : declare
12082             Type_Id : Node_Id;
12083             Typ     : Entity_Id;
12084
12085             Discard : Boolean;
12086             pragma Unreferenced (Discard);
12087
12088          begin
12089             GNAT_Pragma;
12090             Check_Arg_Count (2);
12091             Check_Optional_Identifier (Arg1, Name_Entity);
12092             Check_Optional_Identifier (Arg2, Name_Check);
12093
12094             Check_Arg_Is_Local_Name (Arg1);
12095
12096             Type_Id := Get_Pragma_Arg (Arg1);
12097             Find_Type (Type_Id);
12098             Typ := Entity (Type_Id);
12099
12100             if Typ = Any_Type then
12101                return;
12102             end if;
12103
12104             --  The remaining processing is simply to link the pragma on to
12105             --  the rep item chain, for processing when the type is frozen.
12106             --  This is accomplished by a call to Rep_Item_Too_Late. We also
12107             --  mark the type as having predicates.
12108
12109             Set_Has_Predicates (Typ);
12110             Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
12111          end Predicate;
12112
12113          ------------------
12114          -- Preelaborate --
12115          ------------------
12116
12117          --  pragma Preelaborate [(library_unit_NAME)];
12118
12119          --  Set the flag Is_Preelaborated of program unit name entity
12120
12121          when Pragma_Preelaborate => Preelaborate : declare
12122             Pa  : constant Node_Id   := Parent (N);
12123             Pk  : constant Node_Kind := Nkind (Pa);
12124             Ent : Entity_Id;
12125
12126          begin
12127             Check_Ada_83_Warning;
12128             Check_Valid_Library_Unit_Pragma;
12129
12130             if Nkind (N) = N_Null_Statement then
12131                return;
12132             end if;
12133
12134             Ent := Find_Lib_Unit_Name;
12135             Check_Duplicate_Pragma (Ent);
12136
12137             --  This filters out pragmas inside generic parent then
12138             --  show up inside instantiation
12139
12140             if Present (Ent)
12141               and then not (Pk = N_Package_Specification
12142                              and then Present (Generic_Parent (Pa)))
12143             then
12144                if not Debug_Flag_U then
12145                   Set_Is_Preelaborated (Ent);
12146                   Set_Suppress_Elaboration_Warnings (Ent);
12147                end if;
12148             end if;
12149          end Preelaborate;
12150
12151          ---------------------
12152          -- Preelaborate_05 --
12153          ---------------------
12154
12155          --  pragma Preelaborate_05 [(library_unit_NAME)];
12156
12157          --  This pragma is useable only in GNAT_Mode, where it is used like
12158          --  pragma Preelaborate but it is only effective in Ada 2005 mode
12159          --  (otherwise it is ignored). This is used to implement AI-362 which
12160          --  recategorizes some run-time packages in Ada 2005 mode.
12161
12162          when Pragma_Preelaborate_05 => Preelaborate_05 : declare
12163             Ent : Entity_Id;
12164
12165          begin
12166             GNAT_Pragma;
12167             Check_Valid_Library_Unit_Pragma;
12168
12169             if not GNAT_Mode then
12170                Error_Pragma ("pragma% only available in GNAT mode");
12171             end if;
12172
12173             if Nkind (N) = N_Null_Statement then
12174                return;
12175             end if;
12176
12177             --  This is one of the few cases where we need to test the value of
12178             --  Ada_Version_Explicit rather than Ada_Version (which is always
12179             --  set to Ada_2012 in a predefined unit), we need to know the
12180             --  explicit version set to know if this pragma is active.
12181
12182             if Ada_Version_Explicit >= Ada_2005 then
12183                Ent := Find_Lib_Unit_Name;
12184                Set_Is_Preelaborated (Ent);
12185                Set_Suppress_Elaboration_Warnings (Ent);
12186             end if;
12187          end Preelaborate_05;
12188
12189          --------------
12190          -- Priority --
12191          --------------
12192
12193          --  pragma Priority (EXPRESSION);
12194
12195          when Pragma_Priority => Priority : declare
12196             P   : constant Node_Id := Parent (N);
12197             Arg : Node_Id;
12198
12199          begin
12200             Check_No_Identifiers;
12201             Check_Arg_Count (1);
12202
12203             --  Subprogram case
12204
12205             if Nkind (P) = N_Subprogram_Body then
12206                Check_In_Main_Program;
12207
12208                Arg := Get_Pragma_Arg (Arg1);
12209                Analyze_And_Resolve (Arg, Standard_Integer);
12210
12211                --  Must be static
12212
12213                if not Is_Static_Expression (Arg) then
12214                   Flag_Non_Static_Expr
12215                     ("main subprogram priority is not static!", Arg);
12216                   raise Pragma_Exit;
12217
12218                --  If constraint error, then we already signalled an error
12219
12220                elsif Raises_Constraint_Error (Arg) then
12221                   null;
12222
12223                --  Otherwise check in range
12224
12225                else
12226                   declare
12227                      Val : constant Uint := Expr_Value (Arg);
12228
12229                   begin
12230                      if Val < 0
12231                        or else Val > Expr_Value (Expression
12232                                        (Parent (RTE (RE_Max_Priority))))
12233                      then
12234                         Error_Pragma_Arg
12235                           ("main subprogram priority is out of range", Arg1);
12236                      end if;
12237                   end;
12238                end if;
12239
12240                Set_Main_Priority
12241                     (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
12242
12243                --  Load an arbitrary entity from System.Tasking to make sure
12244                --  this package is implicitly with'ed, since we need to have
12245                --  the tasking run-time active for the pragma Priority to have
12246                --  any effect.
12247
12248                declare
12249                   Discard : Entity_Id;
12250                   pragma Warnings (Off, Discard);
12251                begin
12252                   Discard := RTE (RE_Task_List);
12253                end;
12254
12255             --  Task or Protected, must be of type Integer
12256
12257             elsif Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
12258                Arg := Get_Pragma_Arg (Arg1);
12259
12260                --  The expression must be analyzed in the special manner
12261                --  described in "Handling of Default and Per-Object
12262                --  Expressions" in sem.ads.
12263
12264                Preanalyze_Spec_Expression (Arg, Standard_Integer);
12265
12266                if not Is_Static_Expression (Arg) then
12267                   Check_Restriction (Static_Priorities, Arg);
12268                end if;
12269
12270             --  Anything else is incorrect
12271
12272             else
12273                Pragma_Misplaced;
12274             end if;
12275
12276             if Has_Pragma_Priority (P) then
12277                Error_Pragma ("duplicate pragma% not allowed");
12278             else
12279                Set_Has_Pragma_Priority (P, True);
12280
12281                if Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
12282                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
12283                   --  exp_ch9 should use this ???
12284                end if;
12285             end if;
12286          end Priority;
12287
12288          -----------------------------------
12289          -- Priority_Specific_Dispatching --
12290          -----------------------------------
12291
12292          --  pragma Priority_Specific_Dispatching (
12293          --    policy_IDENTIFIER,
12294          --    first_priority_EXPRESSION,
12295          --    last_priority_EXPRESSION);
12296
12297          when Pragma_Priority_Specific_Dispatching =>
12298          Priority_Specific_Dispatching : declare
12299             Prio_Id : constant Entity_Id := RTE (RE_Any_Priority);
12300             --  This is the entity System.Any_Priority;
12301
12302             DP          : Character;
12303             Lower_Bound : Node_Id;
12304             Upper_Bound : Node_Id;
12305             Lower_Val   : Uint;
12306             Upper_Val   : Uint;
12307
12308          begin
12309             Ada_2005_Pragma;
12310             Check_Arg_Count (3);
12311             Check_No_Identifiers;
12312             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
12313             Check_Valid_Configuration_Pragma;
12314             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
12315             DP := Fold_Upper (Name_Buffer (1));
12316
12317             Lower_Bound := Get_Pragma_Arg (Arg2);
12318             Check_Arg_Is_Static_Expression (Lower_Bound, Standard_Integer);
12319             Lower_Val := Expr_Value (Lower_Bound);
12320
12321             Upper_Bound := Get_Pragma_Arg (Arg3);
12322             Check_Arg_Is_Static_Expression (Upper_Bound, Standard_Integer);
12323             Upper_Val := Expr_Value (Upper_Bound);
12324
12325             --  It is not allowed to use Task_Dispatching_Policy and
12326             --  Priority_Specific_Dispatching in the same partition.
12327
12328             if Task_Dispatching_Policy /= ' ' then
12329                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
12330                Error_Pragma
12331                  ("pragma% incompatible with Task_Dispatching_Policy#");
12332
12333             --  Check lower bound in range
12334
12335             elsif Lower_Val < Expr_Value (Type_Low_Bound (Prio_Id))
12336                     or else
12337                   Lower_Val > Expr_Value (Type_High_Bound (Prio_Id))
12338             then
12339                Error_Pragma_Arg
12340                  ("first_priority is out of range", Arg2);
12341
12342             --  Check upper bound in range
12343
12344             elsif Upper_Val < Expr_Value (Type_Low_Bound (Prio_Id))
12345                     or else
12346                   Upper_Val > Expr_Value (Type_High_Bound (Prio_Id))
12347             then
12348                Error_Pragma_Arg
12349                  ("last_priority is out of range", Arg3);
12350
12351             --  Check that the priority range is valid
12352
12353             elsif Lower_Val > Upper_Val then
12354                Error_Pragma
12355                  ("last_priority_expression must be greater than" &
12356                   " or equal to first_priority_expression");
12357
12358             --  Store the new policy, but always preserve System_Location since
12359             --  we like the error message with the run-time name.
12360
12361             else
12362                --  Check overlapping in the priority ranges specified in other
12363                --  Priority_Specific_Dispatching pragmas within the same
12364                --  partition. We can only check those we know about!
12365
12366                for J in
12367                   Specific_Dispatching.First .. Specific_Dispatching.Last
12368                loop
12369                   if Specific_Dispatching.Table (J).First_Priority in
12370                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
12371                   or else Specific_Dispatching.Table (J).Last_Priority in
12372                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
12373                   then
12374                      Error_Msg_Sloc :=
12375                        Specific_Dispatching.Table (J).Pragma_Loc;
12376                         Error_Pragma
12377                           ("priority range overlaps with "
12378                            & "Priority_Specific_Dispatching#");
12379                   end if;
12380                end loop;
12381
12382                --  The use of Priority_Specific_Dispatching is incompatible
12383                --  with Task_Dispatching_Policy.
12384
12385                if Task_Dispatching_Policy /= ' ' then
12386                   Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
12387                      Error_Pragma
12388                        ("Priority_Specific_Dispatching incompatible "
12389                         & "with Task_Dispatching_Policy#");
12390                end if;
12391
12392                --  The use of Priority_Specific_Dispatching forces ceiling
12393                --  locking policy.
12394
12395                if Locking_Policy /= ' ' and then Locking_Policy /= 'C' then
12396                   Error_Msg_Sloc := Locking_Policy_Sloc;
12397                      Error_Pragma
12398                        ("Priority_Specific_Dispatching incompatible "
12399                         & "with Locking_Policy#");
12400
12401                --  Set the Ceiling_Locking policy, but preserve System_Location
12402                --  since we like the error message with the run time name.
12403
12404                else
12405                   Locking_Policy := 'C';
12406
12407                   if Locking_Policy_Sloc /= System_Location then
12408                      Locking_Policy_Sloc := Loc;
12409                   end if;
12410                end if;
12411
12412                --  Add entry in the table
12413
12414                Specific_Dispatching.Append
12415                     ((Dispatching_Policy => DP,
12416                       First_Priority     => UI_To_Int (Lower_Val),
12417                       Last_Priority      => UI_To_Int (Upper_Val),
12418                       Pragma_Loc         => Loc));
12419             end if;
12420          end Priority_Specific_Dispatching;
12421
12422          -------------
12423          -- Profile --
12424          -------------
12425
12426          --  pragma Profile (profile_IDENTIFIER);
12427
12428          --  profile_IDENTIFIER => Restricted | Ravenscar
12429
12430          when Pragma_Profile =>
12431             Ada_2005_Pragma;
12432             Check_Arg_Count (1);
12433             Check_Valid_Configuration_Pragma;
12434             Check_No_Identifiers;
12435
12436             declare
12437                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
12438
12439             begin
12440                if Chars (Argx) = Name_Ravenscar then
12441                   Set_Ravenscar_Profile (N);
12442
12443                elsif Chars (Argx) = Name_Restricted then
12444                   Set_Profile_Restrictions
12445                     (Restricted,
12446                      N, Warn => Treat_Restrictions_As_Warnings);
12447
12448                elsif Chars (Argx) = Name_No_Implementation_Extensions then
12449                   Set_Profile_Restrictions
12450                     (No_Implementation_Extensions,
12451                      N, Warn => Treat_Restrictions_As_Warnings);
12452
12453                else
12454                   Error_Pragma_Arg ("& is not a valid profile", Argx);
12455                end if;
12456             end;
12457
12458          ----------------------
12459          -- Profile_Warnings --
12460          ----------------------
12461
12462          --  pragma Profile_Warnings (profile_IDENTIFIER);
12463
12464          --  profile_IDENTIFIER => Restricted | Ravenscar
12465
12466          when Pragma_Profile_Warnings =>
12467             GNAT_Pragma;
12468             Check_Arg_Count (1);
12469             Check_Valid_Configuration_Pragma;
12470             Check_No_Identifiers;
12471
12472             declare
12473                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
12474
12475             begin
12476                if Chars (Argx) = Name_Ravenscar then
12477                   Set_Profile_Restrictions (Ravenscar, N, Warn => True);
12478
12479                elsif Chars (Argx) = Name_Restricted then
12480                   Set_Profile_Restrictions (Restricted, N, Warn => True);
12481
12482                elsif Chars (Argx) = Name_No_Implementation_Extensions then
12483                   Set_Profile_Restrictions
12484                     (No_Implementation_Extensions, N, Warn => True);
12485
12486                else
12487                   Error_Pragma_Arg ("& is not a valid profile", Argx);
12488                end if;
12489             end;
12490
12491          --------------------------
12492          -- Propagate_Exceptions --
12493          --------------------------
12494
12495          --  pragma Propagate_Exceptions;
12496
12497          --  Note: this pragma is obsolete and has no effect
12498
12499          when Pragma_Propagate_Exceptions =>
12500             GNAT_Pragma;
12501             Check_Arg_Count (0);
12502
12503             if In_Extended_Main_Source_Unit (N) then
12504                Propagate_Exceptions := True;
12505             end if;
12506
12507          ------------------
12508          -- Psect_Object --
12509          ------------------
12510
12511          --  pragma Psect_Object (
12512          --        [Internal =>] LOCAL_NAME,
12513          --     [, [External =>] EXTERNAL_SYMBOL]
12514          --     [, [Size     =>] EXTERNAL_SYMBOL]);
12515
12516          when Pragma_Psect_Object | Pragma_Common_Object =>
12517          Psect_Object : declare
12518             Args  : Args_List (1 .. 3);
12519             Names : constant Name_List (1 .. 3) := (
12520                       Name_Internal,
12521                       Name_External,
12522                       Name_Size);
12523
12524             Internal : Node_Id renames Args (1);
12525             External : Node_Id renames Args (2);
12526             Size     : Node_Id renames Args (3);
12527
12528             Def_Id : Entity_Id;
12529
12530             procedure Check_Too_Long (Arg : Node_Id);
12531             --  Posts message if the argument is an identifier with more
12532             --  than 31 characters, or a string literal with more than
12533             --  31 characters, and we are operating under VMS
12534
12535             --------------------
12536             -- Check_Too_Long --
12537             --------------------
12538
12539             procedure Check_Too_Long (Arg : Node_Id) is
12540                X : constant Node_Id := Original_Node (Arg);
12541
12542             begin
12543                if not Nkind_In (X, N_String_Literal, N_Identifier) then
12544                   Error_Pragma_Arg
12545                     ("inappropriate argument for pragma %", Arg);
12546                end if;
12547
12548                if OpenVMS_On_Target then
12549                   if (Nkind (X) = N_String_Literal
12550                        and then String_Length (Strval (X)) > 31)
12551                     or else
12552                      (Nkind (X) = N_Identifier
12553                        and then Length_Of_Name (Chars (X)) > 31)
12554                   then
12555                      Error_Pragma_Arg
12556                        ("argument for pragma % is longer than 31 characters",
12557                         Arg);
12558                   end if;
12559                end if;
12560             end Check_Too_Long;
12561
12562          --  Start of processing for Common_Object/Psect_Object
12563
12564          begin
12565             GNAT_Pragma;
12566             Gather_Associations (Names, Args);
12567             Process_Extended_Import_Export_Internal_Arg (Internal);
12568
12569             Def_Id := Entity (Internal);
12570
12571             if not Ekind_In (Def_Id, E_Constant, E_Variable) then
12572                Error_Pragma_Arg
12573                  ("pragma% must designate an object", Internal);
12574             end if;
12575
12576             Check_Too_Long (Internal);
12577
12578             if Is_Imported (Def_Id) or else Is_Exported (Def_Id) then
12579                Error_Pragma_Arg
12580                  ("cannot use pragma% for imported/exported object",
12581                   Internal);
12582             end if;
12583
12584             if Is_Concurrent_Type (Etype (Internal)) then
12585                Error_Pragma_Arg
12586                  ("cannot specify pragma % for task/protected object",
12587                   Internal);
12588             end if;
12589
12590             if Has_Rep_Pragma (Def_Id, Name_Common_Object)
12591                  or else
12592                Has_Rep_Pragma (Def_Id, Name_Psect_Object)
12593             then
12594                Error_Msg_N ("?duplicate Common/Psect_Object pragma", N);
12595             end if;
12596
12597             if Ekind (Def_Id) = E_Constant then
12598                Error_Pragma_Arg
12599                  ("cannot specify pragma % for a constant", Internal);
12600             end if;
12601
12602             if Is_Record_Type (Etype (Internal)) then
12603                declare
12604                   Ent  : Entity_Id;
12605                   Decl : Entity_Id;
12606
12607                begin
12608                   Ent := First_Entity (Etype (Internal));
12609                   while Present (Ent) loop
12610                      Decl := Declaration_Node (Ent);
12611
12612                      if Ekind (Ent) = E_Component
12613                        and then Nkind (Decl) = N_Component_Declaration
12614                        and then Present (Expression (Decl))
12615                        and then Warn_On_Export_Import
12616                      then
12617                         Error_Msg_N
12618                           ("?object for pragma % has defaults", Internal);
12619                         exit;
12620
12621                      else
12622                         Next_Entity (Ent);
12623                      end if;
12624                   end loop;
12625                end;
12626             end if;
12627
12628             if Present (Size) then
12629                Check_Too_Long (Size);
12630             end if;
12631
12632             if Present (External) then
12633                Check_Arg_Is_External_Name (External);
12634                Check_Too_Long (External);
12635             end if;
12636
12637             --  If all error tests pass, link pragma on to the rep item chain
12638
12639             Record_Rep_Item (Def_Id, N);
12640          end Psect_Object;
12641
12642          ----------
12643          -- Pure --
12644          ----------
12645
12646          --  pragma Pure [(library_unit_NAME)];
12647
12648          when Pragma_Pure => Pure : declare
12649             Ent : Entity_Id;
12650
12651          begin
12652             Check_Ada_83_Warning;
12653             Check_Valid_Library_Unit_Pragma;
12654
12655             if Nkind (N) = N_Null_Statement then
12656                return;
12657             end if;
12658
12659             Ent := Find_Lib_Unit_Name;
12660             Set_Is_Pure (Ent);
12661             Set_Has_Pragma_Pure (Ent);
12662             Set_Suppress_Elaboration_Warnings (Ent);
12663          end Pure;
12664
12665          -------------
12666          -- Pure_05 --
12667          -------------
12668
12669          --  pragma Pure_05 [(library_unit_NAME)];
12670
12671          --  This pragma is useable only in GNAT_Mode, where it is used like
12672          --  pragma Pure but it is only effective in Ada 2005 mode (otherwise
12673          --  it is ignored). It may be used after a pragma Preelaborate, in
12674          --  which case it overrides the effect of the pragma Preelaborate.
12675          --  This is used to implement AI-362 which recategorizes some run-time
12676          --  packages in Ada 2005 mode.
12677
12678          when Pragma_Pure_05 => Pure_05 : declare
12679             Ent : Entity_Id;
12680
12681          begin
12682             GNAT_Pragma;
12683             Check_Valid_Library_Unit_Pragma;
12684
12685             if not GNAT_Mode then
12686                Error_Pragma ("pragma% only available in GNAT mode");
12687             end if;
12688
12689             if Nkind (N) = N_Null_Statement then
12690                return;
12691             end if;
12692
12693             --  This is one of the few cases where we need to test the value of
12694             --  Ada_Version_Explicit rather than Ada_Version (which is always
12695             --  set to Ada_2012 in a predefined unit), we need to know the
12696             --  explicit version set to know if this pragma is active.
12697
12698             if Ada_Version_Explicit >= Ada_2005 then
12699                Ent := Find_Lib_Unit_Name;
12700                Set_Is_Preelaborated (Ent, False);
12701                Set_Is_Pure (Ent);
12702                Set_Suppress_Elaboration_Warnings (Ent);
12703             end if;
12704          end Pure_05;
12705
12706          -------------
12707          -- Pure_12 --
12708          -------------
12709
12710          --  pragma Pure_12 [(library_unit_NAME)];
12711
12712          --  This pragma is useable only in GNAT_Mode, where it is used like
12713          --  pragma Pure but it is only effective in Ada 2012 mode (otherwise
12714          --  it is ignored). It may be used after a pragma Preelaborate, in
12715          --  which case it overrides the effect of the pragma Preelaborate.
12716          --  This is used to implement AI05-0212 which recategorizes some
12717          --  run-time packages in Ada 2012 mode.
12718
12719          when Pragma_Pure_12 => Pure_12 : declare
12720             Ent : Entity_Id;
12721
12722          begin
12723             GNAT_Pragma;
12724             Check_Valid_Library_Unit_Pragma;
12725
12726             if not GNAT_Mode then
12727                Error_Pragma ("pragma% only available in GNAT mode");
12728             end if;
12729
12730             if Nkind (N) = N_Null_Statement then
12731                return;
12732             end if;
12733
12734             --  This is one of the few cases where we need to test the value of
12735             --  Ada_Version_Explicit rather than Ada_Version (which is always
12736             --  set to Ada_2012 in a predefined unit), we need to know the
12737             --  explicit version set to know if this pragma is active.
12738
12739             if Ada_Version_Explicit >= Ada_2012 then
12740                Ent := Find_Lib_Unit_Name;
12741                Set_Is_Preelaborated (Ent, False);
12742                Set_Is_Pure (Ent);
12743                Set_Suppress_Elaboration_Warnings (Ent);
12744             end if;
12745          end Pure_12;
12746
12747          -------------------
12748          -- Pure_Function --
12749          -------------------
12750
12751          --  pragma Pure_Function ([Entity =>] function_LOCAL_NAME);
12752
12753          when Pragma_Pure_Function => Pure_Function : declare
12754             E_Id      : Node_Id;
12755             E         : Entity_Id;
12756             Def_Id    : Entity_Id;
12757             Effective : Boolean := False;
12758
12759          begin
12760             GNAT_Pragma;
12761             Check_Arg_Count (1);
12762             Check_Optional_Identifier (Arg1, Name_Entity);
12763             Check_Arg_Is_Local_Name (Arg1);
12764             E_Id := Get_Pragma_Arg (Arg1);
12765
12766             if Error_Posted (E_Id) then
12767                return;
12768             end if;
12769
12770             --  Loop through homonyms (overloadings) of referenced entity
12771
12772             E := Entity (E_Id);
12773
12774             if Present (E) then
12775                loop
12776                   Def_Id := Get_Base_Subprogram (E);
12777
12778                   if not Ekind_In (Def_Id, E_Function,
12779                                            E_Generic_Function,
12780                                            E_Operator)
12781                   then
12782                      Error_Pragma_Arg
12783                        ("pragma% requires a function name", Arg1);
12784                   end if;
12785
12786                   Set_Is_Pure (Def_Id);
12787
12788                   if not Has_Pragma_Pure_Function (Def_Id) then
12789                      Set_Has_Pragma_Pure_Function (Def_Id);
12790                      Effective := True;
12791                   end if;
12792
12793                   exit when From_Aspect_Specification (N);
12794                   E := Homonym (E);
12795                   exit when No (E) or else Scope (E) /= Current_Scope;
12796                end loop;
12797
12798                if not Effective
12799                  and then Warn_On_Redundant_Constructs
12800                then
12801                   Error_Msg_NE
12802                     ("pragma Pure_Function on& is redundant?",
12803                      N, Entity (E_Id));
12804                end if;
12805             end if;
12806          end Pure_Function;
12807
12808          --------------------
12809          -- Queuing_Policy --
12810          --------------------
12811
12812          --  pragma Queuing_Policy (policy_IDENTIFIER);
12813
12814          when Pragma_Queuing_Policy => declare
12815             QP : Character;
12816
12817          begin
12818             Check_Ada_83_Warning;
12819             Check_Arg_Count (1);
12820             Check_No_Identifiers;
12821             Check_Arg_Is_Queuing_Policy (Arg1);
12822             Check_Valid_Configuration_Pragma;
12823             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
12824             QP := Fold_Upper (Name_Buffer (1));
12825
12826             if Queuing_Policy /= ' '
12827               and then Queuing_Policy /= QP
12828             then
12829                Error_Msg_Sloc := Queuing_Policy_Sloc;
12830                Error_Pragma ("queuing policy incompatible with policy#");
12831
12832             --  Set new policy, but always preserve System_Location since we
12833             --  like the error message with the run time name.
12834
12835             else
12836                Queuing_Policy := QP;
12837
12838                if Queuing_Policy_Sloc /= System_Location then
12839                   Queuing_Policy_Sloc := Loc;
12840                end if;
12841             end if;
12842          end;
12843
12844          -----------------------
12845          -- Relative_Deadline --
12846          -----------------------
12847
12848          --  pragma Relative_Deadline (time_span_EXPRESSION);
12849
12850          when Pragma_Relative_Deadline => Relative_Deadline : declare
12851             P   : constant Node_Id := Parent (N);
12852             Arg : Node_Id;
12853
12854          begin
12855             Ada_2005_Pragma;
12856             Check_No_Identifiers;
12857             Check_Arg_Count (1);
12858
12859             Arg := Get_Pragma_Arg (Arg1);
12860
12861             --  The expression must be analyzed in the special manner described
12862             --  in "Handling of Default and Per-Object Expressions" in sem.ads.
12863
12864             Preanalyze_Spec_Expression (Arg, RTE (RE_Time_Span));
12865
12866             --  Subprogram case
12867
12868             if Nkind (P) = N_Subprogram_Body then
12869                Check_In_Main_Program;
12870
12871             --  Tasks
12872
12873             elsif Nkind (P) = N_Task_Definition then
12874                null;
12875
12876             --  Anything else is incorrect
12877
12878             else
12879                Pragma_Misplaced;
12880             end if;
12881
12882             if Has_Relative_Deadline_Pragma (P) then
12883                Error_Pragma ("duplicate pragma% not allowed");
12884             else
12885                Set_Has_Relative_Deadline_Pragma (P, True);
12886
12887                if Nkind (P) = N_Task_Definition then
12888                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
12889                end if;
12890             end if;
12891          end Relative_Deadline;
12892
12893          ------------------------
12894          -- Remote_Access_Type --
12895          ------------------------
12896
12897          --  pragma Remote_Access_Type ([Entity =>] formal_type_LOCAL_NAME);
12898
12899          when Pragma_Remote_Access_Type => Remote_Access_Type : declare
12900             E : Entity_Id;
12901
12902          begin
12903             GNAT_Pragma;
12904             Check_Arg_Count (1);
12905             Check_Optional_Identifier (Arg1, Name_Entity);
12906             Check_Arg_Is_Local_Name (Arg1);
12907
12908             E := Entity (Get_Pragma_Arg (Arg1));
12909
12910             if Nkind (Parent (E)) = N_Formal_Type_Declaration
12911               and then Ekind (E) = E_General_Access_Type
12912               and then Is_Class_Wide_Type (Directly_Designated_Type (E))
12913               and then Scope (Root_Type (Directly_Designated_Type (E)))
12914                          = Scope (E)
12915               and then Is_Valid_Remote_Object_Type
12916                          (Root_Type (Directly_Designated_Type (E)))
12917             then
12918                Set_Is_Remote_Types (E);
12919
12920             else
12921                Error_Pragma_Arg
12922                  ("pragma% applies only to formal access to classwide types",
12923                   Arg1);
12924             end if;
12925          end Remote_Access_Type;
12926
12927          ---------------------------
12928          -- Remote_Call_Interface --
12929          ---------------------------
12930
12931          --  pragma Remote_Call_Interface [(library_unit_NAME)];
12932
12933          when Pragma_Remote_Call_Interface => Remote_Call_Interface : declare
12934             Cunit_Node : Node_Id;
12935             Cunit_Ent  : Entity_Id;
12936             K          : Node_Kind;
12937
12938          begin
12939             Check_Ada_83_Warning;
12940             Check_Valid_Library_Unit_Pragma;
12941
12942             if Nkind (N) = N_Null_Statement then
12943                return;
12944             end if;
12945
12946             Cunit_Node := Cunit (Current_Sem_Unit);
12947             K          := Nkind (Unit (Cunit_Node));
12948             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12949
12950             if K = N_Package_Declaration
12951               or else K = N_Generic_Package_Declaration
12952               or else K = N_Subprogram_Declaration
12953               or else K = N_Generic_Subprogram_Declaration
12954               or else (K = N_Subprogram_Body
12955                          and then Acts_As_Spec (Unit (Cunit_Node)))
12956             then
12957                null;
12958             else
12959                Error_Pragma (
12960                  "pragma% must apply to package or subprogram declaration");
12961             end if;
12962
12963             Set_Is_Remote_Call_Interface (Cunit_Ent);
12964          end Remote_Call_Interface;
12965
12966          ------------------
12967          -- Remote_Types --
12968          ------------------
12969
12970          --  pragma Remote_Types [(library_unit_NAME)];
12971
12972          when Pragma_Remote_Types => Remote_Types : declare
12973             Cunit_Node : Node_Id;
12974             Cunit_Ent  : Entity_Id;
12975
12976          begin
12977             Check_Ada_83_Warning;
12978             Check_Valid_Library_Unit_Pragma;
12979
12980             if Nkind (N) = N_Null_Statement then
12981                return;
12982             end if;
12983
12984             Cunit_Node := Cunit (Current_Sem_Unit);
12985             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12986
12987             if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
12988                                                 N_Generic_Package_Declaration)
12989             then
12990                Error_Pragma
12991                  ("pragma% can only apply to a package declaration");
12992             end if;
12993
12994             Set_Is_Remote_Types (Cunit_Ent);
12995          end Remote_Types;
12996
12997          ---------------
12998          -- Ravenscar --
12999          ---------------
13000
13001          --  pragma Ravenscar;
13002
13003          when Pragma_Ravenscar =>
13004             GNAT_Pragma;
13005             Check_Arg_Count (0);
13006             Check_Valid_Configuration_Pragma;
13007             Set_Ravenscar_Profile (N);
13008
13009             if Warn_On_Obsolescent_Feature then
13010                Error_Msg_N ("pragma Ravenscar is an obsolescent feature?", N);
13011                Error_Msg_N ("|use pragma Profile (Ravenscar) instead", N);
13012             end if;
13013
13014          -------------------------
13015          -- Restricted_Run_Time --
13016          -------------------------
13017
13018          --  pragma Restricted_Run_Time;
13019
13020          when Pragma_Restricted_Run_Time =>
13021             GNAT_Pragma;
13022             Check_Arg_Count (0);
13023             Check_Valid_Configuration_Pragma;
13024             Set_Profile_Restrictions
13025               (Restricted, N, Warn => Treat_Restrictions_As_Warnings);
13026
13027             if Warn_On_Obsolescent_Feature then
13028                Error_Msg_N
13029                  ("pragma Restricted_Run_Time is an obsolescent feature?", N);
13030                Error_Msg_N ("|use pragma Profile (Restricted) instead", N);
13031             end if;
13032
13033          ------------------
13034          -- Restrictions --
13035          ------------------
13036
13037          --  pragma Restrictions (RESTRICTION {, RESTRICTION});
13038
13039          --  RESTRICTION ::=
13040          --    restriction_IDENTIFIER
13041          --  | restriction_parameter_IDENTIFIER => EXPRESSION
13042
13043          when Pragma_Restrictions =>
13044             Process_Restrictions_Or_Restriction_Warnings
13045               (Warn => Treat_Restrictions_As_Warnings);
13046
13047          --------------------------
13048          -- Restriction_Warnings --
13049          --------------------------
13050
13051          --  pragma Restriction_Warnings (RESTRICTION {, RESTRICTION});
13052
13053          --  RESTRICTION ::=
13054          --    restriction_IDENTIFIER
13055          --  | restriction_parameter_IDENTIFIER => EXPRESSION
13056
13057          when Pragma_Restriction_Warnings =>
13058             GNAT_Pragma;
13059             Process_Restrictions_Or_Restriction_Warnings (Warn => True);
13060
13061          ----------------
13062          -- Reviewable --
13063          ----------------
13064
13065          --  pragma Reviewable;
13066
13067          when Pragma_Reviewable =>
13068             Check_Ada_83_Warning;
13069             Check_Arg_Count (0);
13070
13071             --  Call dummy debugging function rv. This is done to assist front
13072             --  end debugging. By placing a Reviewable pragma in the source
13073             --  program, a breakpoint on rv catches this place in the source,
13074             --  allowing convenient stepping to the point of interest.
13075
13076             rv;
13077
13078          --------------------------
13079          -- Short_Circuit_And_Or --
13080          --------------------------
13081
13082          when Pragma_Short_Circuit_And_Or =>
13083             GNAT_Pragma;
13084             Check_Arg_Count (0);
13085             Check_Valid_Configuration_Pragma;
13086             Short_Circuit_And_Or := True;
13087
13088          -------------------
13089          -- Share_Generic --
13090          -------------------
13091
13092          --  pragma Share_Generic (NAME {, NAME});
13093
13094          when Pragma_Share_Generic =>
13095             GNAT_Pragma;
13096             Process_Generic_List;
13097
13098          ------------
13099          -- Shared --
13100          ------------
13101
13102          --  pragma Shared (LOCAL_NAME);
13103
13104          when Pragma_Shared =>
13105             GNAT_Pragma;
13106             Process_Atomic_Shared_Volatile;
13107
13108          --------------------
13109          -- Shared_Passive --
13110          --------------------
13111
13112          --  pragma Shared_Passive [(library_unit_NAME)];
13113
13114          --  Set the flag Is_Shared_Passive of program unit name entity
13115
13116          when Pragma_Shared_Passive => Shared_Passive : declare
13117             Cunit_Node : Node_Id;
13118             Cunit_Ent  : Entity_Id;
13119
13120          begin
13121             Check_Ada_83_Warning;
13122             Check_Valid_Library_Unit_Pragma;
13123
13124             if Nkind (N) = N_Null_Statement then
13125                return;
13126             end if;
13127
13128             Cunit_Node := Cunit (Current_Sem_Unit);
13129             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
13130
13131             if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
13132                                                 N_Generic_Package_Declaration)
13133             then
13134                Error_Pragma
13135                  ("pragma% can only apply to a package declaration");
13136             end if;
13137
13138             Set_Is_Shared_Passive (Cunit_Ent);
13139          end Shared_Passive;
13140
13141          -----------------------
13142          -- Short_Descriptors --
13143          -----------------------
13144
13145          --  pragma Short_Descriptors;
13146
13147          when Pragma_Short_Descriptors =>
13148             GNAT_Pragma;
13149             Check_Arg_Count (0);
13150             Check_Valid_Configuration_Pragma;
13151             Short_Descriptors := True;
13152
13153          ----------------------
13154          -- Source_File_Name --
13155          ----------------------
13156
13157          --  There are five forms for this pragma:
13158
13159          --  pragma Source_File_Name (
13160          --    [UNIT_NAME      =>] unit_NAME,
13161          --     BODY_FILE_NAME =>  STRING_LITERAL
13162          --    [, [INDEX =>] INTEGER_LITERAL]);
13163
13164          --  pragma Source_File_Name (
13165          --    [UNIT_NAME      =>] unit_NAME,
13166          --     SPEC_FILE_NAME =>  STRING_LITERAL
13167          --    [, [INDEX =>] INTEGER_LITERAL]);
13168
13169          --  pragma Source_File_Name (
13170          --     BODY_FILE_NAME  => STRING_LITERAL
13171          --  [, DOT_REPLACEMENT => STRING_LITERAL]
13172          --  [, CASING          => CASING_SPEC]);
13173
13174          --  pragma Source_File_Name (
13175          --     SPEC_FILE_NAME  => STRING_LITERAL
13176          --  [, DOT_REPLACEMENT => STRING_LITERAL]
13177          --  [, CASING          => CASING_SPEC]);
13178
13179          --  pragma Source_File_Name (
13180          --     SUBUNIT_FILE_NAME  => STRING_LITERAL
13181          --  [, DOT_REPLACEMENT    => STRING_LITERAL]
13182          --  [, CASING             => CASING_SPEC]);
13183
13184          --  CASING_SPEC ::= Uppercase | Lowercase | Mixedcase
13185
13186          --  Pragma Source_File_Name_Project (SFNP) is equivalent to pragma
13187          --  Source_File_Name (SFN), however their usage is exclusive: SFN can
13188          --  only be used when no project file is used, while SFNP can only be
13189          --  used when a project file is used.
13190
13191          --  No processing here. Processing was completed during parsing, since
13192          --  we need to have file names set as early as possible. Units are
13193          --  loaded well before semantic processing starts.
13194
13195          --  The only processing we defer to this point is the check for
13196          --  correct placement.
13197
13198          when Pragma_Source_File_Name =>
13199             GNAT_Pragma;
13200             Check_Valid_Configuration_Pragma;
13201
13202          ------------------------------
13203          -- Source_File_Name_Project --
13204          ------------------------------
13205
13206          --  See Source_File_Name for syntax
13207
13208          --  No processing here. Processing was completed during parsing, since
13209          --  we need to have file names set as early as possible. Units are
13210          --  loaded well before semantic processing starts.
13211
13212          --  The only processing we defer to this point is the check for
13213          --  correct placement.
13214
13215          when Pragma_Source_File_Name_Project =>
13216             GNAT_Pragma;
13217             Check_Valid_Configuration_Pragma;
13218
13219             --  Check that a pragma Source_File_Name_Project is used only in a
13220             --  configuration pragmas file.
13221
13222             --  Pragmas Source_File_Name_Project should only be generated by
13223             --  the Project Manager in configuration pragmas files.
13224
13225             --  This is really an ugly test. It seems to depend on some
13226             --  accidental and undocumented property. At the very least it
13227             --  needs to be documented, but it would be better to have a
13228             --  clean way of testing if we are in a configuration file???
13229
13230             if Present (Parent (N)) then
13231                Error_Pragma
13232                  ("pragma% can only appear in a configuration pragmas file");
13233             end if;
13234
13235          ----------------------
13236          -- Source_Reference --
13237          ----------------------
13238
13239          --  pragma Source_Reference (INTEGER_LITERAL [, STRING_LITERAL]);
13240
13241          --  Nothing to do, all processing completed in Par.Prag, since we need
13242          --  the information for possible parser messages that are output.
13243
13244          when Pragma_Source_Reference =>
13245             GNAT_Pragma;
13246
13247          --------------------------------
13248          -- Static_Elaboration_Desired --
13249          --------------------------------
13250
13251          --  pragma Static_Elaboration_Desired (DIRECT_NAME);
13252
13253          when Pragma_Static_Elaboration_Desired =>
13254             GNAT_Pragma;
13255             Check_At_Most_N_Arguments (1);
13256
13257             if Is_Compilation_Unit (Current_Scope)
13258               and then Ekind (Current_Scope) = E_Package
13259             then
13260                Set_Static_Elaboration_Desired (Current_Scope, True);
13261             else
13262                Error_Pragma ("pragma% must apply to a library-level package");
13263             end if;
13264
13265          ------------------
13266          -- Storage_Size --
13267          ------------------
13268
13269          --  pragma Storage_Size (EXPRESSION);
13270
13271          when Pragma_Storage_Size => Storage_Size : declare
13272             P   : constant Node_Id := Parent (N);
13273             Arg : Node_Id;
13274
13275          begin
13276             Check_No_Identifiers;
13277             Check_Arg_Count (1);
13278
13279             --  The expression must be analyzed in the special manner described
13280             --  in "Handling of Default Expressions" in sem.ads.
13281
13282             Arg := Get_Pragma_Arg (Arg1);
13283             Preanalyze_Spec_Expression (Arg, Any_Integer);
13284
13285             if not Is_Static_Expression (Arg) then
13286                Check_Restriction (Static_Storage_Size, Arg);
13287             end if;
13288
13289             if Nkind (P) /= N_Task_Definition then
13290                Pragma_Misplaced;
13291                return;
13292
13293             else
13294                if Has_Storage_Size_Pragma (P) then
13295                   Error_Pragma ("duplicate pragma% not allowed");
13296                else
13297                   Set_Has_Storage_Size_Pragma (P, True);
13298                end if;
13299
13300                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
13301                --  ???  exp_ch9 should use this!
13302             end if;
13303          end Storage_Size;
13304
13305          ------------------
13306          -- Storage_Unit --
13307          ------------------
13308
13309          --  pragma Storage_Unit (NUMERIC_LITERAL);
13310
13311          --  Only permitted argument is System'Storage_Unit value
13312
13313          when Pragma_Storage_Unit =>
13314             Check_No_Identifiers;
13315             Check_Arg_Count (1);
13316             Check_Arg_Is_Integer_Literal (Arg1);
13317
13318             if Intval (Get_Pragma_Arg (Arg1)) /=
13319               UI_From_Int (Ttypes.System_Storage_Unit)
13320             then
13321                Error_Msg_Uint_1 := UI_From_Int (Ttypes.System_Storage_Unit);
13322                Error_Pragma_Arg
13323                  ("the only allowed argument for pragma% is ^", Arg1);
13324             end if;
13325
13326          --------------------
13327          -- Stream_Convert --
13328          --------------------
13329
13330          --  pragma Stream_Convert (
13331          --    [Entity =>] type_LOCAL_NAME,
13332          --    [Read   =>] function_NAME,
13333          --    [Write  =>] function NAME);
13334
13335          when Pragma_Stream_Convert => Stream_Convert : declare
13336
13337             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id);
13338             --  Check that the given argument is the name of a local function
13339             --  of one argument that is not overloaded earlier in the current
13340             --  local scope. A check is also made that the argument is a
13341             --  function with one parameter.
13342
13343             --------------------------------------
13344             -- Check_OK_Stream_Convert_Function --
13345             --------------------------------------
13346
13347             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id) is
13348                Ent : Entity_Id;
13349
13350             begin
13351                Check_Arg_Is_Local_Name (Arg);
13352                Ent := Entity (Get_Pragma_Arg (Arg));
13353
13354                if Has_Homonym (Ent) then
13355                   Error_Pragma_Arg
13356                     ("argument for pragma% may not be overloaded", Arg);
13357                end if;
13358
13359                if Ekind (Ent) /= E_Function
13360                  or else No (First_Formal (Ent))
13361                  or else Present (Next_Formal (First_Formal (Ent)))
13362                then
13363                   Error_Pragma_Arg
13364                     ("argument for pragma% must be" &
13365                      " function of one argument", Arg);
13366                end if;
13367             end Check_OK_Stream_Convert_Function;
13368
13369          --  Start of processing for Stream_Convert
13370
13371          begin
13372             GNAT_Pragma;
13373             Check_Arg_Order ((Name_Entity, Name_Read, Name_Write));
13374             Check_Arg_Count (3);
13375             Check_Optional_Identifier (Arg1, Name_Entity);
13376             Check_Optional_Identifier (Arg2, Name_Read);
13377             Check_Optional_Identifier (Arg3, Name_Write);
13378             Check_Arg_Is_Local_Name (Arg1);
13379             Check_OK_Stream_Convert_Function (Arg2);
13380             Check_OK_Stream_Convert_Function (Arg3);
13381
13382             declare
13383                Typ   : constant Entity_Id :=
13384                          Underlying_Type (Entity (Get_Pragma_Arg (Arg1)));
13385                Read  : constant Entity_Id := Entity (Get_Pragma_Arg (Arg2));
13386                Write : constant Entity_Id := Entity (Get_Pragma_Arg (Arg3));
13387
13388             begin
13389                Check_First_Subtype (Arg1);
13390
13391                --  Check for too early or too late. Note that we don't enforce
13392                --  the rule about primitive operations in this case, since, as
13393                --  is the case for explicit stream attributes themselves, these
13394                --  restrictions are not appropriate. Note that the chaining of
13395                --  the pragma by Rep_Item_Too_Late is actually the critical
13396                --  processing done for this pragma.
13397
13398                if Rep_Item_Too_Early (Typ, N)
13399                     or else
13400                   Rep_Item_Too_Late (Typ, N, FOnly => True)
13401                then
13402                   return;
13403                end if;
13404
13405                --  Return if previous error
13406
13407                if Etype (Typ) = Any_Type
13408                     or else
13409                   Etype (Read) = Any_Type
13410                     or else
13411                   Etype (Write) = Any_Type
13412                then
13413                   return;
13414                end if;
13415
13416                --  Error checks
13417
13418                if Underlying_Type (Etype (Read)) /= Typ then
13419                   Error_Pragma_Arg
13420                     ("incorrect return type for function&", Arg2);
13421                end if;
13422
13423                if Underlying_Type (Etype (First_Formal (Write))) /= Typ then
13424                   Error_Pragma_Arg
13425                     ("incorrect parameter type for function&", Arg3);
13426                end if;
13427
13428                if Underlying_Type (Etype (First_Formal (Read))) /=
13429                   Underlying_Type (Etype (Write))
13430                then
13431                   Error_Pragma_Arg
13432                     ("result type of & does not match Read parameter type",
13433                      Arg3);
13434                end if;
13435             end;
13436          end Stream_Convert;
13437
13438          -------------------------
13439          -- Style_Checks (GNAT) --
13440          -------------------------
13441
13442          --  pragma Style_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
13443
13444          --  This is processed by the parser since some of the style checks
13445          --  take place during source scanning and parsing. This means that
13446          --  we don't need to issue error messages here.
13447
13448          when Pragma_Style_Checks => Style_Checks : declare
13449             A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
13450             S  : String_Id;
13451             C  : Char_Code;
13452
13453          begin
13454             GNAT_Pragma;
13455             Check_No_Identifiers;
13456
13457             --  Two argument form
13458
13459             if Arg_Count = 2 then
13460                Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
13461
13462                declare
13463                   E_Id : Node_Id;
13464                   E    : Entity_Id;
13465
13466                begin
13467                   E_Id := Get_Pragma_Arg (Arg2);
13468                   Analyze (E_Id);
13469
13470                   if not Is_Entity_Name (E_Id) then
13471                      Error_Pragma_Arg
13472                        ("second argument of pragma% must be entity name",
13473                         Arg2);
13474                   end if;
13475
13476                   E := Entity (E_Id);
13477
13478                   if E = Any_Id then
13479                      return;
13480                   else
13481                      loop
13482                         Set_Suppress_Style_Checks (E,
13483                           (Chars (Get_Pragma_Arg (Arg1)) = Name_Off));
13484                         exit when No (Homonym (E));
13485                         E := Homonym (E);
13486                      end loop;
13487                   end if;
13488                end;
13489
13490             --  One argument form
13491
13492             else
13493                Check_Arg_Count (1);
13494
13495                if Nkind (A) = N_String_Literal then
13496                   S   := Strval (A);
13497
13498                   declare
13499                      Slen    : constant Natural := Natural (String_Length (S));
13500                      Options : String (1 .. Slen);
13501                      J       : Natural;
13502
13503                   begin
13504                      J := 1;
13505                      loop
13506                         C := Get_String_Char (S, Int (J));
13507                         exit when not In_Character_Range (C);
13508                         Options (J) := Get_Character (C);
13509
13510                         --  If at end of string, set options. As per discussion
13511                         --  above, no need to check for errors, since we issued
13512                         --  them in the parser.
13513
13514                         if J = Slen then
13515                            Set_Style_Check_Options (Options);
13516                            exit;
13517                         end if;
13518
13519                         J := J + 1;
13520                      end loop;
13521                   end;
13522
13523                elsif Nkind (A) = N_Identifier then
13524                   if Chars (A) = Name_All_Checks then
13525                      if GNAT_Mode then
13526                         Set_GNAT_Style_Check_Options;
13527                      else
13528                         Set_Default_Style_Check_Options;
13529                      end if;
13530
13531                   elsif Chars (A) = Name_On then
13532                      Style_Check := True;
13533
13534                   elsif Chars (A) = Name_Off then
13535                      Style_Check := False;
13536                   end if;
13537                end if;
13538             end if;
13539          end Style_Checks;
13540
13541          --------------
13542          -- Subtitle --
13543          --------------
13544
13545          --  pragma Subtitle ([Subtitle =>] STRING_LITERAL);
13546
13547          when Pragma_Subtitle =>
13548             GNAT_Pragma;
13549             Check_Arg_Count (1);
13550             Check_Optional_Identifier (Arg1, Name_Subtitle);
13551             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
13552             Store_Note (N);
13553
13554          --------------
13555          -- Suppress --
13556          --------------
13557
13558          --  pragma Suppress (IDENTIFIER [, [On =>] NAME]);
13559
13560          when Pragma_Suppress =>
13561             Process_Suppress_Unsuppress (True);
13562
13563          ------------------
13564          -- Suppress_All --
13565          ------------------
13566
13567          --  pragma Suppress_All;
13568
13569          --  The only check made here is that the pragma has no arguments.
13570          --  There are no placement rules, and the processing required (setting
13571          --  the Has_Pragma_Suppress_All flag in the compilation unit node was
13572          --  taken care of by the parser). Process_Compilation_Unit_Pragmas
13573          --  then creates and inserts a pragma Suppress (All_Checks).
13574
13575          when Pragma_Suppress_All =>
13576             GNAT_Pragma;
13577             Check_Arg_Count (0);
13578
13579          -------------------------
13580          -- Suppress_Debug_Info --
13581          -------------------------
13582
13583          --  pragma Suppress_Debug_Info ([Entity =>] LOCAL_NAME);
13584
13585          when Pragma_Suppress_Debug_Info =>
13586             GNAT_Pragma;
13587             Check_Arg_Count (1);
13588             Check_Optional_Identifier (Arg1, Name_Entity);
13589             Check_Arg_Is_Local_Name (Arg1);
13590             Set_Debug_Info_Off (Entity (Get_Pragma_Arg (Arg1)));
13591
13592          ----------------------------------
13593          -- Suppress_Exception_Locations --
13594          ----------------------------------
13595
13596          --  pragma Suppress_Exception_Locations;
13597
13598          when Pragma_Suppress_Exception_Locations =>
13599             GNAT_Pragma;
13600             Check_Arg_Count (0);
13601             Check_Valid_Configuration_Pragma;
13602             Exception_Locations_Suppressed := True;
13603
13604          -----------------------------
13605          -- Suppress_Initialization --
13606          -----------------------------
13607
13608          --  pragma Suppress_Initialization ([Entity =>] type_Name);
13609
13610          when Pragma_Suppress_Initialization => Suppress_Init : declare
13611             E_Id : Node_Id;
13612             E    : Entity_Id;
13613
13614          begin
13615             GNAT_Pragma;
13616             Check_Arg_Count (1);
13617             Check_Optional_Identifier (Arg1, Name_Entity);
13618             Check_Arg_Is_Local_Name (Arg1);
13619
13620             E_Id := Get_Pragma_Arg (Arg1);
13621
13622             if Etype (E_Id) = Any_Type then
13623                return;
13624             end if;
13625
13626             E := Entity (E_Id);
13627
13628             if not Is_Type (E) then
13629                Error_Pragma_Arg ("pragma% requires type or subtype", Arg1);
13630             end if;
13631
13632             if Rep_Item_Too_Early (E, N)
13633                  or else
13634                Rep_Item_Too_Late (E, N, FOnly => True)
13635             then
13636                return;
13637             end if;
13638
13639             --  For incomplete/private type, set flag on full view
13640
13641             if Is_Incomplete_Or_Private_Type (E) then
13642                if No (Full_View (Base_Type (E))) then
13643                   Error_Pragma_Arg
13644                     ("argument of pragma% cannot be an incomplete type", Arg1);
13645                else
13646                   Set_Suppress_Initialization (Full_View (Base_Type (E)));
13647                end if;
13648
13649             --  For first subtype, set flag on base type
13650
13651             elsif Is_First_Subtype (E) then
13652                Set_Suppress_Initialization (Base_Type (E));
13653
13654             --  For other than first subtype, set flag on subtype itself
13655
13656             else
13657                Set_Suppress_Initialization (E);
13658             end if;
13659          end Suppress_Init;
13660
13661          -----------------
13662          -- System_Name --
13663          -----------------
13664
13665          --  pragma System_Name (DIRECT_NAME);
13666
13667          --  Syntax check: one argument, which must be the identifier GNAT or
13668          --  the identifier GCC, no other identifiers are acceptable.
13669
13670          when Pragma_System_Name =>
13671             GNAT_Pragma;
13672             Check_No_Identifiers;
13673             Check_Arg_Count (1);
13674             Check_Arg_Is_One_Of (Arg1, Name_Gcc, Name_Gnat);
13675
13676          -----------------------------
13677          -- Task_Dispatching_Policy --
13678          -----------------------------
13679
13680          --  pragma Task_Dispatching_Policy (policy_IDENTIFIER);
13681
13682          when Pragma_Task_Dispatching_Policy => declare
13683             DP : Character;
13684
13685          begin
13686             Check_Ada_83_Warning;
13687             Check_Arg_Count (1);
13688             Check_No_Identifiers;
13689             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
13690             Check_Valid_Configuration_Pragma;
13691             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
13692             DP := Fold_Upper (Name_Buffer (1));
13693
13694             if Task_Dispatching_Policy /= ' '
13695               and then Task_Dispatching_Policy /= DP
13696             then
13697                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
13698                Error_Pragma
13699                  ("task dispatching policy incompatible with policy#");
13700
13701             --  Set new policy, but always preserve System_Location since we
13702             --  like the error message with the run time name.
13703
13704             else
13705                Task_Dispatching_Policy := DP;
13706
13707                if Task_Dispatching_Policy_Sloc /= System_Location then
13708                   Task_Dispatching_Policy_Sloc := Loc;
13709                end if;
13710             end if;
13711          end;
13712
13713          ---------------
13714          -- Task_Info --
13715          ---------------
13716
13717          --  pragma Task_Info (EXPRESSION);
13718
13719          when Pragma_Task_Info => Task_Info : declare
13720             P : constant Node_Id := Parent (N);
13721
13722          begin
13723             GNAT_Pragma;
13724
13725             if Nkind (P) /= N_Task_Definition then
13726                Error_Pragma ("pragma% must appear in task definition");
13727             end if;
13728
13729             Check_No_Identifiers;
13730             Check_Arg_Count (1);
13731
13732             Analyze_And_Resolve
13733               (Get_Pragma_Arg (Arg1), RTE (RE_Task_Info_Type));
13734
13735             if Etype (Get_Pragma_Arg (Arg1)) = Any_Type then
13736                return;
13737             end if;
13738
13739             if Has_Task_Info_Pragma (P) then
13740                Error_Pragma ("duplicate pragma% not allowed");
13741             else
13742                Set_Has_Task_Info_Pragma (P, True);
13743             end if;
13744          end Task_Info;
13745
13746          ---------------
13747          -- Task_Name --
13748          ---------------
13749
13750          --  pragma Task_Name (string_EXPRESSION);
13751
13752          when Pragma_Task_Name => Task_Name : declare
13753             P   : constant Node_Id := Parent (N);
13754             Arg : Node_Id;
13755
13756          begin
13757             Check_No_Identifiers;
13758             Check_Arg_Count (1);
13759
13760             Arg := Get_Pragma_Arg (Arg1);
13761
13762             --  The expression is used in the call to Create_Task, and must be
13763             --  expanded there, not in the context of the current spec. It must
13764             --  however be analyzed to capture global references, in case it
13765             --  appears in a generic context.
13766
13767             Preanalyze_And_Resolve (Arg, Standard_String);
13768
13769             if Nkind (P) /= N_Task_Definition then
13770                Pragma_Misplaced;
13771             end if;
13772
13773             if Has_Task_Name_Pragma (P) then
13774                Error_Pragma ("duplicate pragma% not allowed");
13775             else
13776                Set_Has_Task_Name_Pragma (P, True);
13777                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
13778             end if;
13779          end Task_Name;
13780
13781          ------------------
13782          -- Task_Storage --
13783          ------------------
13784
13785          --  pragma Task_Storage (
13786          --     [Task_Type =>] LOCAL_NAME,
13787          --     [Top_Guard =>] static_integer_EXPRESSION);
13788
13789          when Pragma_Task_Storage => Task_Storage : declare
13790             Args  : Args_List (1 .. 2);
13791             Names : constant Name_List (1 .. 2) := (
13792                       Name_Task_Type,
13793                       Name_Top_Guard);
13794
13795             Task_Type : Node_Id renames Args (1);
13796             Top_Guard : Node_Id renames Args (2);
13797
13798             Ent : Entity_Id;
13799
13800          begin
13801             GNAT_Pragma;
13802             Gather_Associations (Names, Args);
13803
13804             if No (Task_Type) then
13805                Error_Pragma
13806                  ("missing task_type argument for pragma%");
13807             end if;
13808
13809             Check_Arg_Is_Local_Name (Task_Type);
13810
13811             Ent := Entity (Task_Type);
13812
13813             if not Is_Task_Type (Ent) then
13814                Error_Pragma_Arg
13815                  ("argument for pragma% must be task type", Task_Type);
13816             end if;
13817
13818             if No (Top_Guard) then
13819                Error_Pragma_Arg
13820                  ("pragma% takes two arguments", Task_Type);
13821             else
13822                Check_Arg_Is_Static_Expression (Top_Guard, Any_Integer);
13823             end if;
13824
13825             Check_First_Subtype (Task_Type);
13826
13827             if Rep_Item_Too_Late (Ent, N) then
13828                raise Pragma_Exit;
13829             end if;
13830          end Task_Storage;
13831
13832          ---------------
13833          -- Test_Case --
13834          ---------------
13835
13836          --  pragma Test_Case ([Name     =>] Static_String_EXPRESSION
13837          --                   ,[Mode     =>] MODE_TYPE
13838          --                  [, Requires =>  Boolean_EXPRESSION]
13839          --                  [, Ensures  =>  Boolean_EXPRESSION]);
13840
13841          --  MODE_TYPE ::= Nominal | Robustness
13842
13843          when Pragma_Test_Case => Test_Case : declare
13844          begin
13845             GNAT_Pragma;
13846             Check_At_Least_N_Arguments (2);
13847             Check_At_Most_N_Arguments (4);
13848             Check_Arg_Order
13849                  ((Name_Name, Name_Mode, Name_Requires, Name_Ensures));
13850
13851             Check_Optional_Identifier (Arg1, Name_Name);
13852             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
13853
13854             --  In ASIS mode, for a pragma generated from a source aspect, also
13855             --  analyze the original aspect expression.
13856
13857             if ASIS_Mode
13858               and then Present (Corresponding_Aspect (N))
13859             then
13860                Check_Expr_Is_Static_Expression
13861                  (Original_Node (Get_Pragma_Arg (Arg1)), Standard_String);
13862             end if;
13863
13864             Check_Optional_Identifier (Arg2, Name_Mode);
13865             Check_Arg_Is_One_Of (Arg2, Name_Nominal, Name_Robustness);
13866
13867             if Arg_Count = 4 then
13868                Check_Identifier (Arg3, Name_Requires);
13869                Check_Identifier (Arg4, Name_Ensures);
13870
13871             elsif Arg_Count = 3 then
13872                Check_Identifier_Is_One_Of (Arg3, Name_Requires, Name_Ensures);
13873             end if;
13874
13875             Check_Test_Case;
13876          end Test_Case;
13877
13878          --------------------------
13879          -- Thread_Local_Storage --
13880          --------------------------
13881
13882          --  pragma Thread_Local_Storage ([Entity =>] LOCAL_NAME);
13883
13884          when Pragma_Thread_Local_Storage => Thread_Local_Storage : declare
13885             Id : Node_Id;
13886             E  : Entity_Id;
13887
13888          begin
13889             GNAT_Pragma;
13890             Check_Arg_Count (1);
13891             Check_Optional_Identifier (Arg1, Name_Entity);
13892             Check_Arg_Is_Library_Level_Local_Name (Arg1);
13893
13894             Id := Get_Pragma_Arg (Arg1);
13895             Analyze (Id);
13896
13897             if not Is_Entity_Name (Id)
13898               or else Ekind (Entity (Id)) /= E_Variable
13899             then
13900                Error_Pragma_Arg ("local variable name required", Arg1);
13901             end if;
13902
13903             E := Entity (Id);
13904
13905             if Rep_Item_Too_Early (E, N)
13906               or else Rep_Item_Too_Late (E, N)
13907             then
13908                raise Pragma_Exit;
13909             end if;
13910
13911             Set_Has_Pragma_Thread_Local_Storage (E);
13912             Set_Has_Gigi_Rep_Item (E);
13913          end Thread_Local_Storage;
13914
13915          ----------------
13916          -- Time_Slice --
13917          ----------------
13918
13919          --  pragma Time_Slice (static_duration_EXPRESSION);
13920
13921          when Pragma_Time_Slice => Time_Slice : declare
13922             Val : Ureal;
13923             Nod : Node_Id;
13924
13925          begin
13926             GNAT_Pragma;
13927             Check_Arg_Count (1);
13928             Check_No_Identifiers;
13929             Check_In_Main_Program;
13930             Check_Arg_Is_Static_Expression (Arg1, Standard_Duration);
13931
13932             if not Error_Posted (Arg1) then
13933                Nod := Next (N);
13934                while Present (Nod) loop
13935                   if Nkind (Nod) = N_Pragma
13936                     and then Pragma_Name (Nod) = Name_Time_Slice
13937                   then
13938                      Error_Msg_Name_1 := Pname;
13939                      Error_Msg_N ("duplicate pragma% not permitted", Nod);
13940                   end if;
13941
13942                   Next (Nod);
13943                end loop;
13944             end if;
13945
13946             --  Process only if in main unit
13947
13948             if Get_Source_Unit (Loc) = Main_Unit then
13949                Opt.Time_Slice_Set := True;
13950                Val := Expr_Value_R (Get_Pragma_Arg (Arg1));
13951
13952                if Val <= Ureal_0 then
13953                   Opt.Time_Slice_Value := 0;
13954
13955                elsif Val > UR_From_Uint (UI_From_Int (1000)) then
13956                   Opt.Time_Slice_Value := 1_000_000_000;
13957
13958                else
13959                   Opt.Time_Slice_Value :=
13960                     UI_To_Int (UR_To_Uint (Val * UI_From_Int (1_000_000)));
13961                end if;
13962             end if;
13963          end Time_Slice;
13964
13965          -----------
13966          -- Title --
13967          -----------
13968
13969          --  pragma Title (TITLING_OPTION [, TITLING OPTION]);
13970
13971          --   TITLING_OPTION ::=
13972          --     [Title =>] STRING_LITERAL
13973          --   | [Subtitle =>] STRING_LITERAL
13974
13975          when Pragma_Title => Title : declare
13976             Args  : Args_List (1 .. 2);
13977             Names : constant Name_List (1 .. 2) := (
13978                       Name_Title,
13979                       Name_Subtitle);
13980
13981          begin
13982             GNAT_Pragma;
13983             Gather_Associations (Names, Args);
13984             Store_Note (N);
13985
13986             for J in 1 .. 2 loop
13987                if Present (Args (J)) then
13988                   Check_Arg_Is_Static_Expression (Args (J), Standard_String);
13989                end if;
13990             end loop;
13991          end Title;
13992
13993          ---------------------
13994          -- Unchecked_Union --
13995          ---------------------
13996
13997          --  pragma Unchecked_Union (first_subtype_LOCAL_NAME)
13998
13999          when Pragma_Unchecked_Union => Unchecked_Union : declare
14000             Assoc   : constant Node_Id := Arg1;
14001             Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
14002             Typ     : Entity_Id;
14003             Discr   : Entity_Id;
14004             Tdef    : Node_Id;
14005             Clist   : Node_Id;
14006             Vpart   : Node_Id;
14007             Comp    : Node_Id;
14008             Variant : Node_Id;
14009
14010          begin
14011             Ada_2005_Pragma;
14012             Check_No_Identifiers;
14013             Check_Arg_Count (1);
14014             Check_Arg_Is_Local_Name (Arg1);
14015
14016             Find_Type (Type_Id);
14017             Typ := Entity (Type_Id);
14018
14019             if Typ = Any_Type
14020               or else Rep_Item_Too_Early (Typ, N)
14021             then
14022                return;
14023             else
14024                Typ := Underlying_Type (Typ);
14025             end if;
14026
14027             if Rep_Item_Too_Late (Typ, N) then
14028                return;
14029             end if;
14030
14031             Check_First_Subtype (Arg1);
14032
14033             --  Note remaining cases are references to a type in the current
14034             --  declarative part. If we find an error, we post the error on
14035             --  the relevant type declaration at an appropriate point.
14036
14037             if not Is_Record_Type (Typ) then
14038                Error_Msg_N ("Unchecked_Union must be record type", Typ);
14039                return;
14040
14041             elsif Is_Tagged_Type (Typ) then
14042                Error_Msg_N ("Unchecked_Union must not be tagged", Typ);
14043                return;
14044
14045             elsif not Has_Discriminants (Typ) then
14046                Error_Msg_N
14047                 ("Unchecked_Union must have one discriminant", Typ);
14048                return;
14049
14050             --  Note: in previous versions of GNAT we used to check for limited
14051             --  types and give an error, but in fact the standard does allow
14052             --  Unchecked_Union on limited types, so this check was removed.
14053
14054             --  Proceed with basic error checks completed
14055
14056             else
14057                Discr := First_Discriminant (Typ);
14058                while Present (Discr) loop
14059                   if No (Discriminant_Default_Value (Discr)) then
14060                      Error_Msg_N
14061                        ("Unchecked_Union discriminant must have default value",
14062                         Discr);
14063                   end if;
14064
14065                   Next_Discriminant (Discr);
14066                end loop;
14067
14068                Tdef  := Type_Definition (Declaration_Node (Typ));
14069                Clist := Component_List (Tdef);
14070
14071                Comp := First (Component_Items (Clist));
14072                while Present (Comp) loop
14073                   Check_Component (Comp, Typ);
14074                   Next (Comp);
14075                end loop;
14076
14077                if No (Clist) or else No (Variant_Part (Clist)) then
14078                   Error_Msg_N
14079                     ("Unchecked_Union must have variant part",
14080                      Tdef);
14081                   return;
14082                end if;
14083
14084                Vpart := Variant_Part (Clist);
14085
14086                Variant := First (Variants (Vpart));
14087                while Present (Variant) loop
14088                   Check_Variant (Variant, Typ);
14089                   Next (Variant);
14090                end loop;
14091             end if;
14092
14093             Set_Is_Unchecked_Union  (Typ);
14094             Set_Convention (Typ, Convention_C);
14095             Set_Has_Unchecked_Union (Base_Type (Typ));
14096             Set_Is_Unchecked_Union  (Base_Type (Typ));
14097          end Unchecked_Union;
14098
14099          ------------------------
14100          -- Unimplemented_Unit --
14101          ------------------------
14102
14103          --  pragma Unimplemented_Unit;
14104
14105          --  Note: this only gives an error if we are generating code, or if
14106          --  we are in a generic library unit (where the pragma appears in the
14107          --  body, not in the spec).
14108
14109          when Pragma_Unimplemented_Unit => Unimplemented_Unit : declare
14110             Cunitent : constant Entity_Id :=
14111                          Cunit_Entity (Get_Source_Unit (Loc));
14112             Ent_Kind : constant Entity_Kind :=
14113                          Ekind (Cunitent);
14114
14115          begin
14116             GNAT_Pragma;
14117             Check_Arg_Count (0);
14118
14119             if Operating_Mode = Generate_Code
14120               or else Ent_Kind = E_Generic_Function
14121               or else Ent_Kind = E_Generic_Procedure
14122               or else Ent_Kind = E_Generic_Package
14123             then
14124                Get_Name_String (Chars (Cunitent));
14125                Set_Casing (Mixed_Case);
14126                Write_Str (Name_Buffer (1 .. Name_Len));
14127                Write_Str (" is not supported in this configuration");
14128                Write_Eol;
14129                raise Unrecoverable_Error;
14130             end if;
14131          end Unimplemented_Unit;
14132
14133          ------------------------
14134          -- Universal_Aliasing --
14135          ------------------------
14136
14137          --  pragma Universal_Aliasing [([Entity =>] type_LOCAL_NAME)];
14138
14139          when Pragma_Universal_Aliasing => Universal_Alias : declare
14140             E_Id : Entity_Id;
14141
14142          begin
14143             GNAT_Pragma;
14144             Check_Arg_Count (1);
14145             Check_Optional_Identifier (Arg2, Name_Entity);
14146             Check_Arg_Is_Local_Name (Arg1);
14147             E_Id := Entity (Get_Pragma_Arg (Arg1));
14148
14149             if E_Id = Any_Type then
14150                return;
14151             elsif No (E_Id) or else not Is_Type (E_Id) then
14152                Error_Pragma_Arg ("pragma% requires type", Arg1);
14153             end if;
14154
14155             Set_Universal_Aliasing (Implementation_Base_Type (E_Id));
14156          end Universal_Alias;
14157
14158          --------------------
14159          -- Universal_Data --
14160          --------------------
14161
14162          --  pragma Universal_Data [(library_unit_NAME)];
14163
14164          when Pragma_Universal_Data =>
14165             GNAT_Pragma;
14166
14167             --  If this is a configuration pragma, then set the universal
14168             --  addressing option, otherwise confirm that the pragma satisfies
14169             --  the requirements of library unit pragma placement and leave it
14170             --  to the GNAAMP back end to detect the pragma (avoids transitive
14171             --  setting of the option due to withed units).
14172
14173             if Is_Configuration_Pragma then
14174                Universal_Addressing_On_AAMP := True;
14175             else
14176                Check_Valid_Library_Unit_Pragma;
14177             end if;
14178
14179             if not AAMP_On_Target then
14180                Error_Pragma ("?pragma% ignored (applies only to AAMP)");
14181             end if;
14182
14183          ----------------
14184          -- Unmodified --
14185          ----------------
14186
14187          --  pragma Unmodified (local_Name {, local_Name});
14188
14189          when Pragma_Unmodified => Unmodified : declare
14190             Arg_Node : Node_Id;
14191             Arg_Expr : Node_Id;
14192             Arg_Ent  : Entity_Id;
14193
14194          begin
14195             GNAT_Pragma;
14196             Check_At_Least_N_Arguments (1);
14197
14198             --  Loop through arguments
14199
14200             Arg_Node := Arg1;
14201             while Present (Arg_Node) loop
14202                Check_No_Identifier (Arg_Node);
14203
14204                --  Note: the analyze call done by Check_Arg_Is_Local_Name will
14205                --  in fact generate reference, so that the entity will have a
14206                --  reference, which will inhibit any warnings about it not
14207                --  being referenced, and also properly show up in the ali file
14208                --  as a reference. But this reference is recorded before the
14209                --  Has_Pragma_Unreferenced flag is set, so that no warning is
14210                --  generated for this reference.
14211
14212                Check_Arg_Is_Local_Name (Arg_Node);
14213                Arg_Expr := Get_Pragma_Arg (Arg_Node);
14214
14215                if Is_Entity_Name (Arg_Expr) then
14216                   Arg_Ent := Entity (Arg_Expr);
14217
14218                   if not Is_Assignable (Arg_Ent) then
14219                      Error_Pragma_Arg
14220                        ("pragma% can only be applied to a variable",
14221                         Arg_Expr);
14222                   else
14223                      Set_Has_Pragma_Unmodified (Arg_Ent);
14224                   end if;
14225                end if;
14226
14227                Next (Arg_Node);
14228             end loop;
14229          end Unmodified;
14230
14231          ------------------
14232          -- Unreferenced --
14233          ------------------
14234
14235          --  pragma Unreferenced (local_Name {, local_Name});
14236
14237          --    or when used in a context clause:
14238
14239          --  pragma Unreferenced (library_unit_NAME {, library_unit_NAME}
14240
14241          when Pragma_Unreferenced => Unreferenced : declare
14242             Arg_Node : Node_Id;
14243             Arg_Expr : Node_Id;
14244             Arg_Ent  : Entity_Id;
14245             Citem    : Node_Id;
14246
14247          begin
14248             GNAT_Pragma;
14249             Check_At_Least_N_Arguments (1);
14250
14251             --  Check case of appearing within context clause
14252
14253             if Is_In_Context_Clause then
14254
14255                --  The arguments must all be units mentioned in a with clause
14256                --  in the same context clause. Note we already checked (in
14257                --  Par.Prag) that the arguments are either identifiers or
14258                --  selected components.
14259
14260                Arg_Node := Arg1;
14261                while Present (Arg_Node) loop
14262                   Citem := First (List_Containing (N));
14263                   while Citem /= N loop
14264                      if Nkind (Citem) = N_With_Clause
14265                        and then
14266                          Same_Name (Name (Citem), Get_Pragma_Arg (Arg_Node))
14267                      then
14268                         Set_Has_Pragma_Unreferenced
14269                           (Cunit_Entity
14270                              (Get_Source_Unit
14271                                 (Library_Unit (Citem))));
14272                         Set_Unit_Name
14273                           (Get_Pragma_Arg (Arg_Node), Name (Citem));
14274                         exit;
14275                      end if;
14276
14277                      Next (Citem);
14278                   end loop;
14279
14280                   if Citem = N then
14281                      Error_Pragma_Arg
14282                        ("argument of pragma% is not withed unit", Arg_Node);
14283                   end if;
14284
14285                   Next (Arg_Node);
14286                end loop;
14287
14288             --  Case of not in list of context items
14289
14290             else
14291                Arg_Node := Arg1;
14292                while Present (Arg_Node) loop
14293                   Check_No_Identifier (Arg_Node);
14294
14295                   --  Note: the analyze call done by Check_Arg_Is_Local_Name
14296                   --  will in fact generate reference, so that the entity will
14297                   --  have a reference, which will inhibit any warnings about
14298                   --  it not being referenced, and also properly show up in the
14299                   --  ali file as a reference. But this reference is recorded
14300                   --  before the Has_Pragma_Unreferenced flag is set, so that
14301                   --  no warning is generated for this reference.
14302
14303                   Check_Arg_Is_Local_Name (Arg_Node);
14304                   Arg_Expr := Get_Pragma_Arg (Arg_Node);
14305
14306                   if Is_Entity_Name (Arg_Expr) then
14307                      Arg_Ent := Entity (Arg_Expr);
14308
14309                      --  If the entity is overloaded, the pragma applies to the
14310                      --  most recent overloading, as documented. In this case,
14311                      --  name resolution does not generate a reference, so it
14312                      --  must be done here explicitly.
14313
14314                      if Is_Overloaded (Arg_Expr) then
14315                         Generate_Reference (Arg_Ent, N);
14316                      end if;
14317
14318                      Set_Has_Pragma_Unreferenced (Arg_Ent);
14319                   end if;
14320
14321                   Next (Arg_Node);
14322                end loop;
14323             end if;
14324          end Unreferenced;
14325
14326          --------------------------
14327          -- Unreferenced_Objects --
14328          --------------------------
14329
14330          --  pragma Unreferenced_Objects (local_Name {, local_Name});
14331
14332          when Pragma_Unreferenced_Objects => Unreferenced_Objects : declare
14333             Arg_Node : Node_Id;
14334             Arg_Expr : Node_Id;
14335
14336          begin
14337             GNAT_Pragma;
14338             Check_At_Least_N_Arguments (1);
14339
14340             Arg_Node := Arg1;
14341             while Present (Arg_Node) loop
14342                Check_No_Identifier (Arg_Node);
14343                Check_Arg_Is_Local_Name (Arg_Node);
14344                Arg_Expr := Get_Pragma_Arg (Arg_Node);
14345
14346                if not Is_Entity_Name (Arg_Expr)
14347                  or else not Is_Type (Entity (Arg_Expr))
14348                then
14349                   Error_Pragma_Arg
14350                     ("argument for pragma% must be type or subtype", Arg_Node);
14351                end if;
14352
14353                Set_Has_Pragma_Unreferenced_Objects (Entity (Arg_Expr));
14354                Next (Arg_Node);
14355             end loop;
14356          end Unreferenced_Objects;
14357
14358          ------------------------------
14359          -- Unreserve_All_Interrupts --
14360          ------------------------------
14361
14362          --  pragma Unreserve_All_Interrupts;
14363
14364          when Pragma_Unreserve_All_Interrupts =>
14365             GNAT_Pragma;
14366             Check_Arg_Count (0);
14367
14368             if In_Extended_Main_Code_Unit (Main_Unit_Entity) then
14369                Unreserve_All_Interrupts := True;
14370             end if;
14371
14372          ----------------
14373          -- Unsuppress --
14374          ----------------
14375
14376          --  pragma Unsuppress (IDENTIFIER [, [On =>] NAME]);
14377
14378          when Pragma_Unsuppress =>
14379             Ada_2005_Pragma;
14380             Process_Suppress_Unsuppress (False);
14381
14382          -------------------
14383          -- Use_VADS_Size --
14384          -------------------
14385
14386          --  pragma Use_VADS_Size;
14387
14388          when Pragma_Use_VADS_Size =>
14389             GNAT_Pragma;
14390             Check_Arg_Count (0);
14391             Check_Valid_Configuration_Pragma;
14392             Use_VADS_Size := True;
14393
14394          ---------------------
14395          -- Validity_Checks --
14396          ---------------------
14397
14398          --  pragma Validity_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
14399
14400          when Pragma_Validity_Checks => Validity_Checks : declare
14401             A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
14402             S  : String_Id;
14403             C  : Char_Code;
14404
14405          begin
14406             GNAT_Pragma;
14407             Check_Arg_Count (1);
14408             Check_No_Identifiers;
14409
14410             if Nkind (A) = N_String_Literal then
14411                S   := Strval (A);
14412
14413                declare
14414                   Slen    : constant Natural := Natural (String_Length (S));
14415                   Options : String (1 .. Slen);
14416                   J       : Natural;
14417
14418                begin
14419                   J := 1;
14420                   loop
14421                      C := Get_String_Char (S, Int (J));
14422                      exit when not In_Character_Range (C);
14423                      Options (J) := Get_Character (C);
14424
14425                      if J = Slen then
14426                         Set_Validity_Check_Options (Options);
14427                         exit;
14428                      else
14429                         J := J + 1;
14430                      end if;
14431                   end loop;
14432                end;
14433
14434             elsif Nkind (A) = N_Identifier then
14435                if Chars (A) = Name_All_Checks then
14436                   Set_Validity_Check_Options ("a");
14437                elsif Chars (A) = Name_On then
14438                   Validity_Checks_On := True;
14439                elsif Chars (A) = Name_Off then
14440                   Validity_Checks_On := False;
14441                end if;
14442             end if;
14443          end Validity_Checks;
14444
14445          --------------
14446          -- Volatile --
14447          --------------
14448
14449          --  pragma Volatile (LOCAL_NAME);
14450
14451          when Pragma_Volatile =>
14452             Process_Atomic_Shared_Volatile;
14453
14454          -------------------------
14455          -- Volatile_Components --
14456          -------------------------
14457
14458          --  pragma Volatile_Components (array_LOCAL_NAME);
14459
14460          --  Volatile is handled by the same circuit as Atomic_Components
14461
14462          --------------
14463          -- Warnings --
14464          --------------
14465
14466          --  pragma Warnings (On | Off);
14467          --  pragma Warnings (On | Off, LOCAL_NAME);
14468          --  pragma Warnings (static_string_EXPRESSION);
14469          --  pragma Warnings (On | Off, STRING_LITERAL);
14470
14471          when Pragma_Warnings => Warnings : begin
14472             GNAT_Pragma;
14473             Check_At_Least_N_Arguments (1);
14474             Check_No_Identifiers;
14475
14476             --  If debug flag -gnatd.i is set, pragma is ignored
14477
14478             if Debug_Flag_Dot_I then
14479                return;
14480             end if;
14481
14482             --  Process various forms of the pragma
14483
14484             declare
14485                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
14486
14487             begin
14488                --  One argument case
14489
14490                if Arg_Count = 1 then
14491
14492                   --  On/Off one argument case was processed by parser
14493
14494                   if Nkind (Argx) = N_Identifier
14495                     and then
14496                       (Chars (Argx) = Name_On
14497                          or else
14498                        Chars (Argx) = Name_Off)
14499                   then
14500                      null;
14501
14502                   --  One argument case must be ON/OFF or static string expr
14503
14504                   elsif not Is_Static_String_Expression (Arg1) then
14505                      Error_Pragma_Arg
14506                        ("argument of pragma% must be On/Off or " &
14507                         "static string expression", Arg1);
14508
14509                   --  One argument string expression case
14510
14511                   else
14512                      declare
14513                         Lit : constant Node_Id   := Expr_Value_S (Argx);
14514                         Str : constant String_Id := Strval (Lit);
14515                         Len : constant Nat       := String_Length (Str);
14516                         C   : Char_Code;
14517                         J   : Nat;
14518                         OK  : Boolean;
14519                         Chr : Character;
14520
14521                      begin
14522                         J := 1;
14523                         while J <= Len loop
14524                            C := Get_String_Char (Str, J);
14525                            OK := In_Character_Range (C);
14526
14527                            if OK then
14528                               Chr := Get_Character (C);
14529
14530                               --  Dot case
14531
14532                               if J < Len and then Chr = '.' then
14533                                  J := J + 1;
14534                                  C := Get_String_Char (Str, J);
14535                                  Chr := Get_Character (C);
14536
14537                                  if not Set_Dot_Warning_Switch (Chr) then
14538                                     Error_Pragma_Arg
14539                                       ("invalid warning switch character " &
14540                                        '.' & Chr, Arg1);
14541                                  end if;
14542
14543                               --  Non-Dot case
14544
14545                               else
14546                                  OK := Set_Warning_Switch (Chr);
14547                               end if;
14548                            end if;
14549
14550                            if not OK then
14551                               Error_Pragma_Arg
14552                                 ("invalid warning switch character " & Chr,
14553                                  Arg1);
14554                            end if;
14555
14556                            J := J + 1;
14557                         end loop;
14558                      end;
14559                   end if;
14560
14561                --  Two or more arguments (must be two)
14562
14563                else
14564                   Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
14565                   Check_At_Most_N_Arguments (2);
14566
14567                   declare
14568                      E_Id : Node_Id;
14569                      E    : Entity_Id;
14570                      Err  : Boolean;
14571
14572                   begin
14573                      E_Id := Get_Pragma_Arg (Arg2);
14574                      Analyze (E_Id);
14575
14576                      --  In the expansion of an inlined body, a reference to
14577                      --  the formal may be wrapped in a conversion if the
14578                      --  actual is a conversion. Retrieve the real entity name.
14579
14580                      if (In_Instance_Body or In_Inlined_Body)
14581                        and then Nkind (E_Id) = N_Unchecked_Type_Conversion
14582                      then
14583                         E_Id := Expression (E_Id);
14584                      end if;
14585
14586                      --  Entity name case
14587
14588                      if Is_Entity_Name (E_Id) then
14589                         E := Entity (E_Id);
14590
14591                         if E = Any_Id then
14592                            return;
14593                         else
14594                            loop
14595                               Set_Warnings_Off
14596                                 (E, (Chars (Get_Pragma_Arg (Arg1)) =
14597                                                               Name_Off));
14598
14599                               if Chars (Get_Pragma_Arg (Arg1)) = Name_Off
14600                                 and then Warn_On_Warnings_Off
14601                               then
14602                                  Warnings_Off_Pragmas.Append ((N, E));
14603                               end if;
14604
14605                               if Is_Enumeration_Type (E) then
14606                                  declare
14607                                     Lit : Entity_Id;
14608                                  begin
14609                                     Lit := First_Literal (E);
14610                                     while Present (Lit) loop
14611                                        Set_Warnings_Off (Lit);
14612                                        Next_Literal (Lit);
14613                                     end loop;
14614                                  end;
14615                               end if;
14616
14617                               exit when No (Homonym (E));
14618                               E := Homonym (E);
14619                            end loop;
14620                         end if;
14621
14622                      --  Error if not entity or static string literal case
14623
14624                      elsif not Is_Static_String_Expression (Arg2) then
14625                         Error_Pragma_Arg
14626                           ("second argument of pragma% must be entity " &
14627                            "name or static string expression", Arg2);
14628
14629                      --  String literal case
14630
14631                      else
14632                         String_To_Name_Buffer
14633                           (Strval (Expr_Value_S (Get_Pragma_Arg (Arg2))));
14634
14635                         --  Note on configuration pragma case: If this is a
14636                         --  configuration pragma, then for an OFF pragma, we
14637                         --  just set Config True in the call, which is all
14638                         --  that needs to be done. For the case of ON, this
14639                         --  is normally an error, unless it is canceling the
14640                         --  effect of a previous OFF pragma in the same file.
14641                         --  In any other case, an error will be signalled (ON
14642                         --  with no matching OFF).
14643
14644                         --  Note: We set Used if we are inside a generic to
14645                         --  disable the test that the non-config case actually
14646                         --  cancels a warning. That's because we can't be sure
14647                         --  there isn't an instantiation in some other unit
14648                         --  where a warning is suppressed.
14649
14650                         --  We could do a little better here by checking if the
14651                         --  generic unit we are inside is public, but for now
14652                         --  we don't bother with that refinement.
14653
14654                         if Chars (Argx) = Name_Off then
14655                            Set_Specific_Warning_Off
14656                              (Loc, Name_Buffer (1 .. Name_Len),
14657                               Config => Is_Configuration_Pragma,
14658                               Used   => Inside_A_Generic or else In_Instance);
14659
14660                         elsif Chars (Argx) = Name_On then
14661                            Set_Specific_Warning_On
14662                              (Loc, Name_Buffer (1 .. Name_Len), Err);
14663
14664                            if Err then
14665                               Error_Msg
14666                                 ("?pragma Warnings On with no " &
14667                                  "matching Warnings Off",
14668                                  Loc);
14669                            end if;
14670                         end if;
14671                      end if;
14672                   end;
14673                end if;
14674             end;
14675          end Warnings;
14676
14677          -------------------
14678          -- Weak_External --
14679          -------------------
14680
14681          --  pragma Weak_External ([Entity =>] LOCAL_NAME);
14682
14683          when Pragma_Weak_External => Weak_External : declare
14684             Ent : Entity_Id;
14685
14686          begin
14687             GNAT_Pragma;
14688             Check_Arg_Count (1);
14689             Check_Optional_Identifier (Arg1, Name_Entity);
14690             Check_Arg_Is_Library_Level_Local_Name (Arg1);
14691             Ent := Entity (Get_Pragma_Arg (Arg1));
14692
14693             if Rep_Item_Too_Early (Ent, N) then
14694                return;
14695             else
14696                Ent := Underlying_Type (Ent);
14697             end if;
14698
14699             --  The only processing required is to link this item on to the
14700             --  list of rep items for the given entity. This is accomplished
14701             --  by the call to Rep_Item_Too_Late (when no error is detected
14702             --  and False is returned).
14703
14704             if Rep_Item_Too_Late (Ent, N) then
14705                return;
14706             else
14707                Set_Has_Gigi_Rep_Item (Ent);
14708             end if;
14709          end Weak_External;
14710
14711          -----------------------------
14712          -- Wide_Character_Encoding --
14713          -----------------------------
14714
14715          --  pragma Wide_Character_Encoding (IDENTIFIER);
14716
14717          when Pragma_Wide_Character_Encoding =>
14718             GNAT_Pragma;
14719
14720             --  Nothing to do, handled in parser. Note that we do not enforce
14721             --  configuration pragma placement, this pragma can appear at any
14722             --  place in the source, allowing mixed encodings within a single
14723             --  source program.
14724
14725             null;
14726
14727          --------------------
14728          -- Unknown_Pragma --
14729          --------------------
14730
14731          --  Should be impossible, since the case of an unknown pragma is
14732          --  separately processed before the case statement is entered.
14733
14734          when Unknown_Pragma =>
14735             raise Program_Error;
14736       end case;
14737
14738       --  AI05-0144: detect dangerous order dependence. Disabled for now,
14739       --  until AI is formally approved.
14740
14741       --  Check_Order_Dependence;
14742
14743    exception
14744       when Pragma_Exit => null;
14745    end Analyze_Pragma;
14746
14747    -----------------------------
14748    -- Analyze_TC_In_Decl_Part --
14749    -----------------------------
14750
14751    procedure Analyze_TC_In_Decl_Part (N : Node_Id; S : Entity_Id) is
14752    begin
14753       --  Install formals and push subprogram spec onto scope stack so that we
14754       --  can see the formals from the pragma.
14755
14756       Install_Formals (S);
14757       Push_Scope (S);
14758
14759       --  Preanalyze the boolean expressions, we treat these as spec
14760       --  expressions (i.e. similar to a default expression).
14761
14762       Preanalyze_TC_Args (N,
14763                           Get_Requires_From_Test_Case_Pragma (N),
14764                           Get_Ensures_From_Test_Case_Pragma (N));
14765
14766       --  Remove the subprogram from the scope stack now that the pre-analysis
14767       --  of the expressions in the test-case is done.
14768
14769       End_Scope;
14770    end Analyze_TC_In_Decl_Part;
14771
14772    --------------------
14773    -- Check_Disabled --
14774    --------------------
14775
14776    function Check_Disabled (Nam : Name_Id) return Boolean is
14777       PP : Node_Id;
14778
14779    begin
14780       --  Loop through entries in check policy list
14781
14782       PP := Opt.Check_Policy_List;
14783       loop
14784          --  If there are no specific entries that matched, then nothing is
14785          --  disabled, so return False.
14786
14787          if No (PP) then
14788             return False;
14789
14790          --  Here we have an entry see if it matches
14791
14792          else
14793             declare
14794                PPA : constant List_Id := Pragma_Argument_Associations (PP);
14795             begin
14796                if Nam = Chars (Get_Pragma_Arg (First (PPA))) then
14797                   return Chars (Get_Pragma_Arg (Last (PPA))) = Name_Disable;
14798                else
14799                   PP := Next_Pragma (PP);
14800                end if;
14801             end;
14802          end if;
14803       end loop;
14804    end Check_Disabled;
14805
14806    -------------------
14807    -- Check_Enabled --
14808    -------------------
14809
14810    function Check_Enabled (Nam : Name_Id) return Boolean is
14811       PP : Node_Id;
14812
14813    begin
14814       --  Loop through entries in check policy list
14815
14816       PP := Opt.Check_Policy_List;
14817       loop
14818          --  If there are no specific entries that matched, then we let the
14819          --  setting of assertions govern. Note that this provides the needed
14820          --  compatibility with the RM for the cases of assertion, invariant,
14821          --  precondition, predicate, and postcondition.
14822
14823          if No (PP) then
14824             return Assertions_Enabled;
14825
14826          --  Here we have an entry see if it matches
14827
14828          else
14829             declare
14830                PPA : constant List_Id := Pragma_Argument_Associations (PP);
14831
14832             begin
14833                if Nam = Chars (Get_Pragma_Arg (First (PPA))) then
14834                   case (Chars (Get_Pragma_Arg (Last (PPA)))) is
14835                      when Name_On | Name_Check =>
14836                         return True;
14837                      when Name_Off | Name_Ignore =>
14838                         return False;
14839                      when others =>
14840                         raise Program_Error;
14841                   end case;
14842
14843                else
14844                   PP := Next_Pragma (PP);
14845                end if;
14846             end;
14847          end if;
14848       end loop;
14849    end Check_Enabled;
14850
14851    ---------------------------------
14852    -- Delay_Config_Pragma_Analyze --
14853    ---------------------------------
14854
14855    function Delay_Config_Pragma_Analyze (N : Node_Id) return Boolean is
14856    begin
14857       return Pragma_Name (N) = Name_Interrupt_State
14858                or else
14859              Pragma_Name (N) = Name_Priority_Specific_Dispatching;
14860    end Delay_Config_Pragma_Analyze;
14861
14862    -------------------------
14863    -- Get_Base_Subprogram --
14864    -------------------------
14865
14866    function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id is
14867       Result : Entity_Id;
14868
14869    begin
14870       --  Follow subprogram renaming chain
14871
14872       Result := Def_Id;
14873       while Is_Subprogram (Result)
14874         and then
14875           Nkind (Parent (Declaration_Node (Result))) =
14876                                          N_Subprogram_Renaming_Declaration
14877         and then Present (Alias (Result))
14878       loop
14879          Result := Alias (Result);
14880       end loop;
14881
14882       return Result;
14883    end Get_Base_Subprogram;
14884
14885    ----------------
14886    -- Initialize --
14887    ----------------
14888
14889    procedure Initialize is
14890    begin
14891       Externals.Init;
14892    end Initialize;
14893
14894    -----------------------------
14895    -- Is_Config_Static_String --
14896    -----------------------------
14897
14898    function Is_Config_Static_String (Arg : Node_Id) return Boolean is
14899
14900       function Add_Config_Static_String (Arg : Node_Id) return Boolean;
14901       --  This is an internal recursive function that is just like the outer
14902       --  function except that it adds the string to the name buffer rather
14903       --  than placing the string in the name buffer.
14904
14905       ------------------------------
14906       -- Add_Config_Static_String --
14907       ------------------------------
14908
14909       function Add_Config_Static_String (Arg : Node_Id) return Boolean is
14910          N : Node_Id;
14911          C : Char_Code;
14912
14913       begin
14914          N := Arg;
14915
14916          if Nkind (N) = N_Op_Concat then
14917             if Add_Config_Static_String (Left_Opnd (N)) then
14918                N := Right_Opnd (N);
14919             else
14920                return False;
14921             end if;
14922          end if;
14923
14924          if Nkind (N) /= N_String_Literal then
14925             Error_Msg_N ("string literal expected for pragma argument", N);
14926             return False;
14927
14928          else
14929             for J in 1 .. String_Length (Strval (N)) loop
14930                C := Get_String_Char (Strval (N), J);
14931
14932                if not In_Character_Range (C) then
14933                   Error_Msg
14934                     ("string literal contains invalid wide character",
14935                      Sloc (N) + 1 + Source_Ptr (J));
14936                   return False;
14937                end if;
14938
14939                Add_Char_To_Name_Buffer (Get_Character (C));
14940             end loop;
14941          end if;
14942
14943          return True;
14944       end Add_Config_Static_String;
14945
14946    --  Start of processing for Is_Config_Static_String
14947
14948    begin
14949
14950       Name_Len := 0;
14951       return Add_Config_Static_String (Arg);
14952    end Is_Config_Static_String;
14953
14954    -----------------------------------------
14955    -- Is_Non_Significant_Pragma_Reference --
14956    -----------------------------------------
14957
14958    --  This function makes use of the following static table which indicates
14959    --  whether appearance of some name in a given pragma is to be considered
14960    --  as a reference for the purposes of warnings about unreferenced objects.
14961
14962    --  -1  indicates that references in any argument position are significant
14963    --  0   indicates that appearance in any argument is not significant
14964    --  +n  indicates that appearance as argument n is significant, but all
14965    --      other arguments are not significant
14966    --  99  special processing required (e.g. for pragma Check)
14967
14968    Sig_Flags : constant array (Pragma_Id) of Int :=
14969      (Pragma_AST_Entry                      => -1,
14970       Pragma_Abort_Defer                    => -1,
14971       Pragma_Ada_83                         => -1,
14972       Pragma_Ada_95                         => -1,
14973       Pragma_Ada_05                         => -1,
14974       Pragma_Ada_2005                       => -1,
14975       Pragma_Ada_12                         => -1,
14976       Pragma_Ada_2012                       => -1,
14977       Pragma_All_Calls_Remote               => -1,
14978       Pragma_Annotate                       => -1,
14979       Pragma_Assert                         => -1,
14980       Pragma_Assertion_Policy               =>  0,
14981       Pragma_Assume_No_Invalid_Values       =>  0,
14982       Pragma_Asynchronous                   => -1,
14983       Pragma_Atomic                         =>  0,
14984       Pragma_Atomic_Components              =>  0,
14985       Pragma_Attach_Handler                 => -1,
14986       Pragma_Check                          => 99,
14987       Pragma_Check_Name                     =>  0,
14988       Pragma_Check_Policy                   =>  0,
14989       Pragma_CIL_Constructor                => -1,
14990       Pragma_CPP_Class                      =>  0,
14991       Pragma_CPP_Constructor                =>  0,
14992       Pragma_CPP_Virtual                    =>  0,
14993       Pragma_CPP_Vtable                     =>  0,
14994       Pragma_CPU                            => -1,
14995       Pragma_C_Pass_By_Copy                 =>  0,
14996       Pragma_Comment                        =>  0,
14997       Pragma_Common_Object                  => -1,
14998       Pragma_Compile_Time_Error             => -1,
14999       Pragma_Compile_Time_Warning           => -1,
15000       Pragma_Compiler_Unit                  =>  0,
15001       Pragma_Complete_Representation        =>  0,
15002       Pragma_Complex_Representation         =>  0,
15003       Pragma_Component_Alignment            => -1,
15004       Pragma_Controlled                     =>  0,
15005       Pragma_Convention                     =>  0,
15006       Pragma_Convention_Identifier          =>  0,
15007       Pragma_Debug                          => -1,
15008       Pragma_Debug_Policy                   =>  0,
15009       Pragma_Detect_Blocking                => -1,
15010       Pragma_Default_Storage_Pool           => -1,
15011       Pragma_Disable_Atomic_Synchronization => -1,
15012       Pragma_Discard_Names                  =>  0,
15013       Pragma_Dispatching_Domain             => -1,
15014       Pragma_Elaborate                      => -1,
15015       Pragma_Elaborate_All                  => -1,
15016       Pragma_Elaborate_Body                 => -1,
15017       Pragma_Elaboration_Checks             => -1,
15018       Pragma_Eliminate                      => -1,
15019       Pragma_Enable_Atomic_Synchronization  => -1,
15020       Pragma_Export                         => -1,
15021       Pragma_Export_Exception               => -1,
15022       Pragma_Export_Function                => -1,
15023       Pragma_Export_Object                  => -1,
15024       Pragma_Export_Procedure               => -1,
15025       Pragma_Export_Value                   => -1,
15026       Pragma_Export_Valued_Procedure        => -1,
15027       Pragma_Extend_System                  => -1,
15028       Pragma_Extensions_Allowed             => -1,
15029       Pragma_External                       => -1,
15030       Pragma_Favor_Top_Level                => -1,
15031       Pragma_External_Name_Casing           => -1,
15032       Pragma_Fast_Math                      => -1,
15033       Pragma_Finalize_Storage_Only          =>  0,
15034       Pragma_Float_Representation           =>  0,
15035       Pragma_Ident                          => -1,
15036       Pragma_Implementation_Defined         => -1,
15037       Pragma_Implemented                    => -1,
15038       Pragma_Implicit_Packing               =>  0,
15039       Pragma_Import                         => +2,
15040       Pragma_Import_Exception               =>  0,
15041       Pragma_Import_Function                =>  0,
15042       Pragma_Import_Object                  =>  0,
15043       Pragma_Import_Procedure               =>  0,
15044       Pragma_Import_Valued_Procedure        =>  0,
15045       Pragma_Independent                    =>  0,
15046       Pragma_Independent_Components         =>  0,
15047       Pragma_Initialize_Scalars             => -1,
15048       Pragma_Inline                         =>  0,
15049       Pragma_Inline_Always                  =>  0,
15050       Pragma_Inline_Generic                 =>  0,
15051       Pragma_Inspection_Point               => -1,
15052       Pragma_Interface                      => +2,
15053       Pragma_Interface_Name                 => +2,
15054       Pragma_Interrupt_Handler              => -1,
15055       Pragma_Interrupt_Priority             => -1,
15056       Pragma_Interrupt_State                => -1,
15057       Pragma_Invariant                      => -1,
15058       Pragma_Java_Constructor               => -1,
15059       Pragma_Java_Interface                 => -1,
15060       Pragma_Keep_Names                     =>  0,
15061       Pragma_License                        => -1,
15062       Pragma_Link_With                      => -1,
15063       Pragma_Linker_Alias                   => -1,
15064       Pragma_Linker_Constructor             => -1,
15065       Pragma_Linker_Destructor              => -1,
15066       Pragma_Linker_Options                 => -1,
15067       Pragma_Linker_Section                 => -1,
15068       Pragma_List                           => -1,
15069       Pragma_Locking_Policy                 => -1,
15070       Pragma_Long_Float                     => -1,
15071       Pragma_Machine_Attribute              => -1,
15072       Pragma_Main                           => -1,
15073       Pragma_Main_Storage                   => -1,
15074       Pragma_Memory_Size                    => -1,
15075       Pragma_No_Return                      =>  0,
15076       Pragma_No_Body                        =>  0,
15077       Pragma_No_Run_Time                    => -1,
15078       Pragma_No_Strict_Aliasing             => -1,
15079       Pragma_Normalize_Scalars              => -1,
15080       Pragma_Obsolescent                    =>  0,
15081       Pragma_Optimize                       => -1,
15082       Pragma_Optimize_Alignment             => -1,
15083       Pragma_Ordered                        =>  0,
15084       Pragma_Pack                           =>  0,
15085       Pragma_Page                           => -1,
15086       Pragma_Passive                        => -1,
15087       Pragma_Preelaborable_Initialization   => -1,
15088       Pragma_Polling                        => -1,
15089       Pragma_Persistent_BSS                 =>  0,
15090       Pragma_Postcondition                  => -1,
15091       Pragma_Precondition                   => -1,
15092       Pragma_Predicate                      => -1,
15093       Pragma_Preelaborate                   => -1,
15094       Pragma_Preelaborate_05                => -1,
15095       Pragma_Priority                       => -1,
15096       Pragma_Priority_Specific_Dispatching  => -1,
15097       Pragma_Profile                        =>  0,
15098       Pragma_Profile_Warnings               =>  0,
15099       Pragma_Propagate_Exceptions           => -1,
15100       Pragma_Psect_Object                   => -1,
15101       Pragma_Pure                           => -1,
15102       Pragma_Pure_05                        => -1,
15103       Pragma_Pure_12                        => -1,
15104       Pragma_Pure_Function                  => -1,
15105       Pragma_Queuing_Policy                 => -1,
15106       Pragma_Ravenscar                      => -1,
15107       Pragma_Relative_Deadline              => -1,
15108       Pragma_Remote_Access_Type             => -1,
15109       Pragma_Remote_Call_Interface          => -1,
15110       Pragma_Remote_Types                   => -1,
15111       Pragma_Restricted_Run_Time            => -1,
15112       Pragma_Restriction_Warnings           => -1,
15113       Pragma_Restrictions                   => -1,
15114       Pragma_Reviewable                     => -1,
15115       Pragma_Short_Circuit_And_Or           => -1,
15116       Pragma_Share_Generic                  => -1,
15117       Pragma_Shared                         => -1,
15118       Pragma_Shared_Passive                 => -1,
15119       Pragma_Short_Descriptors              =>  0,
15120       Pragma_Source_File_Name               => -1,
15121       Pragma_Source_File_Name_Project       => -1,
15122       Pragma_Source_Reference               => -1,
15123       Pragma_Storage_Size                   => -1,
15124       Pragma_Storage_Unit                   => -1,
15125       Pragma_Static_Elaboration_Desired     => -1,
15126       Pragma_Stream_Convert                 => -1,
15127       Pragma_Style_Checks                   => -1,
15128       Pragma_Subtitle                       => -1,
15129       Pragma_Suppress                       =>  0,
15130       Pragma_Suppress_Exception_Locations   =>  0,
15131       Pragma_Suppress_All                   => -1,
15132       Pragma_Suppress_Debug_Info            =>  0,
15133       Pragma_Suppress_Initialization        =>  0,
15134       Pragma_System_Name                    => -1,
15135       Pragma_Task_Dispatching_Policy        => -1,
15136       Pragma_Task_Info                      => -1,
15137       Pragma_Task_Name                      => -1,
15138       Pragma_Task_Storage                   =>  0,
15139       Pragma_Test_Case                      => -1,
15140       Pragma_Thread_Local_Storage           =>  0,
15141       Pragma_Time_Slice                     => -1,
15142       Pragma_Title                          => -1,
15143       Pragma_Unchecked_Union                =>  0,
15144       Pragma_Unimplemented_Unit             => -1,
15145       Pragma_Universal_Aliasing             => -1,
15146       Pragma_Universal_Data                 => -1,
15147       Pragma_Unmodified                     => -1,
15148       Pragma_Unreferenced                   => -1,
15149       Pragma_Unreferenced_Objects           => -1,
15150       Pragma_Unreserve_All_Interrupts       => -1,
15151       Pragma_Unsuppress                     =>  0,
15152       Pragma_Use_VADS_Size                  => -1,
15153       Pragma_Validity_Checks                => -1,
15154       Pragma_Volatile                       =>  0,
15155       Pragma_Volatile_Components            =>  0,
15156       Pragma_Warnings                       => -1,
15157       Pragma_Weak_External                  => -1,
15158       Pragma_Wide_Character_Encoding        =>  0,
15159       Unknown_Pragma                        =>  0);
15160
15161    function Is_Non_Significant_Pragma_Reference (N : Node_Id) return Boolean is
15162       Id : Pragma_Id;
15163       P  : Node_Id;
15164       C  : Int;
15165       A  : Node_Id;
15166
15167    begin
15168       P := Parent (N);
15169
15170       if Nkind (P) /= N_Pragma_Argument_Association then
15171          return False;
15172
15173       else
15174          Id := Get_Pragma_Id (Parent (P));
15175          C := Sig_Flags (Id);
15176
15177          case C is
15178             when -1 =>
15179                return False;
15180
15181             when 0 =>
15182                return True;
15183
15184             when 99 =>
15185                case Id is
15186
15187                   --  For pragma Check, the first argument is not significant,
15188                   --  the second and the third (if present) arguments are
15189                   --  significant.
15190
15191                   when Pragma_Check =>
15192                      return
15193                        P = First (Pragma_Argument_Associations (Parent (P)));
15194
15195                   when others =>
15196                      raise Program_Error;
15197                end case;
15198
15199             when others =>
15200                A := First (Pragma_Argument_Associations (Parent (P)));
15201                for J in 1 .. C - 1 loop
15202                   if No (A) then
15203                      return False;
15204                   end if;
15205
15206                   Next (A);
15207                end loop;
15208
15209                return A = P; -- is this wrong way round ???
15210          end case;
15211       end if;
15212    end Is_Non_Significant_Pragma_Reference;
15213
15214    ------------------------------
15215    -- Is_Pragma_String_Literal --
15216    ------------------------------
15217
15218    --  This function returns true if the corresponding pragma argument is a
15219    --  static string expression. These are the only cases in which string
15220    --  literals can appear as pragma arguments. We also allow a string literal
15221    --  as the first argument to pragma Assert (although it will of course
15222    --  always generate a type error).
15223
15224    function Is_Pragma_String_Literal (Par : Node_Id) return Boolean is
15225       Pragn : constant Node_Id := Parent (Par);
15226       Assoc : constant List_Id := Pragma_Argument_Associations (Pragn);
15227       Pname : constant Name_Id := Pragma_Name (Pragn);
15228       Argn  : Natural;
15229       N     : Node_Id;
15230
15231    begin
15232       Argn := 1;
15233       N := First (Assoc);
15234       loop
15235          exit when N = Par;
15236          Argn := Argn + 1;
15237          Next (N);
15238       end loop;
15239
15240       if Pname = Name_Assert then
15241          return True;
15242
15243       elsif Pname = Name_Export then
15244          return Argn > 2;
15245
15246       elsif Pname = Name_Ident then
15247          return Argn = 1;
15248
15249       elsif Pname = Name_Import then
15250          return Argn > 2;
15251
15252       elsif Pname = Name_Interface_Name then
15253          return Argn > 1;
15254
15255       elsif Pname = Name_Linker_Alias then
15256          return Argn = 2;
15257
15258       elsif Pname = Name_Linker_Section then
15259          return Argn = 2;
15260
15261       elsif Pname = Name_Machine_Attribute then
15262          return Argn = 2;
15263
15264       elsif Pname = Name_Source_File_Name then
15265          return True;
15266
15267       elsif Pname = Name_Source_Reference then
15268          return Argn = 2;
15269
15270       elsif Pname = Name_Title then
15271          return True;
15272
15273       elsif Pname = Name_Subtitle then
15274          return True;
15275
15276       else
15277          return False;
15278       end if;
15279    end Is_Pragma_String_Literal;
15280
15281    -----------------------------------------
15282    -- Make_Aspect_For_PPC_In_Gen_Sub_Decl --
15283    -----------------------------------------
15284
15285    procedure Make_Aspect_For_PPC_In_Gen_Sub_Decl (Decl : Node_Id) is
15286       Aspects : constant List_Id := New_List;
15287       Loc     : constant Source_Ptr := Sloc (Decl);
15288       Or_Decl : constant Node_Id := Original_Node (Decl);
15289
15290       Original_Aspects : List_Id;
15291       --  To capture global references, a copy of the created aspects must be
15292       --  inserted in the original tree.
15293
15294       Prag         : Node_Id;
15295       Prag_Arg_Ass : Node_Id;
15296       Prag_Id      : Pragma_Id;
15297
15298    begin
15299       --  Check for any PPC pragmas that appear within Decl
15300
15301       Prag := Next (Decl);
15302       while Nkind (Prag) = N_Pragma loop
15303          Prag_Id := Get_Pragma_Id (Chars (Pragma_Identifier (Prag)));
15304
15305          case Prag_Id is
15306             when Pragma_Postcondition | Pragma_Precondition =>
15307                Prag_Arg_Ass := First (Pragma_Argument_Associations (Prag));
15308
15309                --  Make an aspect from any PPC pragma
15310
15311                Append_To (Aspects,
15312                  Make_Aspect_Specification (Loc,
15313                    Identifier =>
15314                      Make_Identifier (Loc, Chars (Pragma_Identifier (Prag))),
15315                    Expression =>
15316                      Copy_Separate_Tree (Expression (Prag_Arg_Ass))));
15317
15318                --  Generate the analysis information in the pragma expression
15319                --  and then set the pragma node analyzed to avoid any further
15320                --  analysis.
15321
15322                Analyze (Expression (Prag_Arg_Ass));
15323                Set_Analyzed (Prag, True);
15324
15325             when others => null;
15326          end case;
15327
15328          Next (Prag);
15329       end loop;
15330
15331       --  Set all new aspects into the generic declaration node
15332
15333       if Is_Non_Empty_List (Aspects) then
15334
15335          --  Create the list of aspects to be inserted in the original tree
15336
15337          Original_Aspects := Copy_Separate_List (Aspects);
15338
15339          --  Check if Decl already has aspects
15340
15341          --  Attach the new lists of aspects to both the generic copy and the
15342          --  original tree.
15343
15344          if Has_Aspects (Decl) then
15345             Append_List (Aspects, Aspect_Specifications (Decl));
15346             Append_List (Original_Aspects, Aspect_Specifications (Or_Decl));
15347
15348          else
15349             Set_Parent (Aspects, Decl);
15350             Set_Aspect_Specifications (Decl, Aspects);
15351             Set_Parent (Original_Aspects, Or_Decl);
15352             Set_Aspect_Specifications (Or_Decl, Original_Aspects);
15353          end if;
15354       end if;
15355    end Make_Aspect_For_PPC_In_Gen_Sub_Decl;
15356
15357    ------------------------
15358    -- Preanalyze_TC_Args --
15359    ------------------------
15360
15361    procedure Preanalyze_TC_Args (N, Arg_Req, Arg_Ens : Node_Id) is
15362    begin
15363       --  Preanalyze the boolean expressions, we treat these as spec
15364       --  expressions (i.e. similar to a default expression).
15365
15366       if Present (Arg_Req) then
15367          Preanalyze_Spec_Expression
15368            (Get_Pragma_Arg (Arg_Req), Standard_Boolean);
15369
15370          --  In ASIS mode, for a pragma generated from a source aspect, also
15371          --  analyze the original aspect expression.
15372
15373          if ASIS_Mode and then Present (Corresponding_Aspect (N)) then
15374             Preanalyze_Spec_Expression
15375               (Original_Node (Get_Pragma_Arg (Arg_Req)), Standard_Boolean);
15376          end if;
15377       end if;
15378
15379       if Present (Arg_Ens) then
15380          Preanalyze_Spec_Expression
15381            (Get_Pragma_Arg (Arg_Ens), Standard_Boolean);
15382
15383          --  In ASIS mode, for a pragma generated from a source aspect, also
15384          --  analyze the original aspect expression.
15385
15386          if ASIS_Mode and then Present (Corresponding_Aspect (N)) then
15387             Preanalyze_Spec_Expression
15388               (Original_Node (Get_Pragma_Arg (Arg_Ens)), Standard_Boolean);
15389          end if;
15390       end if;
15391    end Preanalyze_TC_Args;
15392
15393    --------------------------------------
15394    -- Process_Compilation_Unit_Pragmas --
15395    --------------------------------------
15396
15397    procedure Process_Compilation_Unit_Pragmas (N : Node_Id) is
15398    begin
15399       --  A special check for pragma Suppress_All, a very strange DEC pragma,
15400       --  strange because it comes at the end of the unit. Rational has the
15401       --  same name for a pragma, but treats it as a program unit pragma, In
15402       --  GNAT we just decide to allow it anywhere at all. If it appeared then
15403       --  the flag Has_Pragma_Suppress_All was set on the compilation unit
15404       --  node, and we insert a pragma Suppress (All_Checks) at the start of
15405       --  the context clause to ensure the correct processing.
15406
15407       if Has_Pragma_Suppress_All (N) then
15408          Prepend_To (Context_Items (N),
15409            Make_Pragma (Sloc (N),
15410              Chars                        => Name_Suppress,
15411              Pragma_Argument_Associations => New_List (
15412                Make_Pragma_Argument_Association (Sloc (N),
15413                  Expression => Make_Identifier (Sloc (N), Name_All_Checks)))));
15414       end if;
15415
15416       --  Nothing else to do at the current time!
15417
15418    end Process_Compilation_Unit_Pragmas;
15419
15420    --------
15421    -- rv --
15422    --------
15423
15424    procedure rv is
15425    begin
15426       null;
15427    end rv;
15428
15429    --------------------------------
15430    -- Set_Encoded_Interface_Name --
15431    --------------------------------
15432
15433    procedure Set_Encoded_Interface_Name (E : Entity_Id; S : Node_Id) is
15434       Str : constant String_Id := Strval (S);
15435       Len : constant Int       := String_Length (Str);
15436       CC  : Char_Code;
15437       C   : Character;
15438       J   : Int;
15439
15440       Hex : constant array (0 .. 15) of Character := "0123456789abcdef";
15441
15442       procedure Encode;
15443       --  Stores encoded value of character code CC. The encoding we use an
15444       --  underscore followed by four lower case hex digits.
15445
15446       ------------
15447       -- Encode --
15448       ------------
15449
15450       procedure Encode is
15451       begin
15452          Store_String_Char (Get_Char_Code ('_'));
15453          Store_String_Char
15454            (Get_Char_Code (Hex (Integer (CC / 2 ** 12))));
15455          Store_String_Char
15456            (Get_Char_Code (Hex (Integer (CC / 2 ** 8 and 16#0F#))));
15457          Store_String_Char
15458            (Get_Char_Code (Hex (Integer (CC / 2 ** 4 and 16#0F#))));
15459          Store_String_Char
15460            (Get_Char_Code (Hex (Integer (CC and 16#0F#))));
15461       end Encode;
15462
15463    --  Start of processing for Set_Encoded_Interface_Name
15464
15465    begin
15466       --  If first character is asterisk, this is a link name, and we leave it
15467       --  completely unmodified. We also ignore null strings (the latter case
15468       --  happens only in error cases) and no encoding should occur for Java or
15469       --  AAMP interface names.
15470
15471       if Len = 0
15472         or else Get_String_Char (Str, 1) = Get_Char_Code ('*')
15473         or else VM_Target /= No_VM
15474         or else AAMP_On_Target
15475       then
15476          Set_Interface_Name (E, S);
15477
15478       else
15479          J := 1;
15480          loop
15481             CC := Get_String_Char (Str, J);
15482
15483             exit when not In_Character_Range (CC);
15484
15485             C := Get_Character (CC);
15486
15487             exit when C /= '_' and then C /= '$'
15488               and then C not in '0' .. '9'
15489               and then C not in 'a' .. 'z'
15490               and then C not in 'A' .. 'Z';
15491
15492             if J = Len then
15493                Set_Interface_Name (E, S);
15494                return;
15495
15496             else
15497                J := J + 1;
15498             end if;
15499          end loop;
15500
15501          --  Here we need to encode. The encoding we use as follows:
15502          --     three underscores  + four hex digits (lower case)
15503
15504          Start_String;
15505
15506          for J in 1 .. String_Length (Str) loop
15507             CC := Get_String_Char (Str, J);
15508
15509             if not In_Character_Range (CC) then
15510                Encode;
15511             else
15512                C := Get_Character (CC);
15513
15514                if C = '_' or else C = '$'
15515                  or else C in '0' .. '9'
15516                  or else C in 'a' .. 'z'
15517                  or else C in 'A' .. 'Z'
15518                then
15519                   Store_String_Char (CC);
15520                else
15521                   Encode;
15522                end if;
15523             end if;
15524          end loop;
15525
15526          Set_Interface_Name (E,
15527            Make_String_Literal (Sloc (S),
15528              Strval => End_String));
15529       end if;
15530    end Set_Encoded_Interface_Name;
15531
15532    -------------------
15533    -- Set_Unit_Name --
15534    -------------------
15535
15536    procedure Set_Unit_Name (N : Node_Id; With_Item : Node_Id) is
15537       Pref : Node_Id;
15538       Scop : Entity_Id;
15539
15540    begin
15541       if Nkind (N) = N_Identifier
15542         and then Nkind (With_Item) = N_Identifier
15543       then
15544          Set_Entity (N, Entity (With_Item));
15545
15546       elsif Nkind (N) = N_Selected_Component then
15547          Change_Selected_Component_To_Expanded_Name (N);
15548          Set_Entity (N, Entity (With_Item));
15549          Set_Entity (Selector_Name (N), Entity (N));
15550
15551          Pref := Prefix (N);
15552          Scop := Scope (Entity (N));
15553          while Nkind (Pref) = N_Selected_Component loop
15554             Change_Selected_Component_To_Expanded_Name (Pref);
15555             Set_Entity (Selector_Name (Pref), Scop);
15556             Set_Entity (Pref, Scop);
15557             Pref := Prefix (Pref);
15558             Scop := Scope (Scop);
15559          end loop;
15560
15561          Set_Entity (Pref, Scop);
15562       end if;
15563    end Set_Unit_Name;
15564
15565 end Sem_Prag;