OSDN Git Service

2011-11-21 Robert Dewar <dewar@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_prag.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                             S E M _ P R A G                              --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2011, Free Software Foundation, Inc.         --
10 --                                                                          --
11 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
12 -- terms of the  GNU General Public License as published  by the Free Soft- --
13 -- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14 -- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17 -- for  more details.  You should have  received  a copy of the GNU General --
18 -- Public License  distributed with GNAT; see file COPYING3.  If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license.          --
20 --                                                                          --
21 -- GNAT was originally developed  by the GNAT team at  New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
23 --                                                                          --
24 ------------------------------------------------------------------------------
25
26 --  This unit contains the semantic processing for all pragmas, both language
27 --  and implementation defined. For most pragmas, the parser only does the
28 --  most basic job of checking the syntax, so Sem_Prag also contains the code
29 --  to complete the syntax checks. Certain pragmas are handled partially or
30 --  completely by the parser (see Par.Prag for further details).
31
32 with Aspects;  use Aspects;
33 with Atree;    use Atree;
34 with Casing;   use Casing;
35 with Checks;   use Checks;
36 with Csets;    use Csets;
37 with Debug;    use Debug;
38 with Einfo;    use Einfo;
39 with Elists;   use Elists;
40 with Errout;   use Errout;
41 with Exp_Dist; use Exp_Dist;
42 with Exp_Util; use Exp_Util;
43 with Freeze;   use Freeze;
44 with Lib;      use Lib;
45 with Lib.Writ; use Lib.Writ;
46 with Lib.Xref; use Lib.Xref;
47 with Namet.Sp; use Namet.Sp;
48 with Nlists;   use Nlists;
49 with Nmake;    use Nmake;
50 with Opt;      use Opt;
51 with Output;   use Output;
52 with Par_SCO;  use Par_SCO;
53 with Restrict; use Restrict;
54 with Rident;   use Rident;
55 with Rtsfind;  use Rtsfind;
56 with Sem;      use Sem;
57 with Sem_Aux;  use Sem_Aux;
58 with Sem_Ch3;  use Sem_Ch3;
59 with Sem_Ch6;  use Sem_Ch6;
60 with Sem_Ch8;  use Sem_Ch8;
61 with Sem_Ch12; use Sem_Ch12;
62 with Sem_Ch13; use Sem_Ch13;
63 with Sem_Disp; use Sem_Disp;
64 with Sem_Dist; use Sem_Dist;
65 with Sem_Elim; use Sem_Elim;
66 with Sem_Eval; use Sem_Eval;
67 with Sem_Intr; use Sem_Intr;
68 with Sem_Mech; use Sem_Mech;
69 with Sem_Res;  use Sem_Res;
70 with Sem_Type; use Sem_Type;
71 with Sem_Util; use Sem_Util;
72 with Sem_VFpt; use Sem_VFpt;
73 with Sem_Warn; use Sem_Warn;
74 with Stand;    use Stand;
75 with Sinfo;    use Sinfo;
76 with Sinfo.CN; use Sinfo.CN;
77 with Sinput;   use Sinput;
78 with Snames;   use Snames;
79 with Stringt;  use Stringt;
80 with Stylesw;  use Stylesw;
81 with Table;
82 with Targparm; use Targparm;
83 with Tbuild;   use Tbuild;
84 with Ttypes;
85 with Uintp;    use Uintp;
86 with Uname;    use Uname;
87 with Urealp;   use Urealp;
88 with Validsw;  use Validsw;
89 with Warnsw;   use Warnsw;
90
91 package body Sem_Prag is
92
93    ----------------------------------------------
94    -- Common Handling of Import-Export Pragmas --
95    ----------------------------------------------
96
97    --  In the following section, a number of Import_xxx and Export_xxx pragmas
98    --  are defined by GNAT. These are compatible with the DEC pragmas of the
99    --  same name, and all have the following common form and processing:
100
101    --  pragma Export_xxx
102    --        [Internal                 =>] LOCAL_NAME
103    --     [, [External                 =>] EXTERNAL_SYMBOL]
104    --     [, other optional parameters   ]);
105
106    --  pragma Import_xxx
107    --        [Internal                 =>] LOCAL_NAME
108    --     [, [External                 =>] EXTERNAL_SYMBOL]
109    --     [, other optional parameters   ]);
110
111    --   EXTERNAL_SYMBOL ::=
112    --     IDENTIFIER
113    --   | static_string_EXPRESSION
114
115    --  The internal LOCAL_NAME designates the entity that is imported or
116    --  exported, and must refer to an entity in the current declarative
117    --  part (as required by the rules for LOCAL_NAME).
118
119    --  The external linker name is designated by the External parameter if
120    --  given, or the Internal parameter if not (if there is no External
121    --  parameter, the External parameter is a copy of the Internal name).
122
123    --  If the External parameter is given as a string, then this string is
124    --  treated as an external name (exactly as though it had been given as an
125    --  External_Name parameter for a normal Import pragma).
126
127    --  If the External parameter is given as an identifier (or there is no
128    --  External parameter, so that the Internal identifier is used), then
129    --  the external name is the characters of the identifier, translated
130    --  to all upper case letters for OpenVMS versions of GNAT, and to all
131    --  lower case letters for all other versions
132
133    --  Note: the external name specified or implied by any of these special
134    --  Import_xxx or Export_xxx pragmas override an external or link name
135    --  specified in a previous Import or Export pragma.
136
137    --  Note: these and all other DEC-compatible GNAT pragmas allow full use of
138    --  named notation, following the standard rules for subprogram calls, i.e.
139    --  parameters can be given in any order if named notation is used, and
140    --  positional and named notation can be mixed, subject to the rule that all
141    --  positional parameters must appear first.
142
143    --  Note: All these pragmas are implemented exactly following the DEC design
144    --  and implementation and are intended to be fully compatible with the use
145    --  of these pragmas in the DEC Ada compiler.
146
147    --------------------------------------------
148    -- Checking for Duplicated External Names --
149    --------------------------------------------
150
151    --  It is suspicious if two separate Export pragmas use the same external
152    --  name. The following table is used to diagnose this situation so that
153    --  an appropriate warning can be issued.
154
155    --  The Node_Id stored is for the N_String_Literal node created to hold
156    --  the value of the external name. The Sloc of this node is used to
157    --  cross-reference the location of the duplication.
158
159    package Externals is new Table.Table (
160      Table_Component_Type => Node_Id,
161      Table_Index_Type     => Int,
162      Table_Low_Bound      => 0,
163      Table_Initial        => 100,
164      Table_Increment      => 100,
165      Table_Name           => "Name_Externals");
166
167    -------------------------------------
168    -- Local Subprograms and Variables --
169    -------------------------------------
170
171    function Adjust_External_Name_Case (N : Node_Id) return Node_Id;
172    --  This routine is used for possible casing adjustment of an explicit
173    --  external name supplied as a string literal (the node N), according to
174    --  the casing requirement of Opt.External_Name_Casing. If this is set to
175    --  As_Is, then the string literal is returned unchanged, but if it is set
176    --  to Uppercase or Lowercase, then a new string literal with appropriate
177    --  casing is constructed.
178
179    function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id;
180    --  If Def_Id refers to a renamed subprogram, then the base subprogram (the
181    --  original one, following the renaming chain) is returned. Otherwise the
182    --  entity is returned unchanged. Should be in Einfo???
183
184    procedure Preanalyze_TC_Args (N, Arg_Req, Arg_Ens : Node_Id);
185    --  Preanalyze the boolean expressions in the Requires and Ensures arguments
186    --  of a Test_Case pragma if present (possibly Empty). We treat these as
187    --  spec expressions (i.e. similar to a default expression).
188
189    procedure rv;
190    --  This is a dummy function called by the processing for pragma Reviewable.
191    --  It is there for assisting front end debugging. By placing a Reviewable
192    --  pragma in the source program, a breakpoint on rv catches this place in
193    --  the source, allowing convenient stepping to the point of interest.
194
195    procedure Set_Unit_Name (N : Node_Id; With_Item : Node_Id);
196    --  Place semantic information on the argument of an Elaborate/Elaborate_All
197    --  pragma. Entity name for unit and its parents is taken from item in
198    --  previous with_clause that mentions the unit.
199
200    -------------------------------
201    -- Adjust_External_Name_Case --
202    -------------------------------
203
204    function Adjust_External_Name_Case (N : Node_Id) return Node_Id is
205       CC : Char_Code;
206
207    begin
208       --  Adjust case of literal if required
209
210       if Opt.External_Name_Exp_Casing = As_Is then
211          return N;
212
213       else
214          --  Copy existing string
215
216          Start_String;
217
218          --  Set proper casing
219
220          for J in 1 .. String_Length (Strval (N)) loop
221             CC := Get_String_Char (Strval (N), J);
222
223             if Opt.External_Name_Exp_Casing = Uppercase
224               and then CC >= Get_Char_Code ('a')
225               and then CC <= Get_Char_Code ('z')
226             then
227                Store_String_Char (CC - 32);
228
229             elsif Opt.External_Name_Exp_Casing = Lowercase
230               and then CC >= Get_Char_Code ('A')
231               and then CC <= Get_Char_Code ('Z')
232             then
233                Store_String_Char (CC + 32);
234
235             else
236                Store_String_Char (CC);
237             end if;
238          end loop;
239
240          return
241            Make_String_Literal (Sloc (N),
242              Strval => End_String);
243       end if;
244    end Adjust_External_Name_Case;
245
246    ------------------------------
247    -- Analyze_PPC_In_Decl_Part --
248    ------------------------------
249
250    procedure Analyze_PPC_In_Decl_Part (N : Node_Id; S : Entity_Id) is
251       Arg1 : constant Node_Id := First (Pragma_Argument_Associations (N));
252
253    begin
254       --  Install formals and push subprogram spec onto scope stack so that we
255       --  can see the formals from the pragma.
256
257       Install_Formals (S);
258       Push_Scope (S);
259
260       --  Preanalyze the boolean expression, we treat this as a spec expression
261       --  (i.e. similar to a default expression).
262
263       Preanalyze_Spec_Expression (Get_Pragma_Arg (Arg1), Standard_Boolean);
264
265       --  In ASIS mode, for a pragma generated from a source aspect, also
266       --  analyze the original aspect expression.
267
268       if ASIS_Mode
269         and then Present (Corresponding_Aspect (N))
270       then
271          Preanalyze_Spec_Expression
272            (Expression (Corresponding_Aspect (N)), Standard_Boolean);
273       end if;
274
275       --  For a class-wide condition, a reference to a controlling formal must
276       --  be interpreted as having the class-wide type (or an access to such)
277       --  so that the inherited condition can be properly applied to any
278       --  overriding operation (see ARM12 6.6.1 (7)).
279
280       if Class_Present (N) then
281          declare
282             T   : constant Entity_Id := Find_Dispatching_Type (S);
283
284             ACW : Entity_Id := Empty;
285             --  Access to T'class, created if there is a controlling formal
286             --  that is an access parameter.
287
288             function Get_ACW return Entity_Id;
289             --  If the expression has a reference to an controlling access
290             --  parameter, create an access to T'class for the necessary
291             --  conversions if one does not exist.
292
293             function Process (N : Node_Id) return Traverse_Result;
294             --  ARM 6.1.1: Within the expression for a Pre'Class or Post'Class
295             --  aspect for a primitive subprogram of a tagged type T, a name
296             --  that denotes a formal parameter of type T is interpreted as
297             --  having type T'Class. Similarly, a name that denotes a formal
298             --  accessparameter of type access-to-T is interpreted as having
299             --  type access-to-T'Class. This ensures the expression is well-
300             --  defined for a primitive subprogram of a type descended from T.
301
302             -------------
303             -- Get_ACW --
304             -------------
305
306             function Get_ACW return Entity_Id is
307                Loc  : constant Source_Ptr := Sloc (N);
308                Decl : Node_Id;
309
310             begin
311                if No (ACW) then
312                   Decl := Make_Full_Type_Declaration (Loc,
313                     Defining_Identifier => Make_Temporary (Loc, 'T'),
314                     Type_Definition =>
315                        Make_Access_To_Object_Definition (Loc,
316                        Subtype_Indication =>
317                          New_Occurrence_Of (Class_Wide_Type (T), Loc),
318                        All_Present => True));
319
320                   Insert_Before (Unit_Declaration_Node (S), Decl);
321                   Analyze (Decl);
322                   ACW := Defining_Identifier (Decl);
323                   Freeze_Before (Unit_Declaration_Node (S), ACW);
324                end if;
325
326                return ACW;
327             end Get_ACW;
328
329             -------------
330             -- Process --
331             -------------
332
333             function Process (N : Node_Id) return Traverse_Result is
334                Loc : constant Source_Ptr := Sloc (N);
335                Typ : Entity_Id;
336
337             begin
338                if Is_Entity_Name (N)
339                  and then Is_Formal (Entity (N))
340                  and then Nkind (Parent (N)) /= N_Type_Conversion
341                then
342                   if Etype (Entity (N)) = T then
343                      Typ := Class_Wide_Type (T);
344
345                   elsif Is_Access_Type (Etype (Entity (N)))
346                     and then Designated_Type (Etype (Entity (N))) = T
347                   then
348                      Typ := Get_ACW;
349                   else
350                      Typ := Empty;
351                   end if;
352
353                   if Present (Typ) then
354                      Rewrite (N,
355                        Make_Type_Conversion (Loc,
356                          Subtype_Mark =>
357                            New_Occurrence_Of (Typ, Loc),
358                          Expression  => New_Occurrence_Of (Entity (N), Loc)));
359                      Set_Etype (N, Typ);
360                   end if;
361                end if;
362
363                return OK;
364             end Process;
365
366             procedure Replace_Type is new Traverse_Proc (Process);
367
368          begin
369             Replace_Type (Get_Pragma_Arg (Arg1));
370          end;
371       end if;
372
373       --  Remove the subprogram from the scope stack now that the pre-analysis
374       --  of the precondition/postcondition is done.
375
376       End_Scope;
377    end Analyze_PPC_In_Decl_Part;
378
379    --------------------
380    -- Analyze_Pragma --
381    --------------------
382
383    procedure Analyze_Pragma (N : Node_Id) is
384       Loc     : constant Source_Ptr := Sloc (N);
385       Prag_Id : Pragma_Id;
386
387       Pname : Name_Id;
388       --  Name of the source pragma, or name of the corresponding aspect for
389       --  pragmas which originate in a source aspect. In the latter case, the
390       --  name may be different from the pragma name.
391
392       Pragma_Exit : exception;
393       --  This exception is used to exit pragma processing completely. It is
394       --  used when an error is detected, and no further processing is
395       --  required. It is also used if an earlier error has left the tree in
396       --  a state where the pragma should not be processed.
397
398       Arg_Count : Nat;
399       --  Number of pragma argument associations
400
401       Arg1 : Node_Id;
402       Arg2 : Node_Id;
403       Arg3 : Node_Id;
404       Arg4 : Node_Id;
405       --  First four pragma arguments (pragma argument association nodes, or
406       --  Empty if the corresponding argument does not exist).
407
408       type Name_List is array (Natural range <>) of Name_Id;
409       type Args_List is array (Natural range <>) of Node_Id;
410       --  Types used for arguments to Check_Arg_Order and Gather_Associations
411
412       procedure Ada_2005_Pragma;
413       --  Called for pragmas defined in Ada 2005, that are not in Ada 95. In
414       --  Ada 95 mode, these are implementation defined pragmas, so should be
415       --  caught by the No_Implementation_Pragmas restriction.
416
417       procedure Ada_2012_Pragma;
418       --  Called for pragmas defined in Ada 2012, that are not in Ada 95 or 05.
419       --  In Ada 95 or 05 mode, these are implementation defined pragmas, so
420       --  should be caught by the No_Implementation_Pragmas restriction.
421
422       procedure Check_Ada_83_Warning;
423       --  Issues a warning message for the current pragma if operating in Ada
424       --  83 mode (used for language pragmas that are not a standard part of
425       --  Ada 83). This procedure does not raise Error_Pragma. Also notes use
426       --  of 95 pragma.
427
428       procedure Check_Arg_Count (Required : Nat);
429       --  Check argument count for pragma is equal to given parameter. If not,
430       --  then issue an error message and raise Pragma_Exit.
431
432       --  Note: all routines whose name is Check_Arg_Is_xxx take an argument
433       --  Arg which can either be a pragma argument association, in which case
434       --  the check is applied to the expression of the association or an
435       --  expression directly.
436
437       procedure Check_Arg_Is_External_Name (Arg : Node_Id);
438       --  Check that an argument has the right form for an EXTERNAL_NAME
439       --  parameter of an extended import/export pragma. The rule is that the
440       --  name must be an identifier or string literal (in Ada 83 mode) or a
441       --  static string expression (in Ada 95 mode).
442
443       procedure Check_Arg_Is_Identifier (Arg : Node_Id);
444       --  Check the specified argument Arg to make sure that it is an
445       --  identifier. If not give error and raise Pragma_Exit.
446
447       procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id);
448       --  Check the specified argument Arg to make sure that it is an integer
449       --  literal. If not give error and raise Pragma_Exit.
450
451       procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id);
452       --  Check the specified argument Arg to make sure that it has the proper
453       --  syntactic form for a local name and meets the semantic requirements
454       --  for a local name. The local name is analyzed as part of the
455       --  processing for this call. In addition, the local name is required
456       --  to represent an entity at the library level.
457
458       procedure Check_Arg_Is_Local_Name (Arg : Node_Id);
459       --  Check the specified argument Arg to make sure that it has the proper
460       --  syntactic form for a local name and meets the semantic requirements
461       --  for a local name. The local name is analyzed as part of the
462       --  processing for this call.
463
464       procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id);
465       --  Check the specified argument Arg to make sure that it is a valid
466       --  locking policy name. If not give error and raise Pragma_Exit.
467
468       procedure Check_Arg_Is_One_Of
469         (Arg                : Node_Id;
470          N1, N2             : Name_Id);
471       procedure Check_Arg_Is_One_Of
472         (Arg                : Node_Id;
473          N1, N2, N3         : Name_Id);
474       procedure Check_Arg_Is_One_Of
475         (Arg                : Node_Id;
476          N1, N2, N3, N4, N5 : Name_Id);
477       --  Check the specified argument Arg to make sure that it is an
478       --  identifier whose name matches either N1 or N2 (or N3, N4, N5 if
479       --  present). If not then give error and raise Pragma_Exit.
480
481       procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id);
482       --  Check the specified argument Arg to make sure that it is a valid
483       --  queuing policy name. If not give error and raise Pragma_Exit.
484
485       procedure Check_Arg_Is_Static_Expression
486         (Arg : Node_Id;
487          Typ : Entity_Id := Empty);
488       --  Check the specified argument Arg to make sure that it is a static
489       --  expression of the given type (i.e. it will be analyzed and resolved
490       --  using this type, which can be any valid argument to Resolve, e.g.
491       --  Any_Integer is OK). If not, given error and raise Pragma_Exit. If
492       --  Typ is left Empty, then any static expression is allowed.
493
494       procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id);
495       --  Check the specified argument Arg to make sure that it is a valid task
496       --  dispatching policy name. If not give error and raise Pragma_Exit.
497
498       procedure Check_Arg_Order (Names : Name_List);
499       --  Checks for an instance of two arguments with identifiers for the
500       --  current pragma which are not in the sequence indicated by Names,
501       --  and if so, generates a fatal message about bad order of arguments.
502
503       procedure Check_At_Least_N_Arguments (N : Nat);
504       --  Check there are at least N arguments present
505
506       procedure Check_At_Most_N_Arguments (N : Nat);
507       --  Check there are no more than N arguments present
508
509       procedure Check_Component
510         (Comp            : Node_Id;
511          UU_Typ          : Entity_Id;
512          In_Variant_Part : Boolean := False);
513       --  Examine an Unchecked_Union component for correct use of per-object
514       --  constrained subtypes, and for restrictions on finalizable components.
515       --  UU_Typ is the related Unchecked_Union type. Flag In_Variant_Part
516       --  should be set when Comp comes from a record variant.
517
518       procedure Check_Duplicate_Pragma (E : Entity_Id);
519       --  Check if a pragma of the same name as the current pragma is already
520       --  chained as a rep pragma to the given entity. If so give a message
521       --  about the duplicate, and then raise Pragma_Exit so does not return.
522       --  Also checks for delayed aspect specification node in the chain.
523
524       procedure Check_Duplicated_Export_Name (Nam : Node_Id);
525       --  Nam is an N_String_Literal node containing the external name set by
526       --  an Import or Export pragma (or extended Import or Export pragma).
527       --  This procedure checks for possible duplications if this is the export
528       --  case, and if found, issues an appropriate error message.
529
530       procedure Check_Expr_Is_Static_Expression
531         (Expr : Node_Id;
532          Typ  : Entity_Id := Empty);
533       --  Check the specified expression Expr to make sure that it is a static
534       --  expression of the given type (i.e. it will be analyzed and resolved
535       --  using this type, which can be any valid argument to Resolve, e.g.
536       --  Any_Integer is OK). If not, given error and raise Pragma_Exit. If
537       --  Typ is left Empty, then any static expression is allowed.
538
539       procedure Check_First_Subtype (Arg : Node_Id);
540       --  Checks that Arg, whose expression is an entity name, references a
541       --  first subtype.
542
543       procedure Check_Identifier (Arg : Node_Id; Id : Name_Id);
544       --  Checks that the given argument has an identifier, and if so, requires
545       --  it to match the given identifier name. If there is no identifier, or
546       --  a non-matching identifier, then an error message is given and
547       --  Pragma_Exit is raised.
548
549       procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id);
550       --  Checks that the given argument has an identifier, and if so, requires
551       --  it to match one of the given identifier names. If there is no
552       --  identifier, or a non-matching identifier, then an error message is
553       --  given and Pragma_Exit is raised.
554
555       procedure Check_In_Main_Program;
556       --  Common checks for pragmas that appear within a main program
557       --  (Priority, Main_Storage, Time_Slice, Relative_Deadline, CPU).
558
559       procedure Check_Interrupt_Or_Attach_Handler;
560       --  Common processing for first argument of pragma Interrupt_Handler or
561       --  pragma Attach_Handler.
562
563       procedure Check_Is_In_Decl_Part_Or_Package_Spec;
564       --  Check that pragma appears in a declarative part, or in a package
565       --  specification, i.e. that it does not occur in a statement sequence
566       --  in a body.
567
568       procedure Check_No_Identifier (Arg : Node_Id);
569       --  Checks that the given argument does not have an identifier. If
570       --  an identifier is present, then an error message is issued, and
571       --  Pragma_Exit is raised.
572
573       procedure Check_No_Identifiers;
574       --  Checks that none of the arguments to the pragma has an identifier.
575       --  If any argument has an identifier, then an error message is issued,
576       --  and Pragma_Exit is raised.
577
578       procedure Check_No_Link_Name;
579       --  Checks that no link name is specified
580
581       procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id);
582       --  Checks if the given argument has an identifier, and if so, requires
583       --  it to match the given identifier name. If there is a non-matching
584       --  identifier, then an error message is given and Pragma_Exit is raised.
585
586       procedure Check_Optional_Identifier (Arg : Node_Id; Id : String);
587       --  Checks if the given argument has an identifier, and if so, requires
588       --  it to match the given identifier name. If there is a non-matching
589       --  identifier, then an error message is given and Pragma_Exit is raised.
590       --  In this version of the procedure, the identifier name is given as
591       --  a string with lower case letters.
592
593       procedure Check_Precondition_Postcondition (In_Body : out Boolean);
594       --  Called to process a precondition or postcondition pragma. There are
595       --  three cases:
596       --
597       --    The pragma appears after a subprogram spec
598       --
599       --      If the corresponding check is not enabled, the pragma is analyzed
600       --      but otherwise ignored and control returns with In_Body set False.
601       --
602       --      If the check is enabled, then the first step is to analyze the
603       --      pragma, but this is skipped if the subprogram spec appears within
604       --      a package specification (because this is the case where we delay
605       --      analysis till the end of the spec). Then (whether or not it was
606       --      analyzed), the pragma is chained to the subprogram in question
607       --      (using Spec_PPC_List and Next_Pragma) and control returns to the
608       --      caller with In_Body set False.
609       --
610       --    The pragma appears at the start of subprogram body declarations
611       --
612       --      In this case an immediate return to the caller is made with
613       --      In_Body set True, and the pragma is NOT analyzed.
614       --
615       --    In all other cases, an error message for bad placement is given
616
617       procedure Check_Static_Constraint (Constr : Node_Id);
618       --  Constr is a constraint from an N_Subtype_Indication node from a
619       --  component constraint in an Unchecked_Union type. This routine checks
620       --  that the constraint is static as required by the restrictions for
621       --  Unchecked_Union.
622
623       procedure Check_Test_Case;
624       --  Called to process a test-case pragma. The treatment is similar to the
625       --  one for pre- and postcondition in Check_Precondition_Postcondition,
626       --  except the placement rules for the test-case pragma are stricter.
627       --  This pragma may only occur after a subprogram spec declared directly
628       --  in a package spec unit. In this case, the pragma is chained to the
629       --  subprogram in question (using Spec_TC_List and Next_Pragma) and
630       --  analysis of the pragma is delayed till the end of the spec. In
631       --  all other cases, an error message for bad placement is given.
632
633       procedure Check_Valid_Configuration_Pragma;
634       --  Legality checks for placement of a configuration pragma
635
636       procedure Check_Valid_Library_Unit_Pragma;
637       --  Legality checks for library unit pragmas. A special case arises for
638       --  pragmas in generic instances that come from copies of the original
639       --  library unit pragmas in the generic templates. In the case of other
640       --  than library level instantiations these can appear in contexts which
641       --  would normally be invalid (they only apply to the original template
642       --  and to library level instantiations), and they are simply ignored,
643       --  which is implemented by rewriting them as null statements.
644
645       procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id);
646       --  Check an Unchecked_Union variant for lack of nested variants and
647       --  presence of at least one component. UU_Typ is the related Unchecked_
648       --  Union type.
649
650       procedure Error_Pragma (Msg : String);
651       pragma No_Return (Error_Pragma);
652       --  Outputs error message for current pragma. The message contains a %
653       --  that will be replaced with the pragma name, and the flag is placed
654       --  on the pragma itself. Pragma_Exit is then raised.
655
656       procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id);
657       pragma No_Return (Error_Pragma_Arg);
658       --  Outputs error message for current pragma. The message may contain
659       --  a % that will be replaced with the pragma name. The parameter Arg
660       --  may either be a pragma argument association, in which case the flag
661       --  is placed on the expression of this association, or an expression,
662       --  in which case the flag is placed directly on the expression. The
663       --  message is placed using Error_Msg_N, so the message may also contain
664       --  an & insertion character which will reference the given Arg value.
665       --  After placing the message, Pragma_Exit is raised.
666
667       procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id);
668       pragma No_Return (Error_Pragma_Arg);
669       --  Similar to above form of Error_Pragma_Arg except that two messages
670       --  are provided, the second is a continuation comment starting with \.
671
672       procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id);
673       pragma No_Return (Error_Pragma_Arg_Ident);
674       --  Outputs error message for current pragma. The message may contain
675       --  a % that will be replaced with the pragma name. The parameter Arg
676       --  must be a pragma argument association with a non-empty identifier
677       --  (i.e. its Chars field must be set), and the error message is placed
678       --  on the identifier. The message is placed using Error_Msg_N so
679       --  the message may also contain an & insertion character which will
680       --  reference the identifier. After placing the message, Pragma_Exit
681       --  is raised.
682
683       procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id);
684       pragma No_Return (Error_Pragma_Ref);
685       --  Outputs error message for current pragma. The message may contain
686       --  a % that will be replaced with the pragma name. The parameter Ref
687       --  must be an entity whose name can be referenced by & and sloc by #.
688       --  After placing the message, Pragma_Exit is raised.
689
690       function Find_Lib_Unit_Name return Entity_Id;
691       --  Used for a library unit pragma to find the entity to which the
692       --  library unit pragma applies, returns the entity found.
693
694       procedure Find_Program_Unit_Name (Id : Node_Id);
695       --  If the pragma is a compilation unit pragma, the id must denote the
696       --  compilation unit in the same compilation, and the pragma must appear
697       --  in the list of preceding or trailing pragmas. If it is a program
698       --  unit pragma that is not a compilation unit pragma, then the
699       --  identifier must be visible.
700
701       function Find_Unique_Parameterless_Procedure
702         (Name : Entity_Id;
703          Arg  : Node_Id) return Entity_Id;
704       --  Used for a procedure pragma to find the unique parameterless
705       --  procedure identified by Name, returns it if it exists, otherwise
706       --  errors out and uses Arg as the pragma argument for the message.
707
708       procedure Fix_Error (Msg : in out String);
709       --  This is called prior to issuing an error message. Msg is a string
710       --  which typically contains the substring pragma. If the current pragma
711       --  comes from an aspect, each such "pragma" substring is replaced with
712       --  the characters "aspect", and if Error_Msg_Name_1 is Name_Precondition
713       --  (resp Name_Postcondition) it is changed to Name_Pre (resp Name_Post).
714
715       procedure Gather_Associations
716         (Names : Name_List;
717          Args  : out Args_List);
718       --  This procedure is used to gather the arguments for a pragma that
719       --  permits arbitrary ordering of parameters using the normal rules
720       --  for named and positional parameters. The Names argument is a list
721       --  of Name_Id values that corresponds to the allowed pragma argument
722       --  association identifiers in order. The result returned in Args is
723       --  a list of corresponding expressions that are the pragma arguments.
724       --  Note that this is a list of expressions, not of pragma argument
725       --  associations (Gather_Associations has completely checked all the
726       --  optional identifiers when it returns). An entry in Args is Empty
727       --  on return if the corresponding argument is not present.
728
729       procedure GNAT_Pragma;
730       --  Called for all GNAT defined pragmas to check the relevant restriction
731       --  (No_Implementation_Pragmas).
732
733       function Is_Before_First_Decl
734         (Pragma_Node : Node_Id;
735          Decls       : List_Id) return Boolean;
736       --  Return True if Pragma_Node is before the first declarative item in
737       --  Decls where Decls is the list of declarative items.
738
739       function Is_Configuration_Pragma return Boolean;
740       --  Determines if the placement of the current pragma is appropriate
741       --  for a configuration pragma.
742
743       function Is_In_Context_Clause return Boolean;
744       --  Returns True if pragma appears within the context clause of a unit,
745       --  and False for any other placement (does not generate any messages).
746
747       function Is_Static_String_Expression (Arg : Node_Id) return Boolean;
748       --  Analyzes the argument, and determines if it is a static string
749       --  expression, returns True if so, False if non-static or not String.
750
751       procedure Pragma_Misplaced;
752       pragma No_Return (Pragma_Misplaced);
753       --  Issue fatal error message for misplaced pragma
754
755       procedure Process_Atomic_Shared_Volatile;
756       --  Common processing for pragmas Atomic, Shared, Volatile. Note that
757       --  Shared is an obsolete Ada 83 pragma, treated as being identical
758       --  in effect to pragma Atomic.
759
760       procedure Process_Compile_Time_Warning_Or_Error;
761       --  Common processing for Compile_Time_Error and Compile_Time_Warning
762
763       procedure Process_Convention
764         (C   : out Convention_Id;
765          Ent : out Entity_Id);
766       --  Common processing for Convention, Interface, Import and Export.
767       --  Checks first two arguments of pragma, and sets the appropriate
768       --  convention value in the specified entity or entities. On return
769       --  C is the convention, Ent is the referenced entity.
770
771       procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id);
772       --  Common processing for Disable/Enable_Atomic_Synchronization. Nam is
773       --  Name_Suppress for Disable and Name_Unsuppress for Enable.
774
775       procedure Process_Extended_Import_Export_Exception_Pragma
776         (Arg_Internal : Node_Id;
777          Arg_External : Node_Id;
778          Arg_Form     : Node_Id;
779          Arg_Code     : Node_Id);
780       --  Common processing for the pragmas Import/Export_Exception. The three
781       --  arguments correspond to the three named parameters of the pragma. An
782       --  argument is empty if the corresponding parameter is not present in
783       --  the pragma.
784
785       procedure Process_Extended_Import_Export_Object_Pragma
786         (Arg_Internal : Node_Id;
787          Arg_External : Node_Id;
788          Arg_Size     : Node_Id);
789       --  Common processing for the pragmas Import/Export_Object. The three
790       --  arguments correspond to the three named parameters of the pragmas. An
791       --  argument is empty if the corresponding parameter is not present in
792       --  the pragma.
793
794       procedure Process_Extended_Import_Export_Internal_Arg
795         (Arg_Internal : Node_Id := Empty);
796       --  Common processing for all extended Import and Export pragmas. The
797       --  argument is the pragma parameter for the Internal argument. If
798       --  Arg_Internal is empty or inappropriate, an error message is posted.
799       --  Otherwise, on normal return, the Entity_Field of Arg_Internal is
800       --  set to identify the referenced entity.
801
802       procedure Process_Extended_Import_Export_Subprogram_Pragma
803         (Arg_Internal                 : Node_Id;
804          Arg_External                 : Node_Id;
805          Arg_Parameter_Types          : Node_Id;
806          Arg_Result_Type              : Node_Id := Empty;
807          Arg_Mechanism                : Node_Id;
808          Arg_Result_Mechanism         : Node_Id := Empty;
809          Arg_First_Optional_Parameter : Node_Id := Empty);
810       --  Common processing for all extended Import and Export pragmas applying
811       --  to subprograms. The caller omits any arguments that do not apply to
812       --  the pragma in question (for example, Arg_Result_Type can be non-Empty
813       --  only in the Import_Function and Export_Function cases). The argument
814       --  names correspond to the allowed pragma association identifiers.
815
816       procedure Process_Generic_List;
817       --  Common processing for Share_Generic and Inline_Generic
818
819       procedure Process_Import_Or_Interface;
820       --  Common processing for Import of Interface
821
822       procedure Process_Import_Predefined_Type;
823       --  Processing for completing a type with pragma Import. This is used
824       --  to declare types that match predefined C types, especially for cases
825       --  without corresponding Ada predefined type.
826
827       procedure Process_Inline (Active : Boolean);
828       --  Common processing for Inline and Inline_Always. The parameter
829       --  indicates if the inline pragma is active, i.e. if it should actually
830       --  cause inlining to occur.
831
832       procedure Process_Interface_Name
833         (Subprogram_Def : Entity_Id;
834          Ext_Arg        : Node_Id;
835          Link_Arg       : Node_Id);
836       --  Given the last two arguments of pragma Import, pragma Export, or
837       --  pragma Interface_Name, performs validity checks and sets the
838       --  Interface_Name field of the given subprogram entity to the
839       --  appropriate external or link name, depending on the arguments given.
840       --  Ext_Arg is always present, but Link_Arg may be missing. Note that
841       --  Ext_Arg may represent the Link_Name if Link_Arg is missing, and
842       --  appropriate named notation is used for Ext_Arg. If neither Ext_Arg
843       --  nor Link_Arg is present, the interface name is set to the default
844       --  from the subprogram name.
845
846       procedure Process_Interrupt_Or_Attach_Handler;
847       --  Common processing for Interrupt and Attach_Handler pragmas
848
849       procedure Process_Restrictions_Or_Restriction_Warnings (Warn : Boolean);
850       --  Common processing for Restrictions and Restriction_Warnings pragmas.
851       --  Warn is True for Restriction_Warnings, or for Restrictions if the
852       --  flag Treat_Restrictions_As_Warnings is set, and False if this flag
853       --  is not set in the Restrictions case.
854
855       procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean);
856       --  Common processing for Suppress and Unsuppress. The boolean parameter
857       --  Suppress_Case is True for the Suppress case, and False for the
858       --  Unsuppress case.
859
860       procedure Set_Exported (E : Entity_Id; Arg : Node_Id);
861       --  This procedure sets the Is_Exported flag for the given entity,
862       --  checking that the entity was not previously imported. Arg is
863       --  the argument that specified the entity. A check is also made
864       --  for exporting inappropriate entities.
865
866       procedure Set_Extended_Import_Export_External_Name
867         (Internal_Ent : Entity_Id;
868          Arg_External : Node_Id);
869       --  Common processing for all extended import export pragmas. The first
870       --  argument, Internal_Ent, is the internal entity, which has already
871       --  been checked for validity by the caller. Arg_External is from the
872       --  Import or Export pragma, and may be null if no External parameter
873       --  was present. If Arg_External is present and is a non-null string
874       --  (a null string is treated as the default), then the Interface_Name
875       --  field of Internal_Ent is set appropriately.
876
877       procedure Set_Imported (E : Entity_Id);
878       --  This procedure sets the Is_Imported flag for the given entity,
879       --  checking that it is not previously exported or imported.
880
881       procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id);
882       --  Mech is a parameter passing mechanism (see Import_Function syntax
883       --  for MECHANISM_NAME). This routine checks that the mechanism argument
884       --  has the right form, and if not issues an error message. If the
885       --  argument has the right form then the Mechanism field of Ent is
886       --  set appropriately.
887
888       procedure Set_Ravenscar_Profile (N : Node_Id);
889       --  Activate the set of configuration pragmas and restrictions that make
890       --  up the Ravenscar Profile. N is the corresponding pragma node, which
891       --  is used for error messages on any constructs that violate the
892       --  profile.
893
894       ---------------------
895       -- Ada_2005_Pragma --
896       ---------------------
897
898       procedure Ada_2005_Pragma is
899       begin
900          if Ada_Version <= Ada_95 then
901             Check_Restriction (No_Implementation_Pragmas, N);
902          end if;
903       end Ada_2005_Pragma;
904
905       ---------------------
906       -- Ada_2012_Pragma --
907       ---------------------
908
909       procedure Ada_2012_Pragma is
910       begin
911          if Ada_Version <= Ada_2005 then
912             Check_Restriction (No_Implementation_Pragmas, N);
913          end if;
914       end Ada_2012_Pragma;
915
916       --------------------------
917       -- Check_Ada_83_Warning --
918       --------------------------
919
920       procedure Check_Ada_83_Warning is
921       begin
922          if Ada_Version = Ada_83 and then Comes_From_Source (N) then
923             Error_Msg_N ("(Ada 83) pragma& is non-standard?", N);
924          end if;
925       end Check_Ada_83_Warning;
926
927       ---------------------
928       -- Check_Arg_Count --
929       ---------------------
930
931       procedure Check_Arg_Count (Required : Nat) is
932       begin
933          if Arg_Count /= Required then
934             Error_Pragma ("wrong number of arguments for pragma%");
935          end if;
936       end Check_Arg_Count;
937
938       --------------------------------
939       -- Check_Arg_Is_External_Name --
940       --------------------------------
941
942       procedure Check_Arg_Is_External_Name (Arg : Node_Id) is
943          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
944
945       begin
946          if Nkind (Argx) = N_Identifier then
947             return;
948
949          else
950             Analyze_And_Resolve (Argx, Standard_String);
951
952             if Is_OK_Static_Expression (Argx) then
953                return;
954
955             elsif Etype (Argx) = Any_Type then
956                raise Pragma_Exit;
957
958             --  An interesting special case, if we have a string literal and
959             --  we are in Ada 83 mode, then we allow it even though it will
960             --  not be flagged as static. This allows expected Ada 83 mode
961             --  use of external names which are string literals, even though
962             --  technically these are not static in Ada 83.
963
964             elsif Ada_Version = Ada_83
965               and then Nkind (Argx) = N_String_Literal
966             then
967                return;
968
969             --  Static expression that raises Constraint_Error. This has
970             --  already been flagged, so just exit from pragma processing.
971
972             elsif Is_Static_Expression (Argx) then
973                raise Pragma_Exit;
974
975             --  Here we have a real error (non-static expression)
976
977             else
978                Error_Msg_Name_1 := Pname;
979
980                declare
981                   Msg : String :=
982                           "argument for pragma% must be a identifier or "
983                           & "static string expression!";
984                begin
985                   Fix_Error (Msg);
986                   Flag_Non_Static_Expr (Msg, Argx);
987                   raise Pragma_Exit;
988                end;
989             end if;
990          end if;
991       end Check_Arg_Is_External_Name;
992
993       -----------------------------
994       -- Check_Arg_Is_Identifier --
995       -----------------------------
996
997       procedure Check_Arg_Is_Identifier (Arg : Node_Id) is
998          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
999       begin
1000          if Nkind (Argx) /= N_Identifier then
1001             Error_Pragma_Arg
1002               ("argument for pragma% must be identifier", Argx);
1003          end if;
1004       end Check_Arg_Is_Identifier;
1005
1006       ----------------------------------
1007       -- Check_Arg_Is_Integer_Literal --
1008       ----------------------------------
1009
1010       procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id) is
1011          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1012       begin
1013          if Nkind (Argx) /= N_Integer_Literal then
1014             Error_Pragma_Arg
1015               ("argument for pragma% must be integer literal", Argx);
1016          end if;
1017       end Check_Arg_Is_Integer_Literal;
1018
1019       -------------------------------------------
1020       -- Check_Arg_Is_Library_Level_Local_Name --
1021       -------------------------------------------
1022
1023       --  LOCAL_NAME ::=
1024       --    DIRECT_NAME
1025       --  | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
1026       --  | library_unit_NAME
1027
1028       procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id) is
1029       begin
1030          Check_Arg_Is_Local_Name (Arg);
1031
1032          if not Is_Library_Level_Entity (Entity (Get_Pragma_Arg (Arg)))
1033            and then Comes_From_Source (N)
1034          then
1035             Error_Pragma_Arg
1036               ("argument for pragma% must be library level entity", Arg);
1037          end if;
1038       end Check_Arg_Is_Library_Level_Local_Name;
1039
1040       -----------------------------
1041       -- Check_Arg_Is_Local_Name --
1042       -----------------------------
1043
1044       --  LOCAL_NAME ::=
1045       --    DIRECT_NAME
1046       --  | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
1047       --  | library_unit_NAME
1048
1049       procedure Check_Arg_Is_Local_Name (Arg : Node_Id) is
1050          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1051
1052       begin
1053          Analyze (Argx);
1054
1055          if Nkind (Argx) not in N_Direct_Name
1056            and then (Nkind (Argx) /= N_Attribute_Reference
1057                       or else Present (Expressions (Argx))
1058                       or else Nkind (Prefix (Argx)) /= N_Identifier)
1059            and then (not Is_Entity_Name (Argx)
1060                       or else not Is_Compilation_Unit (Entity (Argx)))
1061          then
1062             Error_Pragma_Arg ("argument for pragma% must be local name", Argx);
1063          end if;
1064
1065          --  No further check required if not an entity name
1066
1067          if not Is_Entity_Name (Argx) then
1068             null;
1069
1070          else
1071             declare
1072                OK   : Boolean;
1073                Ent  : constant Entity_Id := Entity (Argx);
1074                Scop : constant Entity_Id := Scope (Ent);
1075             begin
1076                --  Case of a pragma applied to a compilation unit: pragma must
1077                --  occur immediately after the program unit in the compilation.
1078
1079                if Is_Compilation_Unit (Ent) then
1080                   declare
1081                      Decl : constant Node_Id := Unit_Declaration_Node (Ent);
1082
1083                   begin
1084                      --  Case of pragma placed immediately after spec
1085
1086                      if Parent (N) = Aux_Decls_Node (Parent (Decl)) then
1087                         OK := True;
1088
1089                      --  Case of pragma placed immediately after body
1090
1091                      elsif Nkind (Decl) = N_Subprogram_Declaration
1092                              and then Present (Corresponding_Body (Decl))
1093                      then
1094                         OK := Parent (N) =
1095                                 Aux_Decls_Node
1096                                   (Parent (Unit_Declaration_Node
1097                                              (Corresponding_Body (Decl))));
1098
1099                      --  All other cases are illegal
1100
1101                      else
1102                         OK := False;
1103                      end if;
1104                   end;
1105
1106                --  Special restricted placement rule from 10.2.1(11.8/2)
1107
1108                elsif Is_Generic_Formal (Ent)
1109                        and then Prag_Id = Pragma_Preelaborable_Initialization
1110                then
1111                   OK := List_Containing (N) =
1112                           Generic_Formal_Declarations
1113                             (Unit_Declaration_Node (Scop));
1114
1115                --  Default case, just check that the pragma occurs in the scope
1116                --  of the entity denoted by the name.
1117
1118                else
1119                   OK := Current_Scope = Scop;
1120                end if;
1121
1122                if not OK then
1123                   Error_Pragma_Arg
1124                     ("pragma% argument must be in same declarative part", Arg);
1125                end if;
1126             end;
1127          end if;
1128       end Check_Arg_Is_Local_Name;
1129
1130       ---------------------------------
1131       -- Check_Arg_Is_Locking_Policy --
1132       ---------------------------------
1133
1134       procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id) is
1135          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1136
1137       begin
1138          Check_Arg_Is_Identifier (Argx);
1139
1140          if not Is_Locking_Policy_Name (Chars (Argx)) then
1141             Error_Pragma_Arg ("& is not a valid locking policy name", Argx);
1142          end if;
1143       end Check_Arg_Is_Locking_Policy;
1144
1145       -------------------------
1146       -- Check_Arg_Is_One_Of --
1147       -------------------------
1148
1149       procedure Check_Arg_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
1150          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1151
1152       begin
1153          Check_Arg_Is_Identifier (Argx);
1154
1155          if Chars (Argx) /= N1 and then Chars (Argx) /= N2 then
1156             Error_Msg_Name_2 := N1;
1157             Error_Msg_Name_3 := N2;
1158             Error_Pragma_Arg ("argument for pragma% must be% or%", Argx);
1159          end if;
1160       end Check_Arg_Is_One_Of;
1161
1162       procedure Check_Arg_Is_One_Of
1163         (Arg        : Node_Id;
1164          N1, N2, N3 : Name_Id)
1165       is
1166          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1167
1168       begin
1169          Check_Arg_Is_Identifier (Argx);
1170
1171          if Chars (Argx) /= N1
1172            and then Chars (Argx) /= N2
1173            and then Chars (Argx) /= N3
1174          then
1175             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1176          end if;
1177       end Check_Arg_Is_One_Of;
1178
1179       procedure Check_Arg_Is_One_Of
1180         (Arg                : Node_Id;
1181          N1, N2, N3, N4, N5 : Name_Id)
1182       is
1183          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1184
1185       begin
1186          Check_Arg_Is_Identifier (Argx);
1187
1188          if Chars (Argx) /= N1
1189            and then Chars (Argx) /= N2
1190            and then Chars (Argx) /= N3
1191            and then Chars (Argx) /= N4
1192            and then Chars (Argx) /= N5
1193          then
1194             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1195          end if;
1196       end Check_Arg_Is_One_Of;
1197       ---------------------------------
1198       -- Check_Arg_Is_Queuing_Policy --
1199       ---------------------------------
1200
1201       procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id) is
1202          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1203
1204       begin
1205          Check_Arg_Is_Identifier (Argx);
1206
1207          if not Is_Queuing_Policy_Name (Chars (Argx)) then
1208             Error_Pragma_Arg ("& is not a valid queuing policy name", Argx);
1209          end if;
1210       end Check_Arg_Is_Queuing_Policy;
1211
1212       ------------------------------------
1213       -- Check_Arg_Is_Static_Expression --
1214       ------------------------------------
1215
1216       procedure Check_Arg_Is_Static_Expression
1217         (Arg : Node_Id;
1218          Typ : Entity_Id := Empty)
1219       is
1220       begin
1221          Check_Expr_Is_Static_Expression (Get_Pragma_Arg (Arg), Typ);
1222       end Check_Arg_Is_Static_Expression;
1223
1224       ------------------------------------------
1225       -- Check_Arg_Is_Task_Dispatching_Policy --
1226       ------------------------------------------
1227
1228       procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id) is
1229          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1230
1231       begin
1232          Check_Arg_Is_Identifier (Argx);
1233
1234          if not Is_Task_Dispatching_Policy_Name (Chars (Argx)) then
1235             Error_Pragma_Arg
1236               ("& is not a valid task dispatching policy name", Argx);
1237          end if;
1238       end Check_Arg_Is_Task_Dispatching_Policy;
1239
1240       ---------------------
1241       -- Check_Arg_Order --
1242       ---------------------
1243
1244       procedure Check_Arg_Order (Names : Name_List) is
1245          Arg : Node_Id;
1246
1247          Highest_So_Far : Natural := 0;
1248          --  Highest index in Names seen do far
1249
1250       begin
1251          Arg := Arg1;
1252          for J in 1 .. Arg_Count loop
1253             if Chars (Arg) /= No_Name then
1254                for K in Names'Range loop
1255                   if Chars (Arg) = Names (K) then
1256                      if K < Highest_So_Far then
1257                         Error_Msg_Name_1 := Pname;
1258                         Error_Msg_N
1259                           ("parameters out of order for pragma%", Arg);
1260                         Error_Msg_Name_1 := Names (K);
1261                         Error_Msg_Name_2 := Names (Highest_So_Far);
1262                         Error_Msg_N ("\% must appear before %", Arg);
1263                         raise Pragma_Exit;
1264
1265                      else
1266                         Highest_So_Far := K;
1267                      end if;
1268                   end if;
1269                end loop;
1270             end if;
1271
1272             Arg := Next (Arg);
1273          end loop;
1274       end Check_Arg_Order;
1275
1276       --------------------------------
1277       -- Check_At_Least_N_Arguments --
1278       --------------------------------
1279
1280       procedure Check_At_Least_N_Arguments (N : Nat) is
1281       begin
1282          if Arg_Count < N then
1283             Error_Pragma ("too few arguments for pragma%");
1284          end if;
1285       end Check_At_Least_N_Arguments;
1286
1287       -------------------------------
1288       -- Check_At_Most_N_Arguments --
1289       -------------------------------
1290
1291       procedure Check_At_Most_N_Arguments (N : Nat) is
1292          Arg : Node_Id;
1293       begin
1294          if Arg_Count > N then
1295             Arg := Arg1;
1296             for J in 1 .. N loop
1297                Next (Arg);
1298                Error_Pragma_Arg ("too many arguments for pragma%", Arg);
1299             end loop;
1300          end if;
1301       end Check_At_Most_N_Arguments;
1302
1303       ---------------------
1304       -- Check_Component --
1305       ---------------------
1306
1307       procedure Check_Component
1308         (Comp            : Node_Id;
1309          UU_Typ          : Entity_Id;
1310          In_Variant_Part : Boolean := False)
1311       is
1312          Comp_Id : constant Entity_Id := Defining_Identifier (Comp);
1313          Sindic  : constant Node_Id :=
1314                      Subtype_Indication (Component_Definition (Comp));
1315          Typ     : constant Entity_Id := Etype (Comp_Id);
1316
1317          function Inside_Generic_Body (Id : Entity_Id) return Boolean;
1318          --  Determine whether entity Id appears inside a generic body.
1319          --  Shouldn't this be in a more general place ???
1320
1321          -------------------------
1322          -- Inside_Generic_Body --
1323          -------------------------
1324
1325          function Inside_Generic_Body (Id : Entity_Id) return Boolean is
1326             S : Entity_Id;
1327
1328          begin
1329             S := Id;
1330             while Present (S) and then S /= Standard_Standard loop
1331                if Ekind (S) = E_Generic_Package
1332                  and then In_Package_Body (S)
1333                then
1334                   return True;
1335                end if;
1336
1337                S := Scope (S);
1338             end loop;
1339
1340             return False;
1341          end Inside_Generic_Body;
1342
1343       --  Start of processing for Check_Component
1344
1345       begin
1346          --  Ada 2005 (AI-216): If a component subtype is subject to a per-
1347          --  object constraint, then the component type shall be an Unchecked_
1348          --  Union.
1349
1350          if Nkind (Sindic) = N_Subtype_Indication
1351            and then Has_Per_Object_Constraint (Comp_Id)
1352            and then not Is_Unchecked_Union (Etype (Subtype_Mark (Sindic)))
1353          then
1354             Error_Msg_N
1355               ("component subtype subject to per-object constraint " &
1356                "must be an Unchecked_Union", Comp);
1357
1358          --  Ada 2012 (AI05-0026): For an unchecked union type declared within
1359          --  the body of a generic unit, or within the body of any of its
1360          --  descendant library units, no part of the type of a component
1361          --  declared in a variant_part of the unchecked union type shall be of
1362          --  a formal private type or formal private extension declared within
1363          --  the formal part of the generic unit.
1364
1365          elsif Ada_Version >= Ada_2012
1366            and then Inside_Generic_Body (UU_Typ)
1367            and then In_Variant_Part
1368            and then Is_Private_Type (Typ)
1369            and then Is_Generic_Type (Typ)
1370          then
1371             Error_Msg_N
1372               ("component of Unchecked_Union cannot be of generic type", Comp);
1373
1374          elsif Needs_Finalization (Typ) then
1375             Error_Msg_N
1376               ("component of Unchecked_Union cannot be controlled", Comp);
1377
1378          elsif Has_Task (Typ) then
1379             Error_Msg_N
1380               ("component of Unchecked_Union cannot have tasks", Comp);
1381          end if;
1382       end Check_Component;
1383
1384       ----------------------------
1385       -- Check_Duplicate_Pragma --
1386       ----------------------------
1387
1388       procedure Check_Duplicate_Pragma (E : Entity_Id) is
1389          P : Node_Id;
1390
1391       begin
1392          --  Nothing to do if this pragma comes from an aspect specification,
1393          --  since we could not be duplicating a pragma, and we dealt with the
1394          --  case of duplicated aspects in Analyze_Aspect_Specifications.
1395
1396          if From_Aspect_Specification (N) then
1397             return;
1398          end if;
1399
1400          --  Otherwise current pragma may duplicate previous pragma or a
1401          --  previously given aspect specification for the same pragma.
1402
1403          P := Get_Rep_Item_For_Entity (E, Pragma_Name (N));
1404
1405          if Present (P) then
1406             Error_Msg_Name_1 := Pragma_Name (N);
1407             Error_Msg_Sloc := Sloc (P);
1408
1409             if Nkind (P) = N_Aspect_Specification
1410               or else From_Aspect_Specification (P)
1411             then
1412                Error_Msg_NE ("aspect% for & previously given#", N, E);
1413             else
1414                Error_Msg_NE ("pragma% for & duplicates pragma#", N, E);
1415             end if;
1416
1417             raise Pragma_Exit;
1418          end if;
1419       end Check_Duplicate_Pragma;
1420
1421       ----------------------------------
1422       -- Check_Duplicated_Export_Name --
1423       ----------------------------------
1424
1425       procedure Check_Duplicated_Export_Name (Nam : Node_Id) is
1426          String_Val : constant String_Id := Strval (Nam);
1427
1428       begin
1429          --  We are only interested in the export case, and in the case of
1430          --  generics, it is the instance, not the template, that is the
1431          --  problem (the template will generate a warning in any case).
1432
1433          if not Inside_A_Generic
1434            and then (Prag_Id = Pragma_Export
1435                        or else
1436                      Prag_Id = Pragma_Export_Procedure
1437                        or else
1438                      Prag_Id = Pragma_Export_Valued_Procedure
1439                        or else
1440                      Prag_Id = Pragma_Export_Function)
1441          then
1442             for J in Externals.First .. Externals.Last loop
1443                if String_Equal (String_Val, Strval (Externals.Table (J))) then
1444                   Error_Msg_Sloc := Sloc (Externals.Table (J));
1445                   Error_Msg_N ("external name duplicates name given#", Nam);
1446                   exit;
1447                end if;
1448             end loop;
1449
1450             Externals.Append (Nam);
1451          end if;
1452       end Check_Duplicated_Export_Name;
1453
1454       -------------------------------------
1455       -- Check_Expr_Is_Static_Expression --
1456       -------------------------------------
1457
1458       procedure Check_Expr_Is_Static_Expression
1459         (Expr : Node_Id;
1460          Typ  : Entity_Id := Empty)
1461       is
1462       begin
1463          if Present (Typ) then
1464             Analyze_And_Resolve (Expr, Typ);
1465          else
1466             Analyze_And_Resolve (Expr);
1467          end if;
1468
1469          if Is_OK_Static_Expression (Expr) then
1470             return;
1471
1472          elsif Etype (Expr) = Any_Type then
1473             raise Pragma_Exit;
1474
1475          --  An interesting special case, if we have a string literal and we
1476          --  are in Ada 83 mode, then we allow it even though it will not be
1477          --  flagged as static. This allows the use of Ada 95 pragmas like
1478          --  Import in Ada 83 mode. They will of course be flagged with
1479          --  warnings as usual, but will not cause errors.
1480
1481          elsif Ada_Version = Ada_83
1482            and then Nkind (Expr) = N_String_Literal
1483          then
1484             return;
1485
1486          --  Static expression that raises Constraint_Error. This has already
1487          --  been flagged, so just exit from pragma processing.
1488
1489          elsif Is_Static_Expression (Expr) then
1490             raise Pragma_Exit;
1491
1492          --  Finally, we have a real error
1493
1494          else
1495             Error_Msg_Name_1 := Pname;
1496
1497             declare
1498                Msg : String :=
1499                        "argument for pragma% must be a static expression!";
1500             begin
1501                Fix_Error (Msg);
1502                Flag_Non_Static_Expr (Msg, Expr);
1503             end;
1504
1505             raise Pragma_Exit;
1506          end if;
1507       end Check_Expr_Is_Static_Expression;
1508
1509       -------------------------
1510       -- Check_First_Subtype --
1511       -------------------------
1512
1513       procedure Check_First_Subtype (Arg : Node_Id) is
1514          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1515          Ent  : constant Entity_Id := Entity (Argx);
1516
1517       begin
1518          if Is_First_Subtype (Ent) then
1519             null;
1520
1521          elsif Is_Type (Ent) then
1522             Error_Pragma_Arg
1523               ("pragma% cannot apply to subtype", Argx);
1524
1525          elsif Is_Object (Ent) then
1526             Error_Pragma_Arg
1527               ("pragma% cannot apply to object, requires a type", Argx);
1528
1529          else
1530             Error_Pragma_Arg
1531               ("pragma% cannot apply to&, requires a type", Argx);
1532          end if;
1533       end Check_First_Subtype;
1534
1535       ----------------------
1536       -- Check_Identifier --
1537       ----------------------
1538
1539       procedure Check_Identifier (Arg : Node_Id; Id : Name_Id) is
1540       begin
1541          if Present (Arg)
1542            and then Nkind (Arg) = N_Pragma_Argument_Association
1543          then
1544             if Chars (Arg) = No_Name or else Chars (Arg) /= Id then
1545                Error_Msg_Name_1 := Pname;
1546                Error_Msg_Name_2 := Id;
1547                Error_Msg_N ("pragma% argument expects identifier%", Arg);
1548                raise Pragma_Exit;
1549             end if;
1550          end if;
1551       end Check_Identifier;
1552
1553       --------------------------------
1554       -- Check_Identifier_Is_One_Of --
1555       --------------------------------
1556
1557       procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
1558       begin
1559          if Present (Arg)
1560            and then Nkind (Arg) = N_Pragma_Argument_Association
1561          then
1562             if Chars (Arg) = No_Name then
1563                Error_Msg_Name_1 := Pname;
1564                Error_Msg_N ("pragma% argument expects an identifier", Arg);
1565                raise Pragma_Exit;
1566
1567             elsif Chars (Arg) /= N1
1568               and then Chars (Arg) /= N2
1569             then
1570                Error_Msg_Name_1 := Pname;
1571                Error_Msg_N ("invalid identifier for pragma% argument", Arg);
1572                raise Pragma_Exit;
1573             end if;
1574          end if;
1575       end Check_Identifier_Is_One_Of;
1576
1577       ---------------------------
1578       -- Check_In_Main_Program --
1579       ---------------------------
1580
1581       procedure Check_In_Main_Program is
1582          P : constant Node_Id := Parent (N);
1583
1584       begin
1585          --  Must be at in subprogram body
1586
1587          if Nkind (P) /= N_Subprogram_Body then
1588             Error_Pragma ("% pragma allowed only in subprogram");
1589
1590          --  Otherwise warn if obviously not main program
1591
1592          elsif Present (Parameter_Specifications (Specification (P)))
1593            or else not Is_Compilation_Unit (Defining_Entity (P))
1594          then
1595             Error_Msg_Name_1 := Pname;
1596             Error_Msg_N
1597               ("?pragma% is only effective in main program", N);
1598          end if;
1599       end Check_In_Main_Program;
1600
1601       ---------------------------------------
1602       -- Check_Interrupt_Or_Attach_Handler --
1603       ---------------------------------------
1604
1605       procedure Check_Interrupt_Or_Attach_Handler is
1606          Arg1_X : constant Node_Id := Get_Pragma_Arg (Arg1);
1607          Handler_Proc, Proc_Scope : Entity_Id;
1608
1609       begin
1610          Analyze (Arg1_X);
1611
1612          if Prag_Id = Pragma_Interrupt_Handler then
1613             Check_Restriction (No_Dynamic_Attachment, N);
1614          end if;
1615
1616          Handler_Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
1617          Proc_Scope := Scope (Handler_Proc);
1618
1619          --  On AAMP only, a pragma Interrupt_Handler is supported for
1620          --  nonprotected parameterless procedures.
1621
1622          if not AAMP_On_Target
1623            or else Prag_Id = Pragma_Attach_Handler
1624          then
1625             if Ekind (Proc_Scope) /= E_Protected_Type then
1626                Error_Pragma_Arg
1627                  ("argument of pragma% must be protected procedure", Arg1);
1628             end if;
1629
1630             if Parent (N) /= Protected_Definition (Parent (Proc_Scope)) then
1631                Error_Pragma ("pragma% must be in protected definition");
1632             end if;
1633          end if;
1634
1635          if not Is_Library_Level_Entity (Proc_Scope)
1636            or else (AAMP_On_Target
1637                      and then not Is_Library_Level_Entity (Handler_Proc))
1638          then
1639             Error_Pragma_Arg
1640               ("argument for pragma% must be library level entity", Arg1);
1641          end if;
1642
1643          --  AI05-0033: A pragma cannot appear within a generic body, because
1644          --  instance can be in a nested scope. The check that protected type
1645          --  is itself a library-level declaration is done elsewhere.
1646
1647          --  Note: we omit this check in Codepeer mode to properly handle code
1648          --  prior to AI-0033 (pragmas don't matter to codepeer in any case).
1649
1650          if Inside_A_Generic then
1651             if Ekind (Scope (Current_Scope)) = E_Generic_Package
1652               and then In_Package_Body (Scope (Current_Scope))
1653               and then not CodePeer_Mode
1654             then
1655                Error_Pragma ("pragma% cannot be used inside a generic");
1656             end if;
1657          end if;
1658       end Check_Interrupt_Or_Attach_Handler;
1659
1660       -------------------------------------------
1661       -- Check_Is_In_Decl_Part_Or_Package_Spec --
1662       -------------------------------------------
1663
1664       procedure Check_Is_In_Decl_Part_Or_Package_Spec is
1665          P : Node_Id;
1666
1667       begin
1668          P := Parent (N);
1669          loop
1670             if No (P) then
1671                exit;
1672
1673             elsif Nkind (P) = N_Handled_Sequence_Of_Statements then
1674                exit;
1675
1676             elsif Nkind_In (P, N_Package_Specification,
1677                                N_Block_Statement)
1678             then
1679                return;
1680
1681             --  Note: the following tests seem a little peculiar, because
1682             --  they test for bodies, but if we were in the statement part
1683             --  of the body, we would already have hit the handled statement
1684             --  sequence, so the only way we get here is by being in the
1685             --  declarative part of the body.
1686
1687             elsif Nkind_In (P, N_Subprogram_Body,
1688                                N_Package_Body,
1689                                N_Task_Body,
1690                                N_Entry_Body)
1691             then
1692                return;
1693             end if;
1694
1695             P := Parent (P);
1696          end loop;
1697
1698          Error_Pragma ("pragma% is not in declarative part or package spec");
1699       end Check_Is_In_Decl_Part_Or_Package_Spec;
1700
1701       -------------------------
1702       -- Check_No_Identifier --
1703       -------------------------
1704
1705       procedure Check_No_Identifier (Arg : Node_Id) is
1706       begin
1707          if Nkind (Arg) = N_Pragma_Argument_Association
1708            and then Chars (Arg) /= No_Name
1709          then
1710             Error_Pragma_Arg_Ident
1711               ("pragma% does not permit identifier& here", Arg);
1712          end if;
1713       end Check_No_Identifier;
1714
1715       --------------------------
1716       -- Check_No_Identifiers --
1717       --------------------------
1718
1719       procedure Check_No_Identifiers is
1720          Arg_Node : Node_Id;
1721       begin
1722          if Arg_Count > 0 then
1723             Arg_Node := Arg1;
1724             while Present (Arg_Node) loop
1725                Check_No_Identifier (Arg_Node);
1726                Next (Arg_Node);
1727             end loop;
1728          end if;
1729       end Check_No_Identifiers;
1730
1731       ------------------------
1732       -- Check_No_Link_Name --
1733       ------------------------
1734
1735       procedure Check_No_Link_Name is
1736       begin
1737          if Present (Arg3)
1738            and then Chars (Arg3) = Name_Link_Name
1739          then
1740             Arg4 := Arg3;
1741          end if;
1742
1743          if Present (Arg4) then
1744             Error_Pragma_Arg
1745               ("Link_Name argument not allowed for Import Intrinsic", Arg4);
1746          end if;
1747       end Check_No_Link_Name;
1748
1749       -------------------------------
1750       -- Check_Optional_Identifier --
1751       -------------------------------
1752
1753       procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id) is
1754       begin
1755          if Present (Arg)
1756            and then Nkind (Arg) = N_Pragma_Argument_Association
1757            and then Chars (Arg) /= No_Name
1758          then
1759             if Chars (Arg) /= Id then
1760                Error_Msg_Name_1 := Pname;
1761                Error_Msg_Name_2 := Id;
1762                Error_Msg_N ("pragma% argument expects identifier%", Arg);
1763                raise Pragma_Exit;
1764             end if;
1765          end if;
1766       end Check_Optional_Identifier;
1767
1768       procedure Check_Optional_Identifier (Arg : Node_Id; Id : String) is
1769       begin
1770          Name_Buffer (1 .. Id'Length) := Id;
1771          Name_Len := Id'Length;
1772          Check_Optional_Identifier (Arg, Name_Find);
1773       end Check_Optional_Identifier;
1774
1775       --------------------------------------
1776       -- Check_Precondition_Postcondition --
1777       --------------------------------------
1778
1779       procedure Check_Precondition_Postcondition (In_Body : out Boolean) is
1780          P  : Node_Id;
1781          PO : Node_Id;
1782
1783          procedure Chain_PPC (PO : Node_Id);
1784          --  If PO is an entry or a [generic] subprogram declaration node, then
1785          --  the precondition/postcondition applies to this subprogram and the
1786          --  processing for the pragma is completed. Otherwise the pragma is
1787          --  misplaced.
1788
1789          ---------------
1790          -- Chain_PPC --
1791          ---------------
1792
1793          procedure Chain_PPC (PO : Node_Id) is
1794             S   : Entity_Id;
1795             P   : Node_Id;
1796
1797          begin
1798             if Nkind (PO) = N_Abstract_Subprogram_Declaration then
1799                if not From_Aspect_Specification (N) then
1800                   Error_Pragma
1801                     ("pragma% cannot be applied to abstract subprogram");
1802
1803                elsif Class_Present (N) then
1804                   null;
1805
1806                else
1807                   Error_Pragma
1808                     ("aspect % requires ''Class for abstract subprogram");
1809                end if;
1810
1811             --  AI05-0230: The same restriction applies to null procedures. For
1812             --  compatibility with earlier uses of the Ada pragma, apply this
1813             --  rule only to aspect specifications.
1814
1815             --  The above discrpency needs documentation. Robert is dubious
1816             --  about whether it is a good idea ???
1817
1818             elsif Nkind (PO) = N_Subprogram_Declaration
1819               and then Nkind (Specification (PO)) = N_Procedure_Specification
1820               and then Null_Present (Specification (PO))
1821               and then From_Aspect_Specification (N)
1822               and then not Class_Present (N)
1823             then
1824                Error_Pragma
1825                  ("aspect % requires ''Class for null procedure");
1826
1827             elsif not Nkind_In (PO, N_Subprogram_Declaration,
1828                                     N_Generic_Subprogram_Declaration,
1829                                     N_Entry_Declaration)
1830             then
1831                Pragma_Misplaced;
1832             end if;
1833
1834             --  Here if we have [generic] subprogram or entry declaration
1835
1836             if Nkind (PO) = N_Entry_Declaration then
1837                S := Defining_Entity (PO);
1838             else
1839                S := Defining_Unit_Name (Specification (PO));
1840             end if;
1841
1842             --  Make sure we do not have the case of a precondition pragma when
1843             --  the Pre'Class aspect is present.
1844
1845             --  We do this by looking at pragmas already chained to the entity
1846             --  since the aspect derived pragma will be put on this list first.
1847
1848             if Pragma_Name (N) = Name_Precondition then
1849                if not From_Aspect_Specification (N) then
1850                   P := Spec_PPC_List (Contract (S));
1851                   while Present (P) loop
1852                      if Pragma_Name (P) = Name_Precondition
1853                        and then From_Aspect_Specification (P)
1854                        and then Class_Present (P)
1855                      then
1856                         Error_Msg_Sloc := Sloc (P);
1857                         Error_Pragma
1858                           ("pragma% not allowed, `Pre''Class` aspect given#");
1859                      end if;
1860
1861                      P := Next_Pragma (P);
1862                   end loop;
1863                end if;
1864             end if;
1865
1866             --  Similarly check for Pre with inherited Pre'Class. Note that
1867             --  we cover the aspect case as well here.
1868
1869             if Pragma_Name (N) = Name_Precondition
1870               and then not Class_Present (N)
1871             then
1872                declare
1873                   Inherited : constant Subprogram_List :=
1874                                 Inherited_Subprograms (S);
1875                   P         : Node_Id;
1876
1877                begin
1878                   for J in Inherited'Range loop
1879                      P := Spec_PPC_List (Contract (Inherited (J)));
1880                      while Present (P) loop
1881                         if Pragma_Name (P) = Name_Precondition
1882                           and then Class_Present (P)
1883                         then
1884                            Error_Msg_Sloc := Sloc (P);
1885                            Error_Pragma
1886                              ("pragma% not allowed, `Pre''Class` "
1887                               & "aspect inherited from#");
1888                         end if;
1889
1890                         P := Next_Pragma (P);
1891                      end loop;
1892                   end loop;
1893                end;
1894             end if;
1895
1896             --  Note: we do not analyze the pragma at this point. Instead we
1897             --  delay this analysis until the end of the declarative part in
1898             --  which the pragma appears. This implements the required delay
1899             --  in this analysis, allowing forward references. The analysis
1900             --  happens at the end of Analyze_Declarations.
1901
1902             --  Chain spec PPC pragma to list for subprogram
1903
1904             Set_Next_Pragma (N, Spec_PPC_List (Contract (S)));
1905             Set_Spec_PPC_List (Contract (S), N);
1906
1907             --  Return indicating spec case
1908
1909             In_Body := False;
1910             return;
1911          end Chain_PPC;
1912
1913       --  Start of processing for Check_Precondition_Postcondition
1914
1915       begin
1916          if not Is_List_Member (N) then
1917             Pragma_Misplaced;
1918          end if;
1919
1920          --  Preanalyze message argument if present. Visibility in this
1921          --  argument is established at the point of pragma occurrence.
1922
1923          if Arg_Count = 2 then
1924             Check_Optional_Identifier (Arg2, Name_Message);
1925             Preanalyze_Spec_Expression
1926               (Get_Pragma_Arg (Arg2), Standard_String);
1927          end if;
1928
1929          --  Record if pragma is disabled
1930
1931          if Check_Enabled (Pname) then
1932             Set_SCO_Pragma_Enabled (Loc);
1933          end if;
1934
1935          --  If we are within an inlined body, the legality of the pragma
1936          --  has been checked already.
1937
1938          if In_Inlined_Body then
1939             In_Body := True;
1940             return;
1941          end if;
1942
1943          --  Search prior declarations
1944
1945          P := N;
1946          while Present (Prev (P)) loop
1947             P := Prev (P);
1948
1949             --  If the previous node is a generic subprogram, do not go to to
1950             --  the original node, which is the unanalyzed tree: we need to
1951             --  attach the pre/postconditions to the analyzed version at this
1952             --  point. They get propagated to the original tree when analyzing
1953             --  the corresponding body.
1954
1955             if Nkind (P) not in N_Generic_Declaration then
1956                PO := Original_Node (P);
1957             else
1958                PO := P;
1959             end if;
1960
1961             --  Skip past prior pragma
1962
1963             if Nkind (PO) = N_Pragma then
1964                null;
1965
1966             --  Skip stuff not coming from source
1967
1968             elsif not Comes_From_Source (PO) then
1969
1970                --  The condition may apply to a subprogram instantiation
1971
1972                if Nkind (PO) = N_Subprogram_Declaration
1973                  and then Present (Generic_Parent (Specification (PO)))
1974                then
1975                   Chain_PPC (PO);
1976                   return;
1977
1978                elsif Nkind (PO) = N_Subprogram_Declaration
1979                  and then In_Instance
1980                then
1981                   Chain_PPC (PO);
1982                   return;
1983
1984                --  For all other cases of non source code, do nothing
1985
1986                else
1987                   null;
1988                end if;
1989
1990             --  Only remaining possibility is subprogram declaration
1991
1992             else
1993                Chain_PPC (PO);
1994                return;
1995             end if;
1996          end loop;
1997
1998          --  If we fall through loop, pragma is at start of list, so see if it
1999          --  is at the start of declarations of a subprogram body.
2000
2001          if Nkind (Parent (N)) = N_Subprogram_Body
2002            and then List_Containing (N) = Declarations (Parent (N))
2003          then
2004             if Operating_Mode /= Generate_Code
2005               or else Inside_A_Generic
2006             then
2007                --  Analyze pragma expression for correctness and for ASIS use
2008
2009                Preanalyze_Spec_Expression
2010                  (Get_Pragma_Arg (Arg1), Standard_Boolean);
2011
2012                --  In ASIS mode, for a pragma generated from a source aspect,
2013                --  also analyze the original aspect expression.
2014
2015                if ASIS_Mode
2016                  and then Present (Corresponding_Aspect (N))
2017                then
2018                   Preanalyze_Spec_Expression
2019                     (Expression (Corresponding_Aspect (N)), Standard_Boolean);
2020                end if;
2021             end if;
2022
2023             In_Body := True;
2024             return;
2025
2026          --  See if it is in the pragmas after a library level subprogram
2027
2028          elsif Nkind (Parent (N)) = N_Compilation_Unit_Aux then
2029
2030             --  In formal verification mode, analyze pragma expression for
2031             --  correctness, as it is not expanded later.
2032
2033             if Alfa_Mode then
2034                Analyze_PPC_In_Decl_Part
2035                  (N, Defining_Entity (Unit (Parent (Parent (N)))));
2036             end if;
2037
2038             Chain_PPC (Unit (Parent (Parent (N))));
2039             return;
2040          end if;
2041
2042          --  If we fall through, pragma was misplaced
2043
2044          Pragma_Misplaced;
2045       end Check_Precondition_Postcondition;
2046
2047       -----------------------------
2048       -- Check_Static_Constraint --
2049       -----------------------------
2050
2051       --  Note: for convenience in writing this procedure, in addition to
2052       --  the officially (i.e. by spec) allowed argument which is always a
2053       --  constraint, it also allows ranges and discriminant associations.
2054       --  Above is not clear ???
2055
2056       procedure Check_Static_Constraint (Constr : Node_Id) is
2057
2058          procedure Require_Static (E : Node_Id);
2059          --  Require given expression to be static expression
2060
2061          --------------------
2062          -- Require_Static --
2063          --------------------
2064
2065          procedure Require_Static (E : Node_Id) is
2066          begin
2067             if not Is_OK_Static_Expression (E) then
2068                Flag_Non_Static_Expr
2069                  ("non-static constraint not allowed in Unchecked_Union!", E);
2070                raise Pragma_Exit;
2071             end if;
2072          end Require_Static;
2073
2074       --  Start of processing for Check_Static_Constraint
2075
2076       begin
2077          case Nkind (Constr) is
2078             when N_Discriminant_Association =>
2079                Require_Static (Expression (Constr));
2080
2081             when N_Range =>
2082                Require_Static (Low_Bound (Constr));
2083                Require_Static (High_Bound (Constr));
2084
2085             when N_Attribute_Reference =>
2086                Require_Static (Type_Low_Bound  (Etype (Prefix (Constr))));
2087                Require_Static (Type_High_Bound (Etype (Prefix (Constr))));
2088
2089             when N_Range_Constraint =>
2090                Check_Static_Constraint (Range_Expression (Constr));
2091
2092             when N_Index_Or_Discriminant_Constraint =>
2093                declare
2094                   IDC : Entity_Id;
2095                begin
2096                   IDC := First (Constraints (Constr));
2097                   while Present (IDC) loop
2098                      Check_Static_Constraint (IDC);
2099                      Next (IDC);
2100                   end loop;
2101                end;
2102
2103             when others =>
2104                null;
2105          end case;
2106       end Check_Static_Constraint;
2107
2108       ---------------------
2109       -- Check_Test_Case --
2110       ---------------------
2111
2112       procedure Check_Test_Case is
2113          P  : Node_Id;
2114          PO : Node_Id;
2115
2116          procedure Chain_TC (PO : Node_Id);
2117          --  If PO is a [generic] subprogram declaration node, then the
2118          --  test-case applies to this subprogram and the processing for the
2119          --  pragma is completed. Otherwise the pragma is misplaced.
2120
2121          --------------
2122          -- Chain_TC --
2123          --------------
2124
2125          procedure Chain_TC (PO : Node_Id) is
2126             S   : Entity_Id;
2127
2128          begin
2129             if Nkind (PO) = N_Abstract_Subprogram_Declaration then
2130                if From_Aspect_Specification (N) then
2131                   Error_Pragma
2132                     ("aspect% cannot be applied to abstract subprogram");
2133                else
2134                   Error_Pragma
2135                     ("pragma% cannot be applied to abstract subprogram");
2136                end if;
2137
2138             elsif Nkind (PO) = N_Entry_Declaration then
2139                if From_Aspect_Specification (N) then
2140                   Error_Pragma ("aspect% cannot be applied to entry");
2141                else
2142                   Error_Pragma ("pragma% cannot be applied to entry");
2143                end if;
2144
2145             elsif not Nkind_In (PO, N_Subprogram_Declaration,
2146                                     N_Generic_Subprogram_Declaration)
2147             then
2148                Pragma_Misplaced;
2149             end if;
2150
2151             --  Here if we have [generic] subprogram declaration
2152
2153             S := Defining_Unit_Name (Specification (PO));
2154
2155             --  Note: we do not analyze the pragma at this point. Instead we
2156             --  delay this analysis until the end of the declarative part in
2157             --  which the pragma appears. This implements the required delay
2158             --  in this analysis, allowing forward references. The analysis
2159             --  happens at the end of Analyze_Declarations.
2160
2161             --  There should not be another test case with the same name
2162             --  associated to this subprogram.
2163
2164             declare
2165                Name : constant String_Id := Get_Name_From_Test_Case_Pragma (N);
2166                TC   : Node_Id;
2167
2168             begin
2169                TC := Spec_TC_List (Contract (S));
2170                while Present (TC) loop
2171
2172                   if String_Equal
2173                     (Name, Get_Name_From_Test_Case_Pragma (TC))
2174                   then
2175                      Error_Msg_Sloc := Sloc (TC);
2176
2177                      if From_Aspect_Specification (N) then
2178                         Error_Pragma ("name for aspect% is already used#");
2179                      else
2180                         Error_Pragma ("name for pragma% is already used#");
2181                      end if;
2182                   end if;
2183
2184                   TC := Next_Pragma (TC);
2185                end loop;
2186             end;
2187
2188             --  Chain spec TC pragma to list for subprogram
2189
2190             Set_Next_Pragma (N, Spec_TC_List (Contract (S)));
2191             Set_Spec_TC_List (Contract (S), N);
2192          end Chain_TC;
2193
2194       --  Start of processing for Check_Test_Case
2195
2196       begin
2197          if not Is_List_Member (N) then
2198             Pragma_Misplaced;
2199          end if;
2200
2201          --  Test cases should only appear in package spec unit
2202
2203          if Get_Source_Unit (N) = No_Unit
2204            or else not Nkind_In (Sinfo.Unit (Cunit (Get_Source_Unit (N))),
2205                                  N_Package_Declaration,
2206                                  N_Generic_Package_Declaration)
2207          then
2208             Pragma_Misplaced;
2209          end if;
2210
2211          --  Search prior declarations
2212
2213          P := N;
2214          while Present (Prev (P)) loop
2215             P := Prev (P);
2216
2217             --  If the previous node is a generic subprogram, do not go to to
2218             --  the original node, which is the unanalyzed tree: we need to
2219             --  attach the test-case to the analyzed version at this point.
2220             --  They get propagated to the original tree when analyzing the
2221             --  corresponding body.
2222
2223             if Nkind (P) not in N_Generic_Declaration then
2224                PO := Original_Node (P);
2225             else
2226                PO := P;
2227             end if;
2228
2229             --  Skip past prior pragma
2230
2231             if Nkind (PO) = N_Pragma then
2232                null;
2233
2234             --  Skip stuff not coming from source
2235
2236             elsif not Comes_From_Source (PO) then
2237                null;
2238
2239             --  Only remaining possibility is subprogram declaration. First
2240             --  check that it is declared directly in a package declaration.
2241             --  This may be either the package declaration for the current unit
2242             --  being defined or a local package declaration.
2243
2244             elsif not Present (Parent (Parent (PO)))
2245               or else not Present (Parent (Parent (Parent (PO))))
2246               or else not Nkind_In (Parent (Parent (PO)),
2247                                     N_Package_Declaration,
2248                                     N_Generic_Package_Declaration)
2249             then
2250                Pragma_Misplaced;
2251
2252             else
2253                Chain_TC (PO);
2254                return;
2255             end if;
2256          end loop;
2257
2258          --  If we fall through, pragma was misplaced
2259
2260          Pragma_Misplaced;
2261       end Check_Test_Case;
2262
2263       --------------------------------------
2264       -- Check_Valid_Configuration_Pragma --
2265       --------------------------------------
2266
2267       --  A configuration pragma must appear in the context clause of a
2268       --  compilation unit, and only other pragmas may precede it. Note that
2269       --  the test also allows use in a configuration pragma file.
2270
2271       procedure Check_Valid_Configuration_Pragma is
2272       begin
2273          if not Is_Configuration_Pragma then
2274             Error_Pragma ("incorrect placement for configuration pragma%");
2275          end if;
2276       end Check_Valid_Configuration_Pragma;
2277
2278       -------------------------------------
2279       -- Check_Valid_Library_Unit_Pragma --
2280       -------------------------------------
2281
2282       procedure Check_Valid_Library_Unit_Pragma is
2283          Plist       : List_Id;
2284          Parent_Node : Node_Id;
2285          Unit_Name   : Entity_Id;
2286          Unit_Kind   : Node_Kind;
2287          Unit_Node   : Node_Id;
2288          Sindex      : Source_File_Index;
2289
2290       begin
2291          if not Is_List_Member (N) then
2292             Pragma_Misplaced;
2293
2294          else
2295             Plist := List_Containing (N);
2296             Parent_Node := Parent (Plist);
2297
2298             if Parent_Node = Empty then
2299                Pragma_Misplaced;
2300
2301             --  Case of pragma appearing after a compilation unit. In this case
2302             --  it must have an argument with the corresponding name and must
2303             --  be part of the following pragmas of its parent.
2304
2305             elsif Nkind (Parent_Node) = N_Compilation_Unit_Aux then
2306                if Plist /= Pragmas_After (Parent_Node) then
2307                   Pragma_Misplaced;
2308
2309                elsif Arg_Count = 0 then
2310                   Error_Pragma
2311                     ("argument required if outside compilation unit");
2312
2313                else
2314                   Check_No_Identifiers;
2315                   Check_Arg_Count (1);
2316                   Unit_Node := Unit (Parent (Parent_Node));
2317                   Unit_Kind := Nkind (Unit_Node);
2318
2319                   Analyze (Get_Pragma_Arg (Arg1));
2320
2321                   if Unit_Kind = N_Generic_Subprogram_Declaration
2322                     or else Unit_Kind = N_Subprogram_Declaration
2323                   then
2324                      Unit_Name := Defining_Entity (Unit_Node);
2325
2326                   elsif Unit_Kind in N_Generic_Instantiation then
2327                      Unit_Name := Defining_Entity (Unit_Node);
2328
2329                   else
2330                      Unit_Name := Cunit_Entity (Current_Sem_Unit);
2331                   end if;
2332
2333                   if Chars (Unit_Name) /=
2334                      Chars (Entity (Get_Pragma_Arg (Arg1)))
2335                   then
2336                      Error_Pragma_Arg
2337                        ("pragma% argument is not current unit name", Arg1);
2338                   end if;
2339
2340                   if Ekind (Unit_Name) = E_Package
2341                     and then Present (Renamed_Entity (Unit_Name))
2342                   then
2343                      Error_Pragma ("pragma% not allowed for renamed package");
2344                   end if;
2345                end if;
2346
2347             --  Pragma appears other than after a compilation unit
2348
2349             else
2350                --  Here we check for the generic instantiation case and also
2351                --  for the case of processing a generic formal package. We
2352                --  detect these cases by noting that the Sloc on the node
2353                --  does not belong to the current compilation unit.
2354
2355                Sindex := Source_Index (Current_Sem_Unit);
2356
2357                if Loc not in Source_First (Sindex) .. Source_Last (Sindex) then
2358                   Rewrite (N, Make_Null_Statement (Loc));
2359                   return;
2360
2361                --  If before first declaration, the pragma applies to the
2362                --  enclosing unit, and the name if present must be this name.
2363
2364                elsif Is_Before_First_Decl (N, Plist) then
2365                   Unit_Node := Unit_Declaration_Node (Current_Scope);
2366                   Unit_Kind := Nkind (Unit_Node);
2367
2368                   if Nkind (Parent (Unit_Node)) /= N_Compilation_Unit then
2369                      Pragma_Misplaced;
2370
2371                   elsif Unit_Kind = N_Subprogram_Body
2372                     and then not Acts_As_Spec (Unit_Node)
2373                   then
2374                      Pragma_Misplaced;
2375
2376                   elsif Nkind (Parent_Node) = N_Package_Body then
2377                      Pragma_Misplaced;
2378
2379                   elsif Nkind (Parent_Node) = N_Package_Specification
2380                     and then Plist = Private_Declarations (Parent_Node)
2381                   then
2382                      Pragma_Misplaced;
2383
2384                   elsif (Nkind (Parent_Node) = N_Generic_Package_Declaration
2385                            or else Nkind (Parent_Node) =
2386                                              N_Generic_Subprogram_Declaration)
2387                     and then Plist = Generic_Formal_Declarations (Parent_Node)
2388                   then
2389                      Pragma_Misplaced;
2390
2391                   elsif Arg_Count > 0 then
2392                      Analyze (Get_Pragma_Arg (Arg1));
2393
2394                      if Entity (Get_Pragma_Arg (Arg1)) /= Current_Scope then
2395                         Error_Pragma_Arg
2396                           ("name in pragma% must be enclosing unit", Arg1);
2397                      end if;
2398
2399                   --  It is legal to have no argument in this context
2400
2401                   else
2402                      return;
2403                   end if;
2404
2405                --  Error if not before first declaration. This is because a
2406                --  library unit pragma argument must be the name of a library
2407                --  unit (RM 10.1.5(7)), but the only names permitted in this
2408                --  context are (RM 10.1.5(6)) names of subprogram declarations,
2409                --  generic subprogram declarations or generic instantiations.
2410
2411                else
2412                   Error_Pragma
2413                     ("pragma% misplaced, must be before first declaration");
2414                end if;
2415             end if;
2416          end if;
2417       end Check_Valid_Library_Unit_Pragma;
2418
2419       -------------------
2420       -- Check_Variant --
2421       -------------------
2422
2423       procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id) is
2424          Clist : constant Node_Id := Component_List (Variant);
2425          Comp  : Node_Id;
2426
2427       begin
2428          if not Is_Non_Empty_List (Component_Items (Clist)) then
2429             Error_Msg_N
2430               ("Unchecked_Union may not have empty component list",
2431                Variant);
2432             return;
2433          end if;
2434
2435          Comp := First (Component_Items (Clist));
2436          while Present (Comp) loop
2437             Check_Component (Comp, UU_Typ, In_Variant_Part => True);
2438             Next (Comp);
2439          end loop;
2440       end Check_Variant;
2441
2442       ------------------
2443       -- Error_Pragma --
2444       ------------------
2445
2446       procedure Error_Pragma (Msg : String) is
2447          MsgF : String := Msg;
2448       begin
2449          Error_Msg_Name_1 := Pname;
2450          Fix_Error (MsgF);
2451          Error_Msg_N (MsgF, N);
2452          raise Pragma_Exit;
2453       end Error_Pragma;
2454
2455       ----------------------
2456       -- Error_Pragma_Arg --
2457       ----------------------
2458
2459       procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id) is
2460          MsgF : String := Msg;
2461       begin
2462          Error_Msg_Name_1 := Pname;
2463          Fix_Error (MsgF);
2464          Error_Msg_N (MsgF, Get_Pragma_Arg (Arg));
2465          raise Pragma_Exit;
2466       end Error_Pragma_Arg;
2467
2468       procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id) is
2469          MsgF : String := Msg1;
2470       begin
2471          Error_Msg_Name_1 := Pname;
2472          Fix_Error (MsgF);
2473          Error_Msg_N (MsgF, Get_Pragma_Arg (Arg));
2474          Error_Pragma_Arg (Msg2, Arg);
2475       end Error_Pragma_Arg;
2476
2477       ----------------------------
2478       -- Error_Pragma_Arg_Ident --
2479       ----------------------------
2480
2481       procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id) is
2482          MsgF : String := Msg;
2483       begin
2484          Error_Msg_Name_1 := Pname;
2485          Fix_Error (MsgF);
2486          Error_Msg_N (MsgF, Arg);
2487          raise Pragma_Exit;
2488       end Error_Pragma_Arg_Ident;
2489
2490       ----------------------
2491       -- Error_Pragma_Ref --
2492       ----------------------
2493
2494       procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id) is
2495          MsgF : String := Msg;
2496       begin
2497          Error_Msg_Name_1 := Pname;
2498          Fix_Error (MsgF);
2499          Error_Msg_Sloc   := Sloc (Ref);
2500          Error_Msg_NE (MsgF, N, Ref);
2501          raise Pragma_Exit;
2502       end Error_Pragma_Ref;
2503
2504       ------------------------
2505       -- Find_Lib_Unit_Name --
2506       ------------------------
2507
2508       function Find_Lib_Unit_Name return Entity_Id is
2509       begin
2510          --  Return inner compilation unit entity, for case of nested
2511          --  categorization pragmas. This happens in generic unit.
2512
2513          if Nkind (Parent (N)) = N_Package_Specification
2514            and then Defining_Entity (Parent (N)) /= Current_Scope
2515          then
2516             return Defining_Entity (Parent (N));
2517          else
2518             return Current_Scope;
2519          end if;
2520       end Find_Lib_Unit_Name;
2521
2522       ----------------------------
2523       -- Find_Program_Unit_Name --
2524       ----------------------------
2525
2526       procedure Find_Program_Unit_Name (Id : Node_Id) is
2527          Unit_Name : Entity_Id;
2528          Unit_Kind : Node_Kind;
2529          P         : constant Node_Id := Parent (N);
2530
2531       begin
2532          if Nkind (P) = N_Compilation_Unit then
2533             Unit_Kind := Nkind (Unit (P));
2534
2535             if Unit_Kind = N_Subprogram_Declaration
2536               or else Unit_Kind = N_Package_Declaration
2537               or else Unit_Kind in N_Generic_Declaration
2538             then
2539                Unit_Name := Defining_Entity (Unit (P));
2540
2541                if Chars (Id) = Chars (Unit_Name) then
2542                   Set_Entity (Id, Unit_Name);
2543                   Set_Etype (Id, Etype (Unit_Name));
2544                else
2545                   Set_Etype (Id, Any_Type);
2546                   Error_Pragma
2547                     ("cannot find program unit referenced by pragma%");
2548                end if;
2549
2550             else
2551                Set_Etype (Id, Any_Type);
2552                Error_Pragma ("pragma% inapplicable to this unit");
2553             end if;
2554
2555          else
2556             Analyze (Id);
2557          end if;
2558       end Find_Program_Unit_Name;
2559
2560       -----------------------------------------
2561       -- Find_Unique_Parameterless_Procedure --
2562       -----------------------------------------
2563
2564       function Find_Unique_Parameterless_Procedure
2565         (Name : Entity_Id;
2566          Arg  : Node_Id) return Entity_Id
2567       is
2568          Proc : Entity_Id := Empty;
2569
2570       begin
2571          --  The body of this procedure needs some comments ???
2572
2573          if not Is_Entity_Name (Name) then
2574             Error_Pragma_Arg
2575               ("argument of pragma% must be entity name", Arg);
2576
2577          elsif not Is_Overloaded (Name) then
2578             Proc := Entity (Name);
2579
2580             if Ekind (Proc) /= E_Procedure
2581               or else Present (First_Formal (Proc))
2582             then
2583                Error_Pragma_Arg
2584                  ("argument of pragma% must be parameterless procedure", Arg);
2585             end if;
2586
2587          else
2588             declare
2589                Found : Boolean := False;
2590                It    : Interp;
2591                Index : Interp_Index;
2592
2593             begin
2594                Get_First_Interp (Name, Index, It);
2595                while Present (It.Nam) loop
2596                   Proc := It.Nam;
2597
2598                   if Ekind (Proc) = E_Procedure
2599                     and then No (First_Formal (Proc))
2600                   then
2601                      if not Found then
2602                         Found := True;
2603                         Set_Entity (Name, Proc);
2604                         Set_Is_Overloaded (Name, False);
2605                      else
2606                         Error_Pragma_Arg
2607                           ("ambiguous handler name for pragma% ", Arg);
2608                      end if;
2609                   end if;
2610
2611                   Get_Next_Interp (Index, It);
2612                end loop;
2613
2614                if not Found then
2615                   Error_Pragma_Arg
2616                     ("argument of pragma% must be parameterless procedure",
2617                      Arg);
2618                else
2619                   Proc := Entity (Name);
2620                end if;
2621             end;
2622          end if;
2623
2624          return Proc;
2625       end Find_Unique_Parameterless_Procedure;
2626
2627       ---------------
2628       -- Fix_Error --
2629       ---------------
2630
2631       procedure Fix_Error (Msg : in out String) is
2632       begin
2633          if From_Aspect_Specification (N) then
2634             for J in Msg'First .. Msg'Last - 5 loop
2635                if Msg (J .. J + 5) = "pragma" then
2636                   Msg (J .. J + 5) := "aspect";
2637                end if;
2638             end loop;
2639
2640             if Error_Msg_Name_1 = Name_Precondition then
2641                Error_Msg_Name_1 := Name_Pre;
2642             elsif Error_Msg_Name_1 = Name_Postcondition then
2643                Error_Msg_Name_1 := Name_Post;
2644             end if;
2645          end if;
2646       end Fix_Error;
2647
2648       -------------------------
2649       -- Gather_Associations --
2650       -------------------------
2651
2652       procedure Gather_Associations
2653         (Names : Name_List;
2654          Args  : out Args_List)
2655       is
2656          Arg : Node_Id;
2657
2658       begin
2659          --  Initialize all parameters to Empty
2660
2661          for J in Args'Range loop
2662             Args (J) := Empty;
2663          end loop;
2664
2665          --  That's all we have to do if there are no argument associations
2666
2667          if No (Pragma_Argument_Associations (N)) then
2668             return;
2669          end if;
2670
2671          --  Otherwise first deal with any positional parameters present
2672
2673          Arg := First (Pragma_Argument_Associations (N));
2674          for Index in Args'Range loop
2675             exit when No (Arg) or else Chars (Arg) /= No_Name;
2676             Args (Index) := Get_Pragma_Arg (Arg);
2677             Next (Arg);
2678          end loop;
2679
2680          --  Positional parameters all processed, if any left, then we
2681          --  have too many positional parameters.
2682
2683          if Present (Arg) and then Chars (Arg) = No_Name then
2684             Error_Pragma_Arg
2685               ("too many positional associations for pragma%", Arg);
2686          end if;
2687
2688          --  Process named parameters if any are present
2689
2690          while Present (Arg) loop
2691             if Chars (Arg) = No_Name then
2692                Error_Pragma_Arg
2693                  ("positional association cannot follow named association",
2694                   Arg);
2695
2696             else
2697                for Index in Names'Range loop
2698                   if Names (Index) = Chars (Arg) then
2699                      if Present (Args (Index)) then
2700                         Error_Pragma_Arg
2701                           ("duplicate argument association for pragma%", Arg);
2702                      else
2703                         Args (Index) := Get_Pragma_Arg (Arg);
2704                         exit;
2705                      end if;
2706                   end if;
2707
2708                   if Index = Names'Last then
2709                      Error_Msg_Name_1 := Pname;
2710                      Error_Msg_N ("pragma% does not allow & argument", Arg);
2711
2712                      --  Check for possible misspelling
2713
2714                      for Index1 in Names'Range loop
2715                         if Is_Bad_Spelling_Of
2716                              (Chars (Arg), Names (Index1))
2717                         then
2718                            Error_Msg_Name_1 := Names (Index1);
2719                            Error_Msg_N -- CODEFIX
2720                              ("\possible misspelling of%", Arg);
2721                            exit;
2722                         end if;
2723                      end loop;
2724
2725                      raise Pragma_Exit;
2726                   end if;
2727                end loop;
2728             end if;
2729
2730             Next (Arg);
2731          end loop;
2732       end Gather_Associations;
2733
2734       -----------------
2735       -- GNAT_Pragma --
2736       -----------------
2737
2738       procedure GNAT_Pragma is
2739       begin
2740          Check_Restriction (No_Implementation_Pragmas, N);
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
3530
3531             --  Subprogram is allowed, but not a generic subprogram, and not a
3532             --  dispatching operation. A dispatching subprogram cannot be used
3533             --  to interface to the Win32 API, so in fact this check does not
3534             --  impose any effective restriction.
3535
3536            and then
3537              ((not Is_Subprogram (E) and then not Is_Generic_Subprogram (E))
3538                 or else Is_Dispatching_Operation (E))
3539
3540             --  A variable is OK
3541
3542            and then Ekind (E) /= E_Variable
3543
3544            --  An access to subprogram is also allowed
3545
3546            and then not
3547              (Is_Access_Type (E)
3548                and then Ekind (Designated_Type (E)) = E_Subprogram_Type)
3549          then
3550             Error_Pragma_Arg
3551               ("second argument of pragma% must be subprogram (type)",
3552                Arg2);
3553          end if;
3554
3555          if not Is_Subprogram (E)
3556            and then not Is_Generic_Subprogram (E)
3557          then
3558             Set_Convention_From_Pragma (E);
3559
3560             if Is_Type (E) then
3561                Check_First_Subtype (Arg2);
3562                Set_Convention_From_Pragma (Base_Type (E));
3563
3564                --  For subprograms, we must set the convention on the
3565                --  internally generated directly designated type as well.
3566
3567                if Ekind (E) = E_Access_Subprogram_Type then
3568                   Set_Convention_From_Pragma (Directly_Designated_Type (E));
3569                end if;
3570             end if;
3571
3572          --  For the subprogram case, set proper convention for all homonyms
3573          --  in same scope and the same declarative part, i.e. the same
3574          --  compilation unit.
3575
3576          else
3577             Comp_Unit := Get_Source_Unit (E);
3578             Set_Convention_From_Pragma (E);
3579
3580             --  Treat a pragma Import as an implicit body, for GPS use
3581
3582             if Prag_Id = Pragma_Import then
3583                Generate_Reference (E, Id, 'b');
3584             end if;
3585
3586             --  Loop through the homonyms of the pragma argument's entity
3587
3588             E1 := Ent;
3589             loop
3590                E1 := Homonym (E1);
3591                exit when No (E1) or else Scope (E1) /= Current_Scope;
3592
3593                --  Do not set the pragma on inherited operations or on formal
3594                --  subprograms.
3595
3596                if Comes_From_Source (E1)
3597                  and then Comp_Unit = Get_Source_Unit (E1)
3598                  and then not Is_Formal_Subprogram (E1)
3599                  and then Nkind (Original_Node (Parent (E1))) /=
3600                                                     N_Full_Type_Declaration
3601                then
3602                   if Present (Alias (E1))
3603                     and then Scope (E1) /= Scope (Alias (E1))
3604                   then
3605                      Error_Pragma_Ref
3606                        ("cannot apply pragma% to non-local entity& declared#",
3607                         E1);
3608                   end if;
3609
3610                   Set_Convention_From_Pragma (E1);
3611
3612                   if Prag_Id = Pragma_Import then
3613                      Generate_Reference (E1, Id, 'b');
3614                   end if;
3615                end if;
3616
3617                --  For aspect case, do NOT apply to homonyms
3618
3619                exit when From_Aspect_Specification (N);
3620             end loop;
3621          end if;
3622       end Process_Convention;
3623
3624       ----------------------------------------
3625       -- Process_Disable_Enable_Atomic_Sync --
3626       ----------------------------------------
3627
3628       procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id) is
3629       begin
3630          GNAT_Pragma;
3631          Check_No_Identifiers;
3632          Check_At_Most_N_Arguments (1);
3633
3634          --  Modeled internally as
3635          --    pragma Unsuppress (Atomic_Synchronization [,Entity])
3636
3637          Rewrite (N,
3638            Make_Pragma (Loc,
3639              Pragma_Identifier            =>
3640                Make_Identifier (Loc, Nam),
3641              Pragma_Argument_Associations => New_List (
3642                Make_Pragma_Argument_Association (Loc,
3643                  Expression =>
3644                    Make_Identifier (Loc, Name_Atomic_Synchronization)))));
3645
3646          if Present (Arg1) then
3647             Append_To (Pragma_Argument_Associations (N), New_Copy (Arg1));
3648          end if;
3649
3650          Analyze (N);
3651       end Process_Disable_Enable_Atomic_Sync;
3652
3653       -----------------------------------------------------
3654       -- Process_Extended_Import_Export_Exception_Pragma --
3655       -----------------------------------------------------
3656
3657       procedure Process_Extended_Import_Export_Exception_Pragma
3658         (Arg_Internal : Node_Id;
3659          Arg_External : Node_Id;
3660          Arg_Form     : Node_Id;
3661          Arg_Code     : Node_Id)
3662       is
3663          Def_Id   : Entity_Id;
3664          Code_Val : Uint;
3665
3666       begin
3667          if not OpenVMS_On_Target then
3668             Error_Pragma
3669               ("?pragma% ignored (applies only to Open'V'M'S)");
3670          end if;
3671
3672          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3673          Def_Id := Entity (Arg_Internal);
3674
3675          if Ekind (Def_Id) /= E_Exception then
3676             Error_Pragma_Arg
3677               ("pragma% must refer to declared exception", Arg_Internal);
3678          end if;
3679
3680          Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
3681
3682          if Present (Arg_Form) then
3683             Check_Arg_Is_One_Of (Arg_Form, Name_Ada, Name_VMS);
3684          end if;
3685
3686          if Present (Arg_Form)
3687            and then Chars (Arg_Form) = Name_Ada
3688          then
3689             null;
3690          else
3691             Set_Is_VMS_Exception (Def_Id);
3692             Set_Exception_Code (Def_Id, No_Uint);
3693          end if;
3694
3695          if Present (Arg_Code) then
3696             if not Is_VMS_Exception (Def_Id) then
3697                Error_Pragma_Arg
3698                  ("Code option for pragma% not allowed for Ada case",
3699                   Arg_Code);
3700             end if;
3701
3702             Check_Arg_Is_Static_Expression (Arg_Code, Any_Integer);
3703             Code_Val := Expr_Value (Arg_Code);
3704
3705             if not UI_Is_In_Int_Range (Code_Val) then
3706                Error_Pragma_Arg
3707                  ("Code option for pragma% must be in 32-bit range",
3708                   Arg_Code);
3709
3710             else
3711                Set_Exception_Code (Def_Id, Code_Val);
3712             end if;
3713          end if;
3714       end Process_Extended_Import_Export_Exception_Pragma;
3715
3716       -------------------------------------------------
3717       -- Process_Extended_Import_Export_Internal_Arg --
3718       -------------------------------------------------
3719
3720       procedure Process_Extended_Import_Export_Internal_Arg
3721         (Arg_Internal : Node_Id := Empty)
3722       is
3723       begin
3724          if No (Arg_Internal) then
3725             Error_Pragma ("Internal parameter required for pragma%");
3726          end if;
3727
3728          if Nkind (Arg_Internal) = N_Identifier then
3729             null;
3730
3731          elsif Nkind (Arg_Internal) = N_Operator_Symbol
3732            and then (Prag_Id = Pragma_Import_Function
3733                        or else
3734                      Prag_Id = Pragma_Export_Function)
3735          then
3736             null;
3737
3738          else
3739             Error_Pragma_Arg
3740               ("wrong form for Internal parameter for pragma%", Arg_Internal);
3741          end if;
3742
3743          Check_Arg_Is_Local_Name (Arg_Internal);
3744       end Process_Extended_Import_Export_Internal_Arg;
3745
3746       --------------------------------------------------
3747       -- Process_Extended_Import_Export_Object_Pragma --
3748       --------------------------------------------------
3749
3750       procedure Process_Extended_Import_Export_Object_Pragma
3751         (Arg_Internal : Node_Id;
3752          Arg_External : Node_Id;
3753          Arg_Size     : Node_Id)
3754       is
3755          Def_Id : Entity_Id;
3756
3757       begin
3758          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3759          Def_Id := Entity (Arg_Internal);
3760
3761          if not Ekind_In (Def_Id, E_Constant, E_Variable) then
3762             Error_Pragma_Arg
3763               ("pragma% must designate an object", Arg_Internal);
3764          end if;
3765
3766          if Has_Rep_Pragma (Def_Id, Name_Common_Object)
3767               or else
3768             Has_Rep_Pragma (Def_Id, Name_Psect_Object)
3769          then
3770             Error_Pragma_Arg
3771               ("previous Common/Psect_Object applies, pragma % not permitted",
3772                Arg_Internal);
3773          end if;
3774
3775          if Rep_Item_Too_Late (Def_Id, N) then
3776             raise Pragma_Exit;
3777          end if;
3778
3779          Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
3780
3781          if Present (Arg_Size) then
3782             Check_Arg_Is_External_Name (Arg_Size);
3783          end if;
3784
3785          --  Export_Object case
3786
3787          if Prag_Id = Pragma_Export_Object then
3788             if not Is_Library_Level_Entity (Def_Id) then
3789                Error_Pragma_Arg
3790                  ("argument for pragma% must be library level entity",
3791                   Arg_Internal);
3792             end if;
3793
3794             if Ekind (Current_Scope) = E_Generic_Package then
3795                Error_Pragma ("pragma& cannot appear in a generic unit");
3796             end if;
3797
3798             if not Size_Known_At_Compile_Time (Etype (Def_Id)) then
3799                Error_Pragma_Arg
3800                  ("exported object must have compile time known size",
3801                   Arg_Internal);
3802             end if;
3803
3804             if Warn_On_Export_Import and then Is_Exported (Def_Id) then
3805                Error_Msg_N ("?duplicate Export_Object pragma", N);
3806             else
3807                Set_Exported (Def_Id, Arg_Internal);
3808             end if;
3809
3810          --  Import_Object case
3811
3812          else
3813             if Is_Concurrent_Type (Etype (Def_Id)) then
3814                Error_Pragma_Arg
3815                  ("cannot use pragma% for task/protected object",
3816                   Arg_Internal);
3817             end if;
3818
3819             if Ekind (Def_Id) = E_Constant then
3820                Error_Pragma_Arg
3821                  ("cannot import a constant", Arg_Internal);
3822             end if;
3823
3824             if Warn_On_Export_Import
3825               and then Has_Discriminants (Etype (Def_Id))
3826             then
3827                Error_Msg_N
3828                  ("imported value must be initialized?", Arg_Internal);
3829             end if;
3830
3831             if Warn_On_Export_Import
3832               and then Is_Access_Type (Etype (Def_Id))
3833             then
3834                Error_Pragma_Arg
3835                  ("cannot import object of an access type?", Arg_Internal);
3836             end if;
3837
3838             if Warn_On_Export_Import
3839               and then Is_Imported (Def_Id)
3840             then
3841                Error_Msg_N
3842                  ("?duplicate Import_Object pragma", N);
3843
3844             --  Check for explicit initialization present. Note that an
3845             --  initialization generated by the code generator, e.g. for an
3846             --  access type, does not count here.
3847
3848             elsif Present (Expression (Parent (Def_Id)))
3849                and then
3850                  Comes_From_Source
3851                    (Original_Node (Expression (Parent (Def_Id))))
3852             then
3853                Error_Msg_Sloc := Sloc (Def_Id);
3854                Error_Pragma_Arg
3855                  ("imported entities cannot be initialized (RM B.1(24))",
3856                   "\no initialization allowed for & declared#", Arg1);
3857             else
3858                Set_Imported (Def_Id);
3859                Note_Possible_Modification (Arg_Internal, Sure => False);
3860             end if;
3861          end if;
3862       end Process_Extended_Import_Export_Object_Pragma;
3863
3864       ------------------------------------------------------
3865       -- Process_Extended_Import_Export_Subprogram_Pragma --
3866       ------------------------------------------------------
3867
3868       procedure Process_Extended_Import_Export_Subprogram_Pragma
3869         (Arg_Internal                 : Node_Id;
3870          Arg_External                 : Node_Id;
3871          Arg_Parameter_Types          : Node_Id;
3872          Arg_Result_Type              : Node_Id := Empty;
3873          Arg_Mechanism                : Node_Id;
3874          Arg_Result_Mechanism         : Node_Id := Empty;
3875          Arg_First_Optional_Parameter : Node_Id := Empty)
3876       is
3877          Ent       : Entity_Id;
3878          Def_Id    : Entity_Id;
3879          Hom_Id    : Entity_Id;
3880          Formal    : Entity_Id;
3881          Ambiguous : Boolean;
3882          Match     : Boolean;
3883          Dval      : Node_Id;
3884
3885          function Same_Base_Type
3886           (Ptype  : Node_Id;
3887            Formal : Entity_Id) return Boolean;
3888          --  Determines if Ptype references the type of Formal. Note that only
3889          --  the base types need to match according to the spec. Ptype here is
3890          --  the argument from the pragma, which is either a type name, or an
3891          --  access attribute.
3892
3893          --------------------
3894          -- Same_Base_Type --
3895          --------------------
3896
3897          function Same_Base_Type
3898            (Ptype  : Node_Id;
3899             Formal : Entity_Id) return Boolean
3900          is
3901             Ftyp : constant Entity_Id := Base_Type (Etype (Formal));
3902             Pref : Node_Id;
3903
3904          begin
3905             --  Case where pragma argument is typ'Access
3906
3907             if Nkind (Ptype) = N_Attribute_Reference
3908               and then Attribute_Name (Ptype) = Name_Access
3909             then
3910                Pref := Prefix (Ptype);
3911                Find_Type (Pref);
3912
3913                if not Is_Entity_Name (Pref)
3914                  or else Entity (Pref) = Any_Type
3915                then
3916                   raise Pragma_Exit;
3917                end if;
3918
3919                --  We have a match if the corresponding argument is of an
3920                --  anonymous access type, and its designated type matches the
3921                --  type of the prefix of the access attribute
3922
3923                return Ekind (Ftyp) = E_Anonymous_Access_Type
3924                  and then Base_Type (Entity (Pref)) =
3925                             Base_Type (Etype (Designated_Type (Ftyp)));
3926
3927             --  Case where pragma argument is a type name
3928
3929             else
3930                Find_Type (Ptype);
3931
3932                if not Is_Entity_Name (Ptype)
3933                  or else Entity (Ptype) = Any_Type
3934                then
3935                   raise Pragma_Exit;
3936                end if;
3937
3938                --  We have a match if the corresponding argument is of the type
3939                --  given in the pragma (comparing base types)
3940
3941                return Base_Type (Entity (Ptype)) = Ftyp;
3942             end if;
3943          end Same_Base_Type;
3944
3945       --  Start of processing for
3946       --  Process_Extended_Import_Export_Subprogram_Pragma
3947
3948       begin
3949          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3950          Ent := Empty;
3951          Ambiguous := False;
3952
3953          --  Loop through homonyms (overloadings) of the entity
3954
3955          Hom_Id := Entity (Arg_Internal);
3956          while Present (Hom_Id) loop
3957             Def_Id := Get_Base_Subprogram (Hom_Id);
3958
3959             --  We need a subprogram in the current scope
3960
3961             if not Is_Subprogram (Def_Id)
3962               or else Scope (Def_Id) /= Current_Scope
3963             then
3964                null;
3965
3966             else
3967                Match := True;
3968
3969                --  Pragma cannot apply to subprogram body
3970
3971                if Is_Subprogram (Def_Id)
3972                  and then Nkind (Parent (Declaration_Node (Def_Id))) =
3973                                                              N_Subprogram_Body
3974                then
3975                   Error_Pragma
3976                     ("pragma% requires separate spec"
3977                       & " and must come before body");
3978                end if;
3979
3980                --  Test result type if given, note that the result type
3981                --  parameter can only be present for the function cases.
3982
3983                if Present (Arg_Result_Type)
3984                  and then not Same_Base_Type (Arg_Result_Type, Def_Id)
3985                then
3986                   Match := False;
3987
3988                elsif Etype (Def_Id) /= Standard_Void_Type
3989                  and then
3990                    (Pname = Name_Export_Procedure
3991                       or else
3992                     Pname = Name_Import_Procedure)
3993                then
3994                   Match := False;
3995
3996                --  Test parameter types if given. Note that this parameter
3997                --  has not been analyzed (and must not be, since it is
3998                --  semantic nonsense), so we get it as the parser left it.
3999
4000                elsif Present (Arg_Parameter_Types) then
4001                   Check_Matching_Types : declare
4002                      Formal : Entity_Id;
4003                      Ptype  : Node_Id;
4004
4005                   begin
4006                      Formal := First_Formal (Def_Id);
4007
4008                      if Nkind (Arg_Parameter_Types) = N_Null then
4009                         if Present (Formal) then
4010                            Match := False;
4011                         end if;
4012
4013                      --  A list of one type, e.g. (List) is parsed as
4014                      --  a parenthesized expression.
4015
4016                      elsif Nkind (Arg_Parameter_Types) /= N_Aggregate
4017                        and then Paren_Count (Arg_Parameter_Types) = 1
4018                      then
4019                         if No (Formal)
4020                           or else Present (Next_Formal (Formal))
4021                         then
4022                            Match := False;
4023                         else
4024                            Match :=
4025                              Same_Base_Type (Arg_Parameter_Types, Formal);
4026                         end if;
4027
4028                      --  A list of more than one type is parsed as a aggregate
4029
4030                      elsif Nkind (Arg_Parameter_Types) = N_Aggregate
4031                        and then Paren_Count (Arg_Parameter_Types) = 0
4032                      then
4033                         Ptype := First (Expressions (Arg_Parameter_Types));
4034                         while Present (Ptype) or else Present (Formal) loop
4035                            if No (Ptype)
4036                              or else No (Formal)
4037                              or else not Same_Base_Type (Ptype, Formal)
4038                            then
4039                               Match := False;
4040                               exit;
4041                            else
4042                               Next_Formal (Formal);
4043                               Next (Ptype);
4044                            end if;
4045                         end loop;
4046
4047                      --  Anything else is of the wrong form
4048
4049                      else
4050                         Error_Pragma_Arg
4051                           ("wrong form for Parameter_Types parameter",
4052                            Arg_Parameter_Types);
4053                      end if;
4054                   end Check_Matching_Types;
4055                end if;
4056
4057                --  Match is now False if the entry we found did not match
4058                --  either a supplied Parameter_Types or Result_Types argument
4059
4060                if Match then
4061                   if No (Ent) then
4062                      Ent := Def_Id;
4063
4064                   --  Ambiguous case, the flag Ambiguous shows if we already
4065                   --  detected this and output the initial messages.
4066
4067                   else
4068                      if not Ambiguous then
4069                         Ambiguous := True;
4070                         Error_Msg_Name_1 := Pname;
4071                         Error_Msg_N
4072                           ("pragma% does not uniquely identify subprogram!",
4073                            N);
4074                         Error_Msg_Sloc := Sloc (Ent);
4075                         Error_Msg_N ("matching subprogram #!", N);
4076                         Ent := Empty;
4077                      end if;
4078
4079                      Error_Msg_Sloc := Sloc (Def_Id);
4080                      Error_Msg_N ("matching subprogram #!", N);
4081                   end if;
4082                end if;
4083             end if;
4084
4085             Hom_Id := Homonym (Hom_Id);
4086          end loop;
4087
4088          --  See if we found an entry
4089
4090          if No (Ent) then
4091             if not Ambiguous then
4092                if Is_Generic_Subprogram (Entity (Arg_Internal)) then
4093                   Error_Pragma
4094                     ("pragma% cannot be given for generic subprogram");
4095                else
4096                   Error_Pragma
4097                     ("pragma% does not identify local subprogram");
4098                end if;
4099             end if;
4100
4101             return;
4102          end if;
4103
4104          --  Import pragmas must be for imported entities
4105
4106          if Prag_Id = Pragma_Import_Function
4107               or else
4108             Prag_Id = Pragma_Import_Procedure
4109               or else
4110             Prag_Id = Pragma_Import_Valued_Procedure
4111          then
4112             if not Is_Imported (Ent) then
4113                Error_Pragma
4114                  ("pragma Import or Interface must precede pragma%");
4115             end if;
4116
4117          --  Here we have the Export case which can set the entity as exported
4118
4119          --  But does not do so if the specified external name is null, since
4120          --  that is taken as a signal in DEC Ada 83 (with which we want to be
4121          --  compatible) to request no external name.
4122
4123          elsif Nkind (Arg_External) = N_String_Literal
4124            and then String_Length (Strval (Arg_External)) = 0
4125          then
4126             null;
4127
4128          --  In all other cases, set entity as exported
4129
4130          else
4131             Set_Exported (Ent, Arg_Internal);
4132          end if;
4133
4134          --  Special processing for Valued_Procedure cases
4135
4136          if Prag_Id = Pragma_Import_Valued_Procedure
4137            or else
4138             Prag_Id = Pragma_Export_Valued_Procedure
4139          then
4140             Formal := First_Formal (Ent);
4141
4142             if No (Formal) then
4143                Error_Pragma ("at least one parameter required for pragma%");
4144
4145             elsif Ekind (Formal) /= E_Out_Parameter then
4146                Error_Pragma ("first parameter must have mode out for pragma%");
4147
4148             else
4149                Set_Is_Valued_Procedure (Ent);
4150             end if;
4151          end if;
4152
4153          Set_Extended_Import_Export_External_Name (Ent, Arg_External);
4154
4155          --  Process Result_Mechanism argument if present. We have already
4156          --  checked that this is only allowed for the function case.
4157
4158          if Present (Arg_Result_Mechanism) then
4159             Set_Mechanism_Value (Ent, Arg_Result_Mechanism);
4160          end if;
4161
4162          --  Process Mechanism parameter if present. Note that this parameter
4163          --  is not analyzed, and must not be analyzed since it is semantic
4164          --  nonsense, so we get it in exactly as the parser left it.
4165
4166          if Present (Arg_Mechanism) then
4167             declare
4168                Formal : Entity_Id;
4169                Massoc : Node_Id;
4170                Mname  : Node_Id;
4171                Choice : Node_Id;
4172
4173             begin
4174                --  A single mechanism association without a formal parameter
4175                --  name is parsed as a parenthesized expression. All other
4176                --  cases are parsed as aggregates, so we rewrite the single
4177                --  parameter case as an aggregate for consistency.
4178
4179                if Nkind (Arg_Mechanism) /= N_Aggregate
4180                  and then Paren_Count (Arg_Mechanism) = 1
4181                then
4182                   Rewrite (Arg_Mechanism,
4183                     Make_Aggregate (Sloc (Arg_Mechanism),
4184                       Expressions => New_List (
4185                         Relocate_Node (Arg_Mechanism))));
4186                end if;
4187
4188                --  Case of only mechanism name given, applies to all formals
4189
4190                if Nkind (Arg_Mechanism) /= N_Aggregate then
4191                   Formal := First_Formal (Ent);
4192                   while Present (Formal) loop
4193                      Set_Mechanism_Value (Formal, Arg_Mechanism);
4194                      Next_Formal (Formal);
4195                   end loop;
4196
4197                --  Case of list of mechanism associations given
4198
4199                else
4200                   if Null_Record_Present (Arg_Mechanism) then
4201                      Error_Pragma_Arg
4202                        ("inappropriate form for Mechanism parameter",
4203                         Arg_Mechanism);
4204                   end if;
4205
4206                   --  Deal with positional ones first
4207
4208                   Formal := First_Formal (Ent);
4209
4210                   if Present (Expressions (Arg_Mechanism)) then
4211                      Mname := First (Expressions (Arg_Mechanism));
4212                      while Present (Mname) loop
4213                         if No (Formal) then
4214                            Error_Pragma_Arg
4215                              ("too many mechanism associations", Mname);
4216                         end if;
4217
4218                         Set_Mechanism_Value (Formal, Mname);
4219                         Next_Formal (Formal);
4220                         Next (Mname);
4221                      end loop;
4222                   end if;
4223
4224                   --  Deal with named entries
4225
4226                   if Present (Component_Associations (Arg_Mechanism)) then
4227                      Massoc := First (Component_Associations (Arg_Mechanism));
4228                      while Present (Massoc) loop
4229                         Choice := First (Choices (Massoc));
4230
4231                         if Nkind (Choice) /= N_Identifier
4232                           or else Present (Next (Choice))
4233                         then
4234                            Error_Pragma_Arg
4235                              ("incorrect form for mechanism association",
4236                               Massoc);
4237                         end if;
4238
4239                         Formal := First_Formal (Ent);
4240                         loop
4241                            if No (Formal) then
4242                               Error_Pragma_Arg
4243                                 ("parameter name & not present", Choice);
4244                            end if;
4245
4246                            if Chars (Choice) = Chars (Formal) then
4247                               Set_Mechanism_Value
4248                                 (Formal, Expression (Massoc));
4249
4250                               --  Set entity on identifier (needed by ASIS)
4251
4252                               Set_Entity (Choice, Formal);
4253
4254                               exit;
4255                            end if;
4256
4257                            Next_Formal (Formal);
4258                         end loop;
4259
4260                         Next (Massoc);
4261                      end loop;
4262                   end if;
4263                end if;
4264             end;
4265          end if;
4266
4267          --  Process First_Optional_Parameter argument if present. We have
4268          --  already checked that this is only allowed for the Import case.
4269
4270          if Present (Arg_First_Optional_Parameter) then
4271             if Nkind (Arg_First_Optional_Parameter) /= N_Identifier then
4272                Error_Pragma_Arg
4273                  ("first optional parameter must be formal parameter name",
4274                   Arg_First_Optional_Parameter);
4275             end if;
4276
4277             Formal := First_Formal (Ent);
4278             loop
4279                if No (Formal) then
4280                   Error_Pragma_Arg
4281                     ("specified formal parameter& not found",
4282                      Arg_First_Optional_Parameter);
4283                end if;
4284
4285                exit when Chars (Formal) =
4286                          Chars (Arg_First_Optional_Parameter);
4287
4288                Next_Formal (Formal);
4289             end loop;
4290
4291             Set_First_Optional_Parameter (Ent, Formal);
4292
4293             --  Check specified and all remaining formals have right form
4294
4295             while Present (Formal) loop
4296                if Ekind (Formal) /= E_In_Parameter then
4297                   Error_Msg_NE
4298                     ("optional formal& is not of mode in!",
4299                      Arg_First_Optional_Parameter, Formal);
4300
4301                else
4302                   Dval := Default_Value (Formal);
4303
4304                   if No (Dval) then
4305                      Error_Msg_NE
4306                        ("optional formal& does not have default value!",
4307                         Arg_First_Optional_Parameter, Formal);
4308
4309                   elsif Compile_Time_Known_Value_Or_Aggr (Dval) then
4310                      null;
4311
4312                   else
4313                      Error_Msg_FE
4314                        ("default value for optional formal& is non-static!",
4315                         Arg_First_Optional_Parameter, Formal);
4316                   end if;
4317                end if;
4318
4319                Set_Is_Optional_Parameter (Formal);
4320                Next_Formal (Formal);
4321             end loop;
4322          end if;
4323       end Process_Extended_Import_Export_Subprogram_Pragma;
4324
4325       --------------------------
4326       -- Process_Generic_List --
4327       --------------------------
4328
4329       procedure Process_Generic_List is
4330          Arg : Node_Id;
4331          Exp : Node_Id;
4332
4333       begin
4334          Check_No_Identifiers;
4335          Check_At_Least_N_Arguments (1);
4336
4337          Arg := Arg1;
4338          while Present (Arg) loop
4339             Exp := Get_Pragma_Arg (Arg);
4340             Analyze (Exp);
4341
4342             if not Is_Entity_Name (Exp)
4343               or else
4344                 (not Is_Generic_Instance (Entity (Exp))
4345                   and then
4346                  not Is_Generic_Unit (Entity (Exp)))
4347             then
4348                Error_Pragma_Arg
4349                  ("pragma% argument must be name of generic unit/instance",
4350                   Arg);
4351             end if;
4352
4353             Next (Arg);
4354          end loop;
4355       end Process_Generic_List;
4356
4357       ------------------------------------
4358       -- Process_Import_Predefined_Type --
4359       ------------------------------------
4360
4361       procedure Process_Import_Predefined_Type is
4362          Loc  : constant Source_Ptr := Sloc (N);
4363          Elmt : Elmt_Id;
4364          Ftyp : Node_Id := Empty;
4365          Decl : Node_Id;
4366          Def  : Node_Id;
4367          Nam  : Name_Id;
4368
4369       begin
4370          String_To_Name_Buffer (Strval (Expression (Arg3)));
4371          Nam := Name_Find;
4372
4373          Elmt := First_Elmt (Predefined_Float_Types);
4374          while Present (Elmt) and then Chars (Node (Elmt)) /= Nam loop
4375             Next_Elmt (Elmt);
4376          end loop;
4377
4378          Ftyp := Node (Elmt);
4379
4380          if Present (Ftyp) then
4381
4382             --  Don't build a derived type declaration, because predefined C
4383             --  types have no declaration anywhere, so cannot really be named.
4384             --  Instead build a full type declaration, starting with an
4385             --  appropriate type definition is built
4386
4387             if Is_Floating_Point_Type (Ftyp) then
4388                Def := Make_Floating_Point_Definition (Loc,
4389                  Make_Integer_Literal (Loc, Digits_Value (Ftyp)),
4390                  Make_Real_Range_Specification (Loc,
4391                    Make_Real_Literal (Loc, Realval (Type_Low_Bound (Ftyp))),
4392                    Make_Real_Literal (Loc, Realval (Type_High_Bound (Ftyp)))));
4393
4394             --  Should never have a predefined type we cannot handle
4395
4396             else
4397                raise Program_Error;
4398             end if;
4399
4400             --  Build and insert a Full_Type_Declaration, which will be
4401             --  analyzed as soon as this list entry has been analyzed.
4402
4403             Decl := Make_Full_Type_Declaration (Loc,
4404               Make_Defining_Identifier (Loc, Chars (Expression (Arg2))),
4405               Type_Definition => Def);
4406
4407             Insert_After (N, Decl);
4408             Mark_Rewrite_Insertion (Decl);
4409
4410          else
4411             Error_Pragma_Arg ("no matching type found for pragma%",
4412             Arg2);
4413          end if;
4414       end Process_Import_Predefined_Type;
4415
4416       ---------------------------------
4417       -- Process_Import_Or_Interface --
4418       ---------------------------------
4419
4420       procedure Process_Import_Or_Interface is
4421          C      : Convention_Id;
4422          Def_Id : Entity_Id;
4423          Hom_Id : Entity_Id;
4424
4425       begin
4426          Process_Convention (C, Def_Id);
4427          Kill_Size_Check_Code (Def_Id);
4428          Note_Possible_Modification (Get_Pragma_Arg (Arg2), Sure => False);
4429
4430          if Ekind_In (Def_Id, E_Variable, E_Constant) then
4431
4432             --  We do not permit Import to apply to a renaming declaration
4433
4434             if Present (Renamed_Object (Def_Id)) then
4435                Error_Pragma_Arg
4436                  ("pragma% not allowed for object renaming", Arg2);
4437
4438             --  User initialization is not allowed for imported object, but
4439             --  the object declaration may contain a default initialization,
4440             --  that will be discarded. Note that an explicit initialization
4441             --  only counts if it comes from source, otherwise it is simply
4442             --  the code generator making an implicit initialization explicit.
4443
4444             elsif Present (Expression (Parent (Def_Id)))
4445               and then Comes_From_Source (Expression (Parent (Def_Id)))
4446             then
4447                Error_Msg_Sloc := Sloc (Def_Id);
4448                Error_Pragma_Arg
4449                  ("no initialization allowed for declaration of& #",
4450                   "\imported entities cannot be initialized (RM B.1(24))",
4451                   Arg2);
4452
4453             else
4454                Set_Imported (Def_Id);
4455                Process_Interface_Name (Def_Id, Arg3, Arg4);
4456
4457                --  Note that we do not set Is_Public here. That's because we
4458                --  only want to set it if there is no address clause, and we
4459                --  don't know that yet, so we delay that processing till
4460                --  freeze time.
4461
4462                --  pragma Import completes deferred constants
4463
4464                if Ekind (Def_Id) = E_Constant then
4465                   Set_Has_Completion (Def_Id);
4466                end if;
4467
4468                --  It is not possible to import a constant of an unconstrained
4469                --  array type (e.g. string) because there is no simple way to
4470                --  write a meaningful subtype for it.
4471
4472                if Is_Array_Type (Etype (Def_Id))
4473                  and then not Is_Constrained (Etype (Def_Id))
4474                then
4475                   Error_Msg_NE
4476                     ("imported constant& must have a constrained subtype",
4477                       N, Def_Id);
4478                end if;
4479             end if;
4480
4481          elsif Is_Subprogram (Def_Id)
4482            or else Is_Generic_Subprogram (Def_Id)
4483          then
4484             --  If the name is overloaded, pragma applies to all of the denoted
4485             --  entities in the same declarative part.
4486
4487             Hom_Id := Def_Id;
4488             while Present (Hom_Id) loop
4489                Def_Id := Get_Base_Subprogram (Hom_Id);
4490
4491                --  Ignore inherited subprograms because the pragma will apply
4492                --  to the parent operation, which is the one called.
4493
4494                if Is_Overloadable (Def_Id)
4495                  and then Present (Alias (Def_Id))
4496                then
4497                   null;
4498
4499                --  If it is not a subprogram, it must be in an outer scope and
4500                --  pragma does not apply.
4501
4502                elsif not Is_Subprogram (Def_Id)
4503                  and then not Is_Generic_Subprogram (Def_Id)
4504                then
4505                   null;
4506
4507                --  The pragma does not apply to primitives of interfaces
4508
4509                elsif Is_Dispatching_Operation (Def_Id)
4510                  and then Present (Find_Dispatching_Type (Def_Id))
4511                  and then Is_Interface (Find_Dispatching_Type (Def_Id))
4512                then
4513                   null;
4514
4515                --  Verify that the homonym is in the same declarative part (not
4516                --  just the same scope).
4517
4518                elsif Parent (Unit_Declaration_Node (Def_Id)) /= Parent (N)
4519                  and then Nkind (Parent (N)) /= N_Compilation_Unit_Aux
4520                then
4521                   exit;
4522
4523                else
4524                   Set_Imported (Def_Id);
4525
4526                   --  Reject an Import applied to an abstract subprogram
4527
4528                   if Is_Subprogram (Def_Id)
4529                     and then Is_Abstract_Subprogram (Def_Id)
4530                   then
4531                      Error_Msg_Sloc := Sloc (Def_Id);
4532                      Error_Msg_NE
4533                        ("cannot import abstract subprogram& declared#",
4534                         Arg2, Def_Id);
4535                   end if;
4536
4537                   --  Special processing for Convention_Intrinsic
4538
4539                   if C = Convention_Intrinsic then
4540
4541                      --  Link_Name argument not allowed for intrinsic
4542
4543                      Check_No_Link_Name;
4544
4545                      Set_Is_Intrinsic_Subprogram (Def_Id);
4546
4547                      --  If no external name is present, then check that this
4548                      --  is a valid intrinsic subprogram. If an external name
4549                      --  is present, then this is handled by the back end.
4550
4551                      if No (Arg3) then
4552                         Check_Intrinsic_Subprogram
4553                           (Def_Id, Get_Pragma_Arg (Arg2));
4554                      end if;
4555                   end if;
4556
4557                   --  All interfaced procedures need an external symbol created
4558                   --  for them since they are always referenced from another
4559                   --  object file.
4560
4561                   Set_Is_Public (Def_Id);
4562
4563                   --  Verify that the subprogram does not have a completion
4564                   --  through a renaming declaration. For other completions the
4565                   --  pragma appears as a too late representation.
4566
4567                   declare
4568                      Decl : constant Node_Id := Unit_Declaration_Node (Def_Id);
4569
4570                   begin
4571                      if Present (Decl)
4572                        and then Nkind (Decl) = N_Subprogram_Declaration
4573                        and then Present (Corresponding_Body (Decl))
4574                        and then Nkind (Unit_Declaration_Node
4575                                         (Corresponding_Body (Decl))) =
4576                                              N_Subprogram_Renaming_Declaration
4577                      then
4578                         Error_Msg_Sloc := Sloc (Def_Id);
4579                         Error_Msg_NE
4580                           ("cannot import&, renaming already provided for " &
4581                            "declaration #", N, Def_Id);
4582                      end if;
4583                   end;
4584
4585                   Set_Has_Completion (Def_Id);
4586                   Process_Interface_Name (Def_Id, Arg3, Arg4);
4587                end if;
4588
4589                if Is_Compilation_Unit (Hom_Id) then
4590
4591                   --  Its possible homonyms are not affected by the pragma.
4592                   --  Such homonyms might be present in the context of other
4593                   --  units being compiled.
4594
4595                   exit;
4596
4597                else
4598                   Hom_Id := Homonym (Hom_Id);
4599                end if;
4600             end loop;
4601
4602          --  When the convention is Java or CIL, we also allow Import to be
4603          --  given for packages, generic packages, exceptions, record
4604          --  components, and access to subprograms.
4605
4606          elsif (C = Convention_Java or else C = Convention_CIL)
4607            and then
4608              (Is_Package_Or_Generic_Package (Def_Id)
4609                or else Ekind (Def_Id) = E_Exception
4610                or else Ekind (Def_Id) = E_Access_Subprogram_Type
4611                or else Nkind (Parent (Def_Id)) = N_Component_Declaration)
4612          then
4613             Set_Imported (Def_Id);
4614             Set_Is_Public (Def_Id);
4615             Process_Interface_Name (Def_Id, Arg3, Arg4);
4616
4617          --  Import a CPP class
4618
4619          elsif Is_Record_Type (Def_Id)
4620            and then C = Convention_CPP
4621          then
4622             --  Types treated as CPP classes must be declared limited (note:
4623             --  this used to be a warning but there is no real benefit to it
4624             --  since we did effectively intend to treat the type as limited
4625             --  anyway).
4626
4627             if not Is_Limited_Type (Def_Id) then
4628                Error_Msg_N
4629                  ("imported 'C'P'P type must be limited",
4630                   Get_Pragma_Arg (Arg2));
4631             end if;
4632
4633             Set_Is_CPP_Class (Def_Id);
4634
4635             --  Imported CPP types must not have discriminants (because C++
4636             --  classes do not have discriminants).
4637
4638             if Has_Discriminants (Def_Id) then
4639                Error_Msg_N
4640                  ("imported 'C'P'P type cannot have discriminants",
4641                   First (Discriminant_Specifications
4642                           (Declaration_Node (Def_Id))));
4643             end if;
4644
4645             --  Components of imported CPP types must not have default
4646             --  expressions because the constructor (if any) is on the
4647             --  C++ side.
4648
4649             declare
4650                Tdef  : constant Node_Id :=
4651                          Type_Definition (Declaration_Node (Def_Id));
4652                Clist : Node_Id;
4653                Comp  : Node_Id;
4654
4655             begin
4656                if Nkind (Tdef) = N_Record_Definition then
4657                   Clist := Component_List (Tdef);
4658
4659                else
4660                   pragma Assert (Nkind (Tdef) = N_Derived_Type_Definition);
4661                   Clist := Component_List (Record_Extension_Part (Tdef));
4662                end if;
4663
4664                if Present (Clist) then
4665                   Comp := First (Component_Items (Clist));
4666                   while Present (Comp) loop
4667                      if Present (Expression (Comp)) then
4668                         Error_Msg_N
4669                           ("component of imported 'C'P'P type cannot have" &
4670                            " default expression", Expression (Comp));
4671                      end if;
4672
4673                      Next (Comp);
4674                   end loop;
4675                end if;
4676             end;
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             Rewrite (N, Make_Implicit_If_Statement (N,
7992               Condition => Cond,
7993                  Then_Statements => New_List (
7994                    Make_Block_Statement (Loc,
7995                      Handled_Statement_Sequence =>
7996                        Make_Handled_Sequence_Of_Statements (Loc,
7997                          Statements => New_List (Relocate_Node (Call)))))));
7998             Analyze (N);
7999          end Debug;
8000
8001          ------------------
8002          -- Debug_Policy --
8003          ------------------
8004
8005          --  pragma Debug_Policy (Check | Ignore)
8006
8007          when Pragma_Debug_Policy =>
8008             GNAT_Pragma;
8009             Check_Arg_Count (1);
8010             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Disable, Name_Ignore);
8011             Debug_Pragmas_Enabled :=
8012               Chars (Get_Pragma_Arg (Arg1)) = Name_Check;
8013             Debug_Pragmas_Disabled :=
8014               Chars (Get_Pragma_Arg (Arg1)) = Name_Disable;
8015
8016          ---------------------
8017          -- Detect_Blocking --
8018          ---------------------
8019
8020          --  pragma Detect_Blocking;
8021
8022          when Pragma_Detect_Blocking =>
8023             Ada_2005_Pragma;
8024             Check_Arg_Count (0);
8025             Check_Valid_Configuration_Pragma;
8026             Detect_Blocking := True;
8027
8028          --------------------------
8029          -- Default_Storage_Pool --
8030          --------------------------
8031
8032          --  pragma Default_Storage_Pool (storage_pool_NAME | null);
8033
8034          when Pragma_Default_Storage_Pool =>
8035             Ada_2012_Pragma;
8036             Check_Arg_Count (1);
8037
8038             --  Default_Storage_Pool can appear as a configuration pragma, or
8039             --  in a declarative part or a package spec.
8040
8041             if not Is_Configuration_Pragma then
8042                Check_Is_In_Decl_Part_Or_Package_Spec;
8043             end if;
8044
8045             --  Case of Default_Storage_Pool (null);
8046
8047             if Nkind (Expression (Arg1)) = N_Null then
8048                Analyze (Expression (Arg1));
8049
8050                --  This is an odd case, this is not really an expression, so
8051                --  we don't have a type for it. So just set the type to Empty.
8052
8053                Set_Etype (Expression (Arg1), Empty);
8054
8055             --  Case of Default_Storage_Pool (storage_pool_NAME);
8056
8057             else
8058                --  If it's a configuration pragma, then the only allowed
8059                --  argument is "null".
8060
8061                if Is_Configuration_Pragma then
8062                   Error_Pragma_Arg ("NULL expected", Arg1);
8063                end if;
8064
8065                --  The expected type for a non-"null" argument is
8066                --  Root_Storage_Pool'Class.
8067
8068                Analyze_And_Resolve
8069                  (Get_Pragma_Arg (Arg1),
8070                   Typ => Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
8071             end if;
8072
8073             --  Finally, record the pool name (or null). Freeze.Freeze_Entity
8074             --  for an access type will use this information to set the
8075             --  appropriate attributes of the access type.
8076
8077             Default_Pool := Expression (Arg1);
8078
8079          ---------------
8080          -- Dimension --
8081          ---------------
8082
8083          when Pragma_Dimension =>
8084             GNAT_Pragma;
8085             Check_Arg_Count (4);
8086             Check_No_Identifiers;
8087             Check_Arg_Is_Local_Name (Arg1);
8088
8089             if not Is_Type (Arg1) then
8090                Error_Pragma ("first argument for pragma% must be subtype");
8091             end if;
8092
8093             Check_Arg_Is_Static_Expression (Arg2, Standard_Integer);
8094             Check_Arg_Is_Static_Expression (Arg3, Standard_Integer);
8095             Check_Arg_Is_Static_Expression (Arg4, Standard_Integer);
8096
8097          ------------------------------------
8098          -- Disable_Atomic_Synchronization --
8099          ------------------------------------
8100
8101          --  pragma Disable_Atomic_Synchronization [(Entity)];
8102
8103          when Pragma_Disable_Atomic_Synchronization =>
8104             Process_Disable_Enable_Atomic_Sync (Name_Suppress);
8105
8106          -------------------
8107          -- Discard_Names --
8108          -------------------
8109
8110          --  pragma Discard_Names [([On =>] LOCAL_NAME)];
8111
8112          when Pragma_Discard_Names => Discard_Names : declare
8113             E    : Entity_Id;
8114             E_Id : Entity_Id;
8115
8116          begin
8117             Check_Ada_83_Warning;
8118
8119             --  Deal with configuration pragma case
8120
8121             if Arg_Count = 0 and then Is_Configuration_Pragma then
8122                Global_Discard_Names := True;
8123                return;
8124
8125             --  Otherwise, check correct appropriate context
8126
8127             else
8128                Check_Is_In_Decl_Part_Or_Package_Spec;
8129
8130                if Arg_Count = 0 then
8131
8132                   --  If there is no parameter, then from now on this pragma
8133                   --  applies to any enumeration, exception or tagged type
8134                   --  defined in the current declarative part, and recursively
8135                   --  to any nested scope.
8136
8137                   Set_Discard_Names (Current_Scope);
8138                   return;
8139
8140                else
8141                   Check_Arg_Count (1);
8142                   Check_Optional_Identifier (Arg1, Name_On);
8143                   Check_Arg_Is_Local_Name (Arg1);
8144
8145                   E_Id := Get_Pragma_Arg (Arg1);
8146
8147                   if Etype (E_Id) = Any_Type then
8148                      return;
8149                   else
8150                      E := Entity (E_Id);
8151                   end if;
8152
8153                   if (Is_First_Subtype (E)
8154                       and then
8155                         (Is_Enumeration_Type (E) or else Is_Tagged_Type (E)))
8156                     or else Ekind (E) = E_Exception
8157                   then
8158                      Set_Discard_Names (E);
8159                   else
8160                      Error_Pragma_Arg
8161                        ("inappropriate entity for pragma%", Arg1);
8162                   end if;
8163
8164                end if;
8165             end if;
8166          end Discard_Names;
8167
8168          ------------------------
8169          -- Dispatching_Domain --
8170          ------------------------
8171
8172          --  pragma Dispatching_Domain (EXPRESSION);
8173
8174          when Pragma_Dispatching_Domain => Dispatching_Domain : declare
8175             P   : constant Node_Id := Parent (N);
8176             Arg : Node_Id;
8177
8178          begin
8179             Ada_2012_Pragma;
8180             Check_No_Identifiers;
8181             Check_Arg_Count (1);
8182
8183             --  This pragma is born obsolete, but not the aspect
8184
8185             if not From_Aspect_Specification (N) then
8186                Check_Restriction
8187                  (No_Obsolescent_Features, Pragma_Identifier (N));
8188             end if;
8189
8190             if Nkind (P) = N_Task_Definition then
8191                Arg := Get_Pragma_Arg (Arg1);
8192
8193                --  The expression must be analyzed in the special manner
8194                --  described in "Handling of Default and Per-Object
8195                --  Expressions" in sem.ads.
8196
8197                Preanalyze_Spec_Expression (Arg, RTE (RE_Dispatching_Domain));
8198
8199             --  Anything else is incorrect
8200
8201             else
8202                Pragma_Misplaced;
8203             end if;
8204
8205             if Has_Pragma_Dispatching_Domain (P) then
8206                Error_Pragma ("duplicate pragma% not allowed");
8207             else
8208                Set_Has_Pragma_Dispatching_Domain (P, True);
8209
8210                if Nkind (P) = N_Task_Definition then
8211                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
8212                end if;
8213             end if;
8214          end Dispatching_Domain;
8215
8216          ---------------
8217          -- Elaborate --
8218          ---------------
8219
8220          --  pragma Elaborate (library_unit_NAME {, library_unit_NAME});
8221
8222          when Pragma_Elaborate => Elaborate : declare
8223             Arg   : Node_Id;
8224             Citem : Node_Id;
8225
8226          begin
8227             --  Pragma must be in context items list of a compilation unit
8228
8229             if not Is_In_Context_Clause then
8230                Pragma_Misplaced;
8231             end if;
8232
8233             --  Must be at least one argument
8234
8235             if Arg_Count = 0 then
8236                Error_Pragma ("pragma% requires at least one argument");
8237             end if;
8238
8239             --  In Ada 83 mode, there can be no items following it in the
8240             --  context list except other pragmas and implicit with clauses
8241             --  (e.g. those added by use of Rtsfind). In Ada 95 mode, this
8242             --  placement rule does not apply.
8243
8244             if Ada_Version = Ada_83 and then Comes_From_Source (N) then
8245                Citem := Next (N);
8246                while Present (Citem) loop
8247                   if Nkind (Citem) = N_Pragma
8248                     or else (Nkind (Citem) = N_With_Clause
8249                               and then Implicit_With (Citem))
8250                   then
8251                      null;
8252                   else
8253                      Error_Pragma
8254                        ("(Ada 83) pragma% must be at end of context clause");
8255                   end if;
8256
8257                   Next (Citem);
8258                end loop;
8259             end if;
8260
8261             --  Finally, the arguments must all be units mentioned in a with
8262             --  clause in the same context clause. Note we already checked (in
8263             --  Par.Prag) that the arguments are all identifiers or selected
8264             --  components.
8265
8266             Arg := Arg1;
8267             Outer : while Present (Arg) loop
8268                Citem := First (List_Containing (N));
8269                Inner : while Citem /= N loop
8270                   if Nkind (Citem) = N_With_Clause
8271                     and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
8272                   then
8273                      Set_Elaborate_Present (Citem, True);
8274                      Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
8275                      Generate_Reference (Entity (Name (Citem)), Citem);
8276
8277                      --  With the pragma present, elaboration calls on
8278                      --  subprograms from the named unit need no further
8279                      --  checks, as long as the pragma appears in the current
8280                      --  compilation unit. If the pragma appears in some unit
8281                      --  in the context, there might still be a need for an
8282                      --  Elaborate_All_Desirable from the current compilation
8283                      --  to the named unit, so we keep the check enabled.
8284
8285                      if In_Extended_Main_Source_Unit (N) then
8286                         Set_Suppress_Elaboration_Warnings
8287                           (Entity (Name (Citem)));
8288                      end if;
8289
8290                      exit Inner;
8291                   end if;
8292
8293                   Next (Citem);
8294                end loop Inner;
8295
8296                if Citem = N then
8297                   Error_Pragma_Arg
8298                     ("argument of pragma% is not with'ed unit", Arg);
8299                end if;
8300
8301                Next (Arg);
8302             end loop Outer;
8303
8304             --  Give a warning if operating in static mode with -gnatwl
8305             --  (elaboration warnings enabled) switch set.
8306
8307             if Elab_Warnings and not Dynamic_Elaboration_Checks then
8308                Error_Msg_N
8309                  ("?use of pragma Elaborate may not be safe", N);
8310                Error_Msg_N
8311                  ("?use pragma Elaborate_All instead if possible", N);
8312             end if;
8313          end Elaborate;
8314
8315          -------------------
8316          -- Elaborate_All --
8317          -------------------
8318
8319          --  pragma Elaborate_All (library_unit_NAME {, library_unit_NAME});
8320
8321          when Pragma_Elaborate_All => Elaborate_All : declare
8322             Arg   : Node_Id;
8323             Citem : Node_Id;
8324
8325          begin
8326             Check_Ada_83_Warning;
8327
8328             --  Pragma must be in context items list of a compilation unit
8329
8330             if not Is_In_Context_Clause then
8331                Pragma_Misplaced;
8332             end if;
8333
8334             --  Must be at least one argument
8335
8336             if Arg_Count = 0 then
8337                Error_Pragma ("pragma% requires at least one argument");
8338             end if;
8339
8340             --  Note: unlike pragma Elaborate, pragma Elaborate_All does not
8341             --  have to appear at the end of the context clause, but may
8342             --  appear mixed in with other items, even in Ada 83 mode.
8343
8344             --  Final check: the arguments must all be units mentioned in
8345             --  a with clause in the same context clause. Note that we
8346             --  already checked (in Par.Prag) that all the arguments are
8347             --  either identifiers or selected components.
8348
8349             Arg := Arg1;
8350             Outr : while Present (Arg) loop
8351                Citem := First (List_Containing (N));
8352                Innr : while Citem /= N loop
8353                   if Nkind (Citem) = N_With_Clause
8354                     and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
8355                   then
8356                      Set_Elaborate_All_Present (Citem, True);
8357                      Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
8358
8359                      --  Suppress warnings and elaboration checks on the named
8360                      --  unit if the pragma is in the current compilation, as
8361                      --  for pragma Elaborate.
8362
8363                      if In_Extended_Main_Source_Unit (N) then
8364                         Set_Suppress_Elaboration_Warnings
8365                           (Entity (Name (Citem)));
8366                      end if;
8367                      exit Innr;
8368                   end if;
8369
8370                   Next (Citem);
8371                end loop Innr;
8372
8373                if Citem = N then
8374                   Set_Error_Posted (N);
8375                   Error_Pragma_Arg
8376                     ("argument of pragma% is not with'ed unit", Arg);
8377                end if;
8378
8379                Next (Arg);
8380             end loop Outr;
8381          end Elaborate_All;
8382
8383          --------------------
8384          -- Elaborate_Body --
8385          --------------------
8386
8387          --  pragma Elaborate_Body [( library_unit_NAME )];
8388
8389          when Pragma_Elaborate_Body => Elaborate_Body : declare
8390             Cunit_Node : Node_Id;
8391             Cunit_Ent  : Entity_Id;
8392
8393          begin
8394             Check_Ada_83_Warning;
8395             Check_Valid_Library_Unit_Pragma;
8396
8397             if Nkind (N) = N_Null_Statement then
8398                return;
8399             end if;
8400
8401             Cunit_Node := Cunit (Current_Sem_Unit);
8402             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
8403
8404             if Nkind_In (Unit (Cunit_Node), N_Package_Body,
8405                                             N_Subprogram_Body)
8406             then
8407                Error_Pragma ("pragma% must refer to a spec, not a body");
8408             else
8409                Set_Body_Required (Cunit_Node, True);
8410                Set_Has_Pragma_Elaborate_Body (Cunit_Ent);
8411
8412                --  If we are in dynamic elaboration mode, then we suppress
8413                --  elaboration warnings for the unit, since it is definitely
8414                --  fine NOT to do dynamic checks at the first level (and such
8415                --  checks will be suppressed because no elaboration boolean
8416                --  is created for Elaborate_Body packages).
8417
8418                --  But in the static model of elaboration, Elaborate_Body is
8419                --  definitely NOT good enough to ensure elaboration safety on
8420                --  its own, since the body may WITH other units that are not
8421                --  safe from an elaboration point of view, so a client must
8422                --  still do an Elaborate_All on such units.
8423
8424                --  Debug flag -gnatdD restores the old behavior of 3.13, where
8425                --  Elaborate_Body always suppressed elab warnings.
8426
8427                if Dynamic_Elaboration_Checks or Debug_Flag_DD then
8428                   Set_Suppress_Elaboration_Warnings (Cunit_Ent);
8429                end if;
8430             end if;
8431          end Elaborate_Body;
8432
8433          ------------------------
8434          -- Elaboration_Checks --
8435          ------------------------
8436
8437          --  pragma Elaboration_Checks (Static | Dynamic);
8438
8439          when Pragma_Elaboration_Checks =>
8440             GNAT_Pragma;
8441             Check_Arg_Count (1);
8442             Check_Arg_Is_One_Of (Arg1, Name_Static, Name_Dynamic);
8443             Dynamic_Elaboration_Checks :=
8444               (Chars (Get_Pragma_Arg (Arg1)) = Name_Dynamic);
8445
8446          ---------------
8447          -- Eliminate --
8448          ---------------
8449
8450          --  pragma Eliminate (
8451          --      [Unit_Name  =>] IDENTIFIER | SELECTED_COMPONENT,
8452          --    [,[Entity     =>] IDENTIFIER |
8453          --                      SELECTED_COMPONENT |
8454          --                      STRING_LITERAL]
8455          --    [,                OVERLOADING_RESOLUTION]);
8456
8457          --  OVERLOADING_RESOLUTION ::= PARAMETER_AND_RESULT_TYPE_PROFILE |
8458          --                             SOURCE_LOCATION
8459
8460          --  PARAMETER_AND_RESULT_TYPE_PROFILE ::= PROCEDURE_PROFILE |
8461          --                                        FUNCTION_PROFILE
8462
8463          --  PROCEDURE_PROFILE ::= Parameter_Types => PARAMETER_TYPES
8464
8465          --  FUNCTION_PROFILE ::= [Parameter_Types => PARAMETER_TYPES,]
8466          --                       Result_Type => result_SUBTYPE_NAME]
8467
8468          --  PARAMETER_TYPES ::= (SUBTYPE_NAME {, SUBTYPE_NAME})
8469          --  SUBTYPE_NAME    ::= STRING_LITERAL
8470
8471          --  SOURCE_LOCATION ::= Source_Location => SOURCE_TRACE
8472          --  SOURCE_TRACE    ::= STRING_LITERAL
8473
8474          when Pragma_Eliminate => Eliminate : declare
8475             Args  : Args_List (1 .. 5);
8476             Names : constant Name_List (1 .. 5) := (
8477                       Name_Unit_Name,
8478                       Name_Entity,
8479                       Name_Parameter_Types,
8480                       Name_Result_Type,
8481                       Name_Source_Location);
8482
8483             Unit_Name       : Node_Id renames Args (1);
8484             Entity          : Node_Id renames Args (2);
8485             Parameter_Types : Node_Id renames Args (3);
8486             Result_Type     : Node_Id renames Args (4);
8487             Source_Location : Node_Id renames Args (5);
8488
8489          begin
8490             GNAT_Pragma;
8491             Check_Valid_Configuration_Pragma;
8492             Gather_Associations (Names, Args);
8493
8494             if No (Unit_Name) then
8495                Error_Pragma ("missing Unit_Name argument for pragma%");
8496             end if;
8497
8498             if No (Entity)
8499               and then (Present (Parameter_Types)
8500                           or else
8501                         Present (Result_Type)
8502                           or else
8503                         Present (Source_Location))
8504             then
8505                Error_Pragma ("missing Entity argument for pragma%");
8506             end if;
8507
8508             if (Present (Parameter_Types)
8509                   or else
8510                 Present (Result_Type))
8511               and then
8512                 Present (Source_Location)
8513             then
8514                Error_Pragma
8515                  ("parameter profile and source location cannot " &
8516                   "be used together in pragma%");
8517             end if;
8518
8519             Process_Eliminate_Pragma
8520               (N,
8521                Unit_Name,
8522                Entity,
8523                Parameter_Types,
8524                Result_Type,
8525                Source_Location);
8526          end Eliminate;
8527
8528          -----------------------------------
8529          -- Enable_Atomic_Synchronization --
8530          -----------------------------------
8531
8532          --  pragma Enable_Atomic_Synchronization [(Entity)];
8533
8534          when Pragma_Enable_Atomic_Synchronization =>
8535             Process_Disable_Enable_Atomic_Sync (Name_Unsuppress);
8536
8537          ------------
8538          -- Export --
8539          ------------
8540
8541          --  pragma Export (
8542          --    [   Convention    =>] convention_IDENTIFIER,
8543          --    [   Entity        =>] local_NAME
8544          --    [, [External_Name =>] static_string_EXPRESSION ]
8545          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
8546
8547          when Pragma_Export => Export : declare
8548             C      : Convention_Id;
8549             Def_Id : Entity_Id;
8550
8551             pragma Warnings (Off, C);
8552
8553          begin
8554             Check_Ada_83_Warning;
8555             Check_Arg_Order
8556               ((Name_Convention,
8557                 Name_Entity,
8558                 Name_External_Name,
8559                 Name_Link_Name));
8560             Check_At_Least_N_Arguments (2);
8561             Check_At_Most_N_Arguments  (4);
8562             Process_Convention (C, Def_Id);
8563
8564             if Ekind (Def_Id) /= E_Constant then
8565                Note_Possible_Modification
8566                  (Get_Pragma_Arg (Arg2), Sure => False);
8567             end if;
8568
8569             Process_Interface_Name (Def_Id, Arg3, Arg4);
8570             Set_Exported (Def_Id, Arg2);
8571
8572             --  If the entity is a deferred constant, propagate the information
8573             --  to the full view, because gigi elaborates the full view only.
8574
8575             if Ekind (Def_Id) = E_Constant
8576               and then Present (Full_View (Def_Id))
8577             then
8578                declare
8579                   Id2 : constant Entity_Id := Full_View (Def_Id);
8580                begin
8581                   Set_Is_Exported    (Id2, Is_Exported          (Def_Id));
8582                   Set_First_Rep_Item (Id2, First_Rep_Item       (Def_Id));
8583                   Set_Interface_Name (Id2, Einfo.Interface_Name (Def_Id));
8584                end;
8585             end if;
8586          end Export;
8587
8588          ----------------------
8589          -- Export_Exception --
8590          ----------------------
8591
8592          --  pragma Export_Exception (
8593          --        [Internal         =>] LOCAL_NAME
8594          --     [, [External         =>] EXTERNAL_SYMBOL]
8595          --     [, [Form     =>] Ada | VMS]
8596          --     [, [Code     =>] static_integer_EXPRESSION]);
8597
8598          when Pragma_Export_Exception => Export_Exception : declare
8599             Args  : Args_List (1 .. 4);
8600             Names : constant Name_List (1 .. 4) := (
8601                       Name_Internal,
8602                       Name_External,
8603                       Name_Form,
8604                       Name_Code);
8605
8606             Internal : Node_Id renames Args (1);
8607             External : Node_Id renames Args (2);
8608             Form     : Node_Id renames Args (3);
8609             Code     : Node_Id renames Args (4);
8610
8611          begin
8612             GNAT_Pragma;
8613
8614             if Inside_A_Generic then
8615                Error_Pragma ("pragma% cannot be used for generic entities");
8616             end if;
8617
8618             Gather_Associations (Names, Args);
8619             Process_Extended_Import_Export_Exception_Pragma (
8620               Arg_Internal => Internal,
8621               Arg_External => External,
8622               Arg_Form     => Form,
8623               Arg_Code     => Code);
8624
8625             if not Is_VMS_Exception (Entity (Internal)) then
8626                Set_Exported (Entity (Internal), Internal);
8627             end if;
8628          end Export_Exception;
8629
8630          ---------------------
8631          -- Export_Function --
8632          ---------------------
8633
8634          --  pragma Export_Function (
8635          --        [Internal         =>] LOCAL_NAME
8636          --     [, [External         =>] EXTERNAL_SYMBOL]
8637          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8638          --     [, [Result_Type      =>] TYPE_DESIGNATOR]
8639          --     [, [Mechanism        =>] MECHANISM]
8640          --     [, [Result_Mechanism =>] MECHANISM_NAME]);
8641
8642          --  EXTERNAL_SYMBOL ::=
8643          --    IDENTIFIER
8644          --  | static_string_EXPRESSION
8645
8646          --  PARAMETER_TYPES ::=
8647          --    null
8648          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8649
8650          --  TYPE_DESIGNATOR ::=
8651          --    subtype_NAME
8652          --  | subtype_Name ' Access
8653
8654          --  MECHANISM ::=
8655          --    MECHANISM_NAME
8656          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8657
8658          --  MECHANISM_ASSOCIATION ::=
8659          --    [formal_parameter_NAME =>] MECHANISM_NAME
8660
8661          --  MECHANISM_NAME ::=
8662          --    Value
8663          --  | Reference
8664          --  | Descriptor [([Class =>] CLASS_NAME)]
8665
8666          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8667
8668          when Pragma_Export_Function => Export_Function : declare
8669             Args  : Args_List (1 .. 6);
8670             Names : constant Name_List (1 .. 6) := (
8671                       Name_Internal,
8672                       Name_External,
8673                       Name_Parameter_Types,
8674                       Name_Result_Type,
8675                       Name_Mechanism,
8676                       Name_Result_Mechanism);
8677
8678             Internal         : Node_Id renames Args (1);
8679             External         : Node_Id renames Args (2);
8680             Parameter_Types  : Node_Id renames Args (3);
8681             Result_Type      : Node_Id renames Args (4);
8682             Mechanism        : Node_Id renames Args (5);
8683             Result_Mechanism : Node_Id renames Args (6);
8684
8685          begin
8686             GNAT_Pragma;
8687             Gather_Associations (Names, Args);
8688             Process_Extended_Import_Export_Subprogram_Pragma (
8689               Arg_Internal         => Internal,
8690               Arg_External         => External,
8691               Arg_Parameter_Types  => Parameter_Types,
8692               Arg_Result_Type      => Result_Type,
8693               Arg_Mechanism        => Mechanism,
8694               Arg_Result_Mechanism => Result_Mechanism);
8695          end Export_Function;
8696
8697          -------------------
8698          -- Export_Object --
8699          -------------------
8700
8701          --  pragma Export_Object (
8702          --        [Internal =>] LOCAL_NAME
8703          --     [, [External =>] EXTERNAL_SYMBOL]
8704          --     [, [Size     =>] EXTERNAL_SYMBOL]);
8705
8706          --  EXTERNAL_SYMBOL ::=
8707          --    IDENTIFIER
8708          --  | static_string_EXPRESSION
8709
8710          --  PARAMETER_TYPES ::=
8711          --    null
8712          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8713
8714          --  TYPE_DESIGNATOR ::=
8715          --    subtype_NAME
8716          --  | subtype_Name ' Access
8717
8718          --  MECHANISM ::=
8719          --    MECHANISM_NAME
8720          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8721
8722          --  MECHANISM_ASSOCIATION ::=
8723          --    [formal_parameter_NAME =>] MECHANISM_NAME
8724
8725          --  MECHANISM_NAME ::=
8726          --    Value
8727          --  | Reference
8728          --  | Descriptor [([Class =>] CLASS_NAME)]
8729
8730          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8731
8732          when Pragma_Export_Object => Export_Object : declare
8733             Args  : Args_List (1 .. 3);
8734             Names : constant Name_List (1 .. 3) := (
8735                       Name_Internal,
8736                       Name_External,
8737                       Name_Size);
8738
8739             Internal : Node_Id renames Args (1);
8740             External : Node_Id renames Args (2);
8741             Size     : Node_Id renames Args (3);
8742
8743          begin
8744             GNAT_Pragma;
8745             Gather_Associations (Names, Args);
8746             Process_Extended_Import_Export_Object_Pragma (
8747               Arg_Internal => Internal,
8748               Arg_External => External,
8749               Arg_Size     => Size);
8750          end Export_Object;
8751
8752          ----------------------
8753          -- Export_Procedure --
8754          ----------------------
8755
8756          --  pragma Export_Procedure (
8757          --        [Internal         =>] LOCAL_NAME
8758          --     [, [External         =>] EXTERNAL_SYMBOL]
8759          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8760          --     [, [Mechanism        =>] MECHANISM]);
8761
8762          --  EXTERNAL_SYMBOL ::=
8763          --    IDENTIFIER
8764          --  | static_string_EXPRESSION
8765
8766          --  PARAMETER_TYPES ::=
8767          --    null
8768          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8769
8770          --  TYPE_DESIGNATOR ::=
8771          --    subtype_NAME
8772          --  | subtype_Name ' Access
8773
8774          --  MECHANISM ::=
8775          --    MECHANISM_NAME
8776          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8777
8778          --  MECHANISM_ASSOCIATION ::=
8779          --    [formal_parameter_NAME =>] MECHANISM_NAME
8780
8781          --  MECHANISM_NAME ::=
8782          --    Value
8783          --  | Reference
8784          --  | Descriptor [([Class =>] CLASS_NAME)]
8785
8786          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8787
8788          when Pragma_Export_Procedure => Export_Procedure : declare
8789             Args  : Args_List (1 .. 4);
8790             Names : constant Name_List (1 .. 4) := (
8791                       Name_Internal,
8792                       Name_External,
8793                       Name_Parameter_Types,
8794                       Name_Mechanism);
8795
8796             Internal        : Node_Id renames Args (1);
8797             External        : Node_Id renames Args (2);
8798             Parameter_Types : Node_Id renames Args (3);
8799             Mechanism       : Node_Id renames Args (4);
8800
8801          begin
8802             GNAT_Pragma;
8803             Gather_Associations (Names, Args);
8804             Process_Extended_Import_Export_Subprogram_Pragma (
8805               Arg_Internal        => Internal,
8806               Arg_External        => External,
8807               Arg_Parameter_Types => Parameter_Types,
8808               Arg_Mechanism       => Mechanism);
8809          end Export_Procedure;
8810
8811          ------------------
8812          -- Export_Value --
8813          ------------------
8814
8815          --  pragma Export_Value (
8816          --     [Value     =>] static_integer_EXPRESSION,
8817          --     [Link_Name =>] static_string_EXPRESSION);
8818
8819          when Pragma_Export_Value =>
8820             GNAT_Pragma;
8821             Check_Arg_Order ((Name_Value, Name_Link_Name));
8822             Check_Arg_Count (2);
8823
8824             Check_Optional_Identifier (Arg1, Name_Value);
8825             Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
8826
8827             Check_Optional_Identifier (Arg2, Name_Link_Name);
8828             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
8829
8830          -----------------------------
8831          -- Export_Valued_Procedure --
8832          -----------------------------
8833
8834          --  pragma Export_Valued_Procedure (
8835          --        [Internal         =>] LOCAL_NAME
8836          --     [, [External         =>] EXTERNAL_SYMBOL,]
8837          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8838          --     [, [Mechanism        =>] MECHANISM]);
8839
8840          --  EXTERNAL_SYMBOL ::=
8841          --    IDENTIFIER
8842          --  | static_string_EXPRESSION
8843
8844          --  PARAMETER_TYPES ::=
8845          --    null
8846          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8847
8848          --  TYPE_DESIGNATOR ::=
8849          --    subtype_NAME
8850          --  | subtype_Name ' Access
8851
8852          --  MECHANISM ::=
8853          --    MECHANISM_NAME
8854          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8855
8856          --  MECHANISM_ASSOCIATION ::=
8857          --    [formal_parameter_NAME =>] MECHANISM_NAME
8858
8859          --  MECHANISM_NAME ::=
8860          --    Value
8861          --  | Reference
8862          --  | Descriptor [([Class =>] CLASS_NAME)]
8863
8864          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8865
8866          when Pragma_Export_Valued_Procedure =>
8867          Export_Valued_Procedure : declare
8868             Args  : Args_List (1 .. 4);
8869             Names : constant Name_List (1 .. 4) := (
8870                       Name_Internal,
8871                       Name_External,
8872                       Name_Parameter_Types,
8873                       Name_Mechanism);
8874
8875             Internal        : Node_Id renames Args (1);
8876             External        : Node_Id renames Args (2);
8877             Parameter_Types : Node_Id renames Args (3);
8878             Mechanism       : Node_Id renames Args (4);
8879
8880          begin
8881             GNAT_Pragma;
8882             Gather_Associations (Names, Args);
8883             Process_Extended_Import_Export_Subprogram_Pragma (
8884               Arg_Internal        => Internal,
8885               Arg_External        => External,
8886               Arg_Parameter_Types => Parameter_Types,
8887               Arg_Mechanism       => Mechanism);
8888          end Export_Valued_Procedure;
8889
8890          -------------------
8891          -- Extend_System --
8892          -------------------
8893
8894          --  pragma Extend_System ([Name =>] Identifier);
8895
8896          when Pragma_Extend_System => Extend_System : declare
8897          begin
8898             GNAT_Pragma;
8899             Check_Valid_Configuration_Pragma;
8900             Check_Arg_Count (1);
8901             Check_Optional_Identifier (Arg1, Name_Name);
8902             Check_Arg_Is_Identifier (Arg1);
8903
8904             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
8905
8906             if Name_Len > 4
8907               and then Name_Buffer (1 .. 4) = "aux_"
8908             then
8909                if Present (System_Extend_Pragma_Arg) then
8910                   if Chars (Get_Pragma_Arg (Arg1)) =
8911                      Chars (Expression (System_Extend_Pragma_Arg))
8912                   then
8913                      null;
8914                   else
8915                      Error_Msg_Sloc := Sloc (System_Extend_Pragma_Arg);
8916                      Error_Pragma ("pragma% conflicts with that #");
8917                   end if;
8918
8919                else
8920                   System_Extend_Pragma_Arg := Arg1;
8921
8922                   if not GNAT_Mode then
8923                      System_Extend_Unit := Arg1;
8924                   end if;
8925                end if;
8926             else
8927                Error_Pragma ("incorrect name for pragma%, must be Aux_xxx");
8928             end if;
8929          end Extend_System;
8930
8931          ------------------------
8932          -- Extensions_Allowed --
8933          ------------------------
8934
8935          --  pragma Extensions_Allowed (ON | OFF);
8936
8937          when Pragma_Extensions_Allowed =>
8938             GNAT_Pragma;
8939             Check_Arg_Count (1);
8940             Check_No_Identifiers;
8941             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
8942
8943             if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
8944                Extensions_Allowed := True;
8945                Ada_Version := Ada_Version_Type'Last;
8946
8947             else
8948                Extensions_Allowed := False;
8949                Ada_Version := Ada_Version_Explicit;
8950             end if;
8951
8952          --------------
8953          -- External --
8954          --------------
8955
8956          --  pragma External (
8957          --    [   Convention    =>] convention_IDENTIFIER,
8958          --    [   Entity        =>] local_NAME
8959          --    [, [External_Name =>] static_string_EXPRESSION ]
8960          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
8961
8962          when Pragma_External => External : declare
8963                Def_Id : Entity_Id;
8964
8965                C : Convention_Id;
8966                pragma Warnings (Off, C);
8967
8968          begin
8969             GNAT_Pragma;
8970             Check_Arg_Order
8971               ((Name_Convention,
8972                 Name_Entity,
8973                 Name_External_Name,
8974                 Name_Link_Name));
8975             Check_At_Least_N_Arguments (2);
8976             Check_At_Most_N_Arguments  (4);
8977             Process_Convention (C, Def_Id);
8978             Note_Possible_Modification
8979               (Get_Pragma_Arg (Arg2), Sure => False);
8980             Process_Interface_Name (Def_Id, Arg3, Arg4);
8981             Set_Exported (Def_Id, Arg2);
8982          end External;
8983
8984          --------------------------
8985          -- External_Name_Casing --
8986          --------------------------
8987
8988          --  pragma External_Name_Casing (
8989          --    UPPERCASE | LOWERCASE
8990          --    [, AS_IS | UPPERCASE | LOWERCASE]);
8991
8992          when Pragma_External_Name_Casing => External_Name_Casing : declare
8993          begin
8994             GNAT_Pragma;
8995             Check_No_Identifiers;
8996
8997             if Arg_Count = 2 then
8998                Check_Arg_Is_One_Of
8999                  (Arg2, Name_As_Is, Name_Uppercase, Name_Lowercase);
9000
9001                case Chars (Get_Pragma_Arg (Arg2)) is
9002                   when Name_As_Is     =>
9003                      Opt.External_Name_Exp_Casing := As_Is;
9004
9005                   when Name_Uppercase =>
9006                      Opt.External_Name_Exp_Casing := Uppercase;
9007
9008                   when Name_Lowercase =>
9009                      Opt.External_Name_Exp_Casing := Lowercase;
9010
9011                   when others =>
9012                      null;
9013                end case;
9014
9015             else
9016                Check_Arg_Count (1);
9017             end if;
9018
9019             Check_Arg_Is_One_Of (Arg1, Name_Uppercase, Name_Lowercase);
9020
9021             case Chars (Get_Pragma_Arg (Arg1)) is
9022                when Name_Uppercase =>
9023                   Opt.External_Name_Imp_Casing := Uppercase;
9024
9025                when Name_Lowercase =>
9026                   Opt.External_Name_Imp_Casing := Lowercase;
9027
9028                when others =>
9029                   null;
9030             end case;
9031          end External_Name_Casing;
9032
9033          --------------------------
9034          -- Favor_Top_Level --
9035          --------------------------
9036
9037          --  pragma Favor_Top_Level (type_NAME);
9038
9039          when Pragma_Favor_Top_Level => Favor_Top_Level : declare
9040                Named_Entity : Entity_Id;
9041
9042          begin
9043             GNAT_Pragma;
9044             Check_No_Identifiers;
9045             Check_Arg_Count (1);
9046             Check_Arg_Is_Local_Name (Arg1);
9047             Named_Entity := Entity (Get_Pragma_Arg (Arg1));
9048
9049             --  If it's an access-to-subprogram type (in particular, not a
9050             --  subtype), set the flag on that type.
9051
9052             if Is_Access_Subprogram_Type (Named_Entity) then
9053                Set_Can_Use_Internal_Rep (Named_Entity, False);
9054
9055             --  Otherwise it's an error (name denotes the wrong sort of entity)
9056
9057             else
9058                Error_Pragma_Arg
9059                  ("access-to-subprogram type expected",
9060                   Get_Pragma_Arg (Arg1));
9061             end if;
9062          end Favor_Top_Level;
9063
9064          ---------------
9065          -- Fast_Math --
9066          ---------------
9067
9068          --  pragma Fast_Math;
9069
9070          when Pragma_Fast_Math =>
9071             GNAT_Pragma;
9072             Check_No_Identifiers;
9073             Check_Valid_Configuration_Pragma;
9074             Fast_Math := True;
9075
9076          ---------------------------
9077          -- Finalize_Storage_Only --
9078          ---------------------------
9079
9080          --  pragma Finalize_Storage_Only (first_subtype_LOCAL_NAME);
9081
9082          when Pragma_Finalize_Storage_Only => Finalize_Storage : declare
9083             Assoc   : constant Node_Id := Arg1;
9084             Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
9085             Typ     : Entity_Id;
9086
9087          begin
9088             GNAT_Pragma;
9089             Check_No_Identifiers;
9090             Check_Arg_Count (1);
9091             Check_Arg_Is_Local_Name (Arg1);
9092
9093             Find_Type (Type_Id);
9094             Typ := Entity (Type_Id);
9095
9096             if Typ = Any_Type
9097               or else Rep_Item_Too_Early (Typ, N)
9098             then
9099                return;
9100             else
9101                Typ := Underlying_Type (Typ);
9102             end if;
9103
9104             if not Is_Controlled (Typ) then
9105                Error_Pragma ("pragma% must specify controlled type");
9106             end if;
9107
9108             Check_First_Subtype (Arg1);
9109
9110             if Finalize_Storage_Only (Typ) then
9111                Error_Pragma ("duplicate pragma%, only one allowed");
9112
9113             elsif not Rep_Item_Too_Late (Typ, N) then
9114                Set_Finalize_Storage_Only (Base_Type (Typ), True);
9115             end if;
9116          end Finalize_Storage;
9117
9118          --------------------------
9119          -- Float_Representation --
9120          --------------------------
9121
9122          --  pragma Float_Representation (FLOAT_REP[, float_type_LOCAL_NAME]);
9123
9124          --  FLOAT_REP ::= VAX_Float | IEEE_Float
9125
9126          when Pragma_Float_Representation => Float_Representation : declare
9127             Argx : Node_Id;
9128             Digs : Nat;
9129             Ent  : Entity_Id;
9130
9131          begin
9132             GNAT_Pragma;
9133
9134             if Arg_Count = 1 then
9135                Check_Valid_Configuration_Pragma;
9136             else
9137                Check_Arg_Count (2);
9138                Check_Optional_Identifier (Arg2, Name_Entity);
9139                Check_Arg_Is_Local_Name (Arg2);
9140             end if;
9141
9142             Check_No_Identifier (Arg1);
9143             Check_Arg_Is_One_Of (Arg1, Name_VAX_Float, Name_IEEE_Float);
9144
9145             if not OpenVMS_On_Target then
9146                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9147                   Error_Pragma
9148                     ("?pragma% ignored (applies only to Open'V'M'S)");
9149                end if;
9150
9151                return;
9152             end if;
9153
9154             --  One argument case
9155
9156             if Arg_Count = 1 then
9157                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9158                   if Opt.Float_Format = 'I' then
9159                      Error_Pragma ("'I'E'E'E format previously specified");
9160                   end if;
9161
9162                   Opt.Float_Format := 'V';
9163
9164                else
9165                   if Opt.Float_Format = 'V' then
9166                      Error_Pragma ("'V'A'X format previously specified");
9167                   end if;
9168
9169                   Opt.Float_Format := 'I';
9170                end if;
9171
9172                Set_Standard_Fpt_Formats;
9173
9174             --  Two argument case
9175
9176             else
9177                Argx := Get_Pragma_Arg (Arg2);
9178
9179                if not Is_Entity_Name (Argx)
9180                  or else not Is_Floating_Point_Type (Entity (Argx))
9181                then
9182                   Error_Pragma_Arg
9183                     ("second argument of% pragma must be floating-point type",
9184                      Arg2);
9185                end if;
9186
9187                Ent  := Entity (Argx);
9188                Digs := UI_To_Int (Digits_Value (Ent));
9189
9190                --  Two arguments, VAX_Float case
9191
9192                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9193                   case Digs is
9194                      when  6 => Set_F_Float (Ent);
9195                      when  9 => Set_D_Float (Ent);
9196                      when 15 => Set_G_Float (Ent);
9197
9198                      when others =>
9199                         Error_Pragma_Arg
9200                           ("wrong digits value, must be 6,9 or 15", Arg2);
9201                   end case;
9202
9203                --  Two arguments, IEEE_Float case
9204
9205                else
9206                   case Digs is
9207                      when  6 => Set_IEEE_Short (Ent);
9208                      when 15 => Set_IEEE_Long  (Ent);
9209
9210                      when others =>
9211                         Error_Pragma_Arg
9212                           ("wrong digits value, must be 6 or 15", Arg2);
9213                   end case;
9214                end if;
9215             end if;
9216          end Float_Representation;
9217
9218          -----------
9219          -- Ident --
9220          -----------
9221
9222          --  pragma Ident (static_string_EXPRESSION)
9223
9224          --  Note: pragma Comment shares this processing. Pragma Comment is
9225          --  identical to Ident, except that the restriction of the argument to
9226          --  31 characters and the placement restrictions are not enforced for
9227          --  pragma Comment.
9228
9229          when Pragma_Ident | Pragma_Comment => Ident : declare
9230             Str : Node_Id;
9231
9232          begin
9233             GNAT_Pragma;
9234             Check_Arg_Count (1);
9235             Check_No_Identifiers;
9236             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
9237             Store_Note (N);
9238
9239             --  For pragma Ident, preserve DEC compatibility by requiring the
9240             --  pragma to appear in a declarative part or package spec.
9241
9242             if Prag_Id = Pragma_Ident then
9243                Check_Is_In_Decl_Part_Or_Package_Spec;
9244             end if;
9245
9246             Str := Expr_Value_S (Get_Pragma_Arg (Arg1));
9247
9248             declare
9249                CS : Node_Id;
9250                GP : Node_Id;
9251
9252             begin
9253                GP := Parent (Parent (N));
9254
9255                if Nkind_In (GP, N_Package_Declaration,
9256                                 N_Generic_Package_Declaration)
9257                then
9258                   GP := Parent (GP);
9259                end if;
9260
9261                --  If we have a compilation unit, then record the ident value,
9262                --  checking for improper duplication.
9263
9264                if Nkind (GP) = N_Compilation_Unit then
9265                   CS := Ident_String (Current_Sem_Unit);
9266
9267                   if Present (CS) then
9268
9269                      --  For Ident, we do not permit multiple instances
9270
9271                      if Prag_Id = Pragma_Ident then
9272                         Error_Pragma ("duplicate% pragma not permitted");
9273
9274                      --  For Comment, we concatenate the string, unless we want
9275                      --  to preserve the tree structure for ASIS.
9276
9277                      elsif not ASIS_Mode then
9278                         Start_String (Strval (CS));
9279                         Store_String_Char (' ');
9280                         Store_String_Chars (Strval (Str));
9281                         Set_Strval (CS, End_String);
9282                      end if;
9283
9284                   else
9285                      --  In VMS, the effect of IDENT is achieved by passing
9286                      --  --identification=name as a --for-linker switch.
9287
9288                      if OpenVMS_On_Target then
9289                         Start_String;
9290                         Store_String_Chars
9291                           ("--for-linker=--identification=");
9292                         String_To_Name_Buffer (Strval (Str));
9293                         Store_String_Chars (Name_Buffer (1 .. Name_Len));
9294
9295                         --  Only the last processed IDENT is saved. The main
9296                         --  purpose is so an IDENT associated with a main
9297                         --  procedure will be used in preference to an IDENT
9298                         --  associated with a with'd package.
9299
9300                         Replace_Linker_Option_String
9301                           (End_String, "--for-linker=--identification=");
9302                      end if;
9303
9304                      Set_Ident_String (Current_Sem_Unit, Str);
9305                   end if;
9306
9307                --  For subunits, we just ignore the Ident, since in GNAT these
9308                --  are not separate object files, and hence not separate units
9309                --  in the unit table.
9310
9311                elsif Nkind (GP) = N_Subunit then
9312                   null;
9313
9314                --  Otherwise we have a misplaced pragma Ident, but we ignore
9315                --  this if we are in an instantiation, since it comes from
9316                --  a generic, and has no relevance to the instantiation.
9317
9318                elsif Prag_Id = Pragma_Ident then
9319                   if Instantiation_Location (Loc) = No_Location then
9320                      Error_Pragma ("pragma% only allowed at outer level");
9321                   end if;
9322                end if;
9323             end;
9324          end Ident;
9325
9326          ----------------------------
9327          -- Implementation_Defined --
9328          ----------------------------
9329
9330          --  pragma Implementation_Defined (local_NAME);
9331
9332          --  Marks previously declared entity as implementation defined. For
9333          --  an overloaded entity, applies to the most recent homonym.
9334
9335          --  pragma Implementation_Defined;
9336
9337          --  The form with no arguments appears anywhere within a scope, most
9338          --  typically a package spec, and indicates that all entities that are
9339          --  defined within the package spec are Implementation_Defined.
9340
9341          when Pragma_Implementation_Defined => Implementation_Defined : declare
9342             Ent : Entity_Id;
9343
9344          begin
9345             Check_No_Identifiers;
9346
9347             --  Form with no arguments
9348
9349             if Arg_Count = 0 then
9350                Set_Is_Implementation_Defined (Current_Scope);
9351
9352             --  Form with one argument
9353
9354             else
9355                Check_Arg_Count (1);
9356                Check_Arg_Is_Local_Name (Arg1);
9357                Ent := Entity (Get_Pragma_Arg (Arg1));
9358                Set_Is_Implementation_Defined (Ent);
9359             end if;
9360          end Implementation_Defined;
9361
9362          -----------------
9363          -- Implemented --
9364          -----------------
9365
9366          --  pragma Implemented (procedure_LOCAL_NAME, implementation_kind);
9367          --  implementation_kind ::= By_Entry | By_Protected_Procedure | By_Any
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
9380               (Arg2, Name_By_Any, Name_By_Entry, Name_By_Protected_Procedure);
9381
9382             --  Extract the name of the local procedure
9383
9384             Proc_Id := Entity (Get_Pragma_Arg (Arg1));
9385
9386             --  Ada 2012 (AI05-0030): The procedure_LOCAL_NAME must denote a
9387             --  primitive procedure of a synchronized tagged type.
9388
9389             if Ekind (Proc_Id) = E_Procedure
9390               and then Is_Primitive (Proc_Id)
9391               and then Present (First_Formal (Proc_Id))
9392             then
9393                Typ := Etype (First_Formal (Proc_Id));
9394
9395                if Is_Tagged_Type (Typ)
9396                  and then
9397
9398                   --  Check for a protected, a synchronized or a task interface
9399
9400                    ((Is_Interface (Typ)
9401                        and then Is_Synchronized_Interface (Typ))
9402
9403                   --  Check for a protected type or a task type that implements
9404                   --  an interface.
9405
9406                    or else
9407                     (Is_Concurrent_Record_Type (Typ)
9408                        and then Present (Interfaces (Typ)))
9409
9410                   --  Check for a private record extension with keyword
9411                   --  "synchronized".
9412
9413                    or else
9414                     (Ekind_In (Typ, E_Record_Type_With_Private,
9415                                     E_Record_Subtype_With_Private)
9416                        and then Synchronized_Present (Parent (Typ))))
9417                then
9418                   null;
9419                else
9420                   Error_Pragma_Arg
9421                     ("controlling formal must be of synchronized " &
9422                      "tagged type", Arg1);
9423                   return;
9424                end if;
9425
9426             --  Procedures declared inside a protected type must be accepted
9427
9428             elsif Ekind (Proc_Id) = E_Procedure
9429               and then Is_Protected_Type (Scope (Proc_Id))
9430             then
9431                null;
9432
9433             --  The first argument is not a primitive procedure
9434
9435             else
9436                Error_Pragma_Arg
9437                  ("pragma % must be applied to a primitive procedure", Arg1);
9438                return;
9439             end if;
9440
9441             --  Ada 2012 (AI05-0030): Cannot apply the implementation_kind
9442             --  By_Protected_Procedure to the primitive procedure of a task
9443             --  interface.
9444
9445             if Chars (Arg2) = Name_By_Protected_Procedure
9446               and then Is_Interface (Typ)
9447               and then Is_Task_Interface (Typ)
9448             then
9449                Error_Pragma_Arg
9450                  ("implementation kind By_Protected_Procedure cannot be " &
9451                   "applied to a task interface primitive", Arg2);
9452                return;
9453             end if;
9454
9455             Record_Rep_Item (Proc_Id, N);
9456          end Implemented;
9457
9458          ----------------------
9459          -- Implicit_Packing --
9460          ----------------------
9461
9462          --  pragma Implicit_Packing;
9463
9464          when Pragma_Implicit_Packing =>
9465             GNAT_Pragma;
9466             Check_Arg_Count (0);
9467             Implicit_Packing := True;
9468
9469          ------------
9470          -- Import --
9471          ------------
9472
9473          --  pragma Import (
9474          --       [Convention    =>] convention_IDENTIFIER,
9475          --       [Entity        =>] local_NAME
9476          --    [, [External_Name =>] static_string_EXPRESSION ]
9477          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
9478
9479          when Pragma_Import =>
9480             Check_Ada_83_Warning;
9481             Check_Arg_Order
9482               ((Name_Convention,
9483                 Name_Entity,
9484                 Name_External_Name,
9485                 Name_Link_Name));
9486             Check_At_Least_N_Arguments (2);
9487             Check_At_Most_N_Arguments  (4);
9488             Process_Import_Or_Interface;
9489
9490          ----------------------
9491          -- Import_Exception --
9492          ----------------------
9493
9494          --  pragma Import_Exception (
9495          --        [Internal         =>] LOCAL_NAME
9496          --     [, [External         =>] EXTERNAL_SYMBOL]
9497          --     [, [Form     =>] Ada | VMS]
9498          --     [, [Code     =>] static_integer_EXPRESSION]);
9499
9500          when Pragma_Import_Exception => Import_Exception : declare
9501             Args  : Args_List (1 .. 4);
9502             Names : constant Name_List (1 .. 4) := (
9503                       Name_Internal,
9504                       Name_External,
9505                       Name_Form,
9506                       Name_Code);
9507
9508             Internal : Node_Id renames Args (1);
9509             External : Node_Id renames Args (2);
9510             Form     : Node_Id renames Args (3);
9511             Code     : Node_Id renames Args (4);
9512
9513          begin
9514             GNAT_Pragma;
9515             Gather_Associations (Names, Args);
9516
9517             if Present (External) and then Present (Code) then
9518                Error_Pragma
9519                  ("cannot give both External and Code options for pragma%");
9520             end if;
9521
9522             Process_Extended_Import_Export_Exception_Pragma (
9523               Arg_Internal => Internal,
9524               Arg_External => External,
9525               Arg_Form     => Form,
9526               Arg_Code     => Code);
9527
9528             if not Is_VMS_Exception (Entity (Internal)) then
9529                Set_Imported (Entity (Internal));
9530             end if;
9531          end Import_Exception;
9532
9533          ---------------------
9534          -- Import_Function --
9535          ---------------------
9536
9537          --  pragma Import_Function (
9538          --        [Internal                 =>] LOCAL_NAME,
9539          --     [, [External                 =>] EXTERNAL_SYMBOL]
9540          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9541          --     [, [Result_Type              =>] SUBTYPE_MARK]
9542          --     [, [Mechanism                =>] MECHANISM]
9543          --     [, [Result_Mechanism         =>] MECHANISM_NAME]
9544          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9545
9546          --  EXTERNAL_SYMBOL ::=
9547          --    IDENTIFIER
9548          --  | static_string_EXPRESSION
9549
9550          --  PARAMETER_TYPES ::=
9551          --    null
9552          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9553
9554          --  TYPE_DESIGNATOR ::=
9555          --    subtype_NAME
9556          --  | subtype_Name ' Access
9557
9558          --  MECHANISM ::=
9559          --    MECHANISM_NAME
9560          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9561
9562          --  MECHANISM_ASSOCIATION ::=
9563          --    [formal_parameter_NAME =>] MECHANISM_NAME
9564
9565          --  MECHANISM_NAME ::=
9566          --    Value
9567          --  | Reference
9568          --  | Descriptor [([Class =>] CLASS_NAME)]
9569
9570          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9571
9572          when Pragma_Import_Function => Import_Function : declare
9573             Args  : Args_List (1 .. 7);
9574             Names : constant Name_List (1 .. 7) := (
9575                       Name_Internal,
9576                       Name_External,
9577                       Name_Parameter_Types,
9578                       Name_Result_Type,
9579                       Name_Mechanism,
9580                       Name_Result_Mechanism,
9581                       Name_First_Optional_Parameter);
9582
9583             Internal                 : Node_Id renames Args (1);
9584             External                 : Node_Id renames Args (2);
9585             Parameter_Types          : Node_Id renames Args (3);
9586             Result_Type              : Node_Id renames Args (4);
9587             Mechanism                : Node_Id renames Args (5);
9588             Result_Mechanism         : Node_Id renames Args (6);
9589             First_Optional_Parameter : Node_Id renames Args (7);
9590
9591          begin
9592             GNAT_Pragma;
9593             Gather_Associations (Names, Args);
9594             Process_Extended_Import_Export_Subprogram_Pragma (
9595               Arg_Internal                 => Internal,
9596               Arg_External                 => External,
9597               Arg_Parameter_Types          => Parameter_Types,
9598               Arg_Result_Type              => Result_Type,
9599               Arg_Mechanism                => Mechanism,
9600               Arg_Result_Mechanism         => Result_Mechanism,
9601               Arg_First_Optional_Parameter => First_Optional_Parameter);
9602          end Import_Function;
9603
9604          -------------------
9605          -- Import_Object --
9606          -------------------
9607
9608          --  pragma Import_Object (
9609          --        [Internal =>] LOCAL_NAME
9610          --     [, [External =>] EXTERNAL_SYMBOL]
9611          --     [, [Size     =>] EXTERNAL_SYMBOL]);
9612
9613          --  EXTERNAL_SYMBOL ::=
9614          --    IDENTIFIER
9615          --  | static_string_EXPRESSION
9616
9617          when Pragma_Import_Object => Import_Object : declare
9618             Args  : Args_List (1 .. 3);
9619             Names : constant Name_List (1 .. 3) := (
9620                       Name_Internal,
9621                       Name_External,
9622                       Name_Size);
9623
9624             Internal : Node_Id renames Args (1);
9625             External : Node_Id renames Args (2);
9626             Size     : Node_Id renames Args (3);
9627
9628          begin
9629             GNAT_Pragma;
9630             Gather_Associations (Names, Args);
9631             Process_Extended_Import_Export_Object_Pragma (
9632               Arg_Internal => Internal,
9633               Arg_External => External,
9634               Arg_Size     => Size);
9635          end Import_Object;
9636
9637          ----------------------
9638          -- Import_Procedure --
9639          ----------------------
9640
9641          --  pragma Import_Procedure (
9642          --        [Internal                 =>] LOCAL_NAME
9643          --     [, [External                 =>] EXTERNAL_SYMBOL]
9644          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9645          --     [, [Mechanism                =>] MECHANISM]
9646          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9647
9648          --  EXTERNAL_SYMBOL ::=
9649          --    IDENTIFIER
9650          --  | static_string_EXPRESSION
9651
9652          --  PARAMETER_TYPES ::=
9653          --    null
9654          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9655
9656          --  TYPE_DESIGNATOR ::=
9657          --    subtype_NAME
9658          --  | subtype_Name ' Access
9659
9660          --  MECHANISM ::=
9661          --    MECHANISM_NAME
9662          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9663
9664          --  MECHANISM_ASSOCIATION ::=
9665          --    [formal_parameter_NAME =>] MECHANISM_NAME
9666
9667          --  MECHANISM_NAME ::=
9668          --    Value
9669          --  | Reference
9670          --  | Descriptor [([Class =>] CLASS_NAME)]
9671
9672          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9673
9674          when Pragma_Import_Procedure => Import_Procedure : declare
9675             Args  : Args_List (1 .. 5);
9676             Names : constant Name_List (1 .. 5) := (
9677                       Name_Internal,
9678                       Name_External,
9679                       Name_Parameter_Types,
9680                       Name_Mechanism,
9681                       Name_First_Optional_Parameter);
9682
9683             Internal                 : Node_Id renames Args (1);
9684             External                 : Node_Id renames Args (2);
9685             Parameter_Types          : Node_Id renames Args (3);
9686             Mechanism                : Node_Id renames Args (4);
9687             First_Optional_Parameter : Node_Id renames Args (5);
9688
9689          begin
9690             GNAT_Pragma;
9691             Gather_Associations (Names, Args);
9692             Process_Extended_Import_Export_Subprogram_Pragma (
9693               Arg_Internal                 => Internal,
9694               Arg_External                 => External,
9695               Arg_Parameter_Types          => Parameter_Types,
9696               Arg_Mechanism                => Mechanism,
9697               Arg_First_Optional_Parameter => First_Optional_Parameter);
9698          end Import_Procedure;
9699
9700          -----------------------------
9701          -- Import_Valued_Procedure --
9702          -----------------------------
9703
9704          --  pragma Import_Valued_Procedure (
9705          --        [Internal                 =>] LOCAL_NAME
9706          --     [, [External                 =>] EXTERNAL_SYMBOL]
9707          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9708          --     [, [Mechanism                =>] MECHANISM]
9709          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9710
9711          --  EXTERNAL_SYMBOL ::=
9712          --    IDENTIFIER
9713          --  | static_string_EXPRESSION
9714
9715          --  PARAMETER_TYPES ::=
9716          --    null
9717          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9718
9719          --  TYPE_DESIGNATOR ::=
9720          --    subtype_NAME
9721          --  | subtype_Name ' Access
9722
9723          --  MECHANISM ::=
9724          --    MECHANISM_NAME
9725          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9726
9727          --  MECHANISM_ASSOCIATION ::=
9728          --    [formal_parameter_NAME =>] MECHANISM_NAME
9729
9730          --  MECHANISM_NAME ::=
9731          --    Value
9732          --  | Reference
9733          --  | Descriptor [([Class =>] CLASS_NAME)]
9734
9735          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9736
9737          when Pragma_Import_Valued_Procedure =>
9738          Import_Valued_Procedure : declare
9739             Args  : Args_List (1 .. 5);
9740             Names : constant Name_List (1 .. 5) := (
9741                       Name_Internal,
9742                       Name_External,
9743                       Name_Parameter_Types,
9744                       Name_Mechanism,
9745                       Name_First_Optional_Parameter);
9746
9747             Internal                 : Node_Id renames Args (1);
9748             External                 : Node_Id renames Args (2);
9749             Parameter_Types          : Node_Id renames Args (3);
9750             Mechanism                : Node_Id renames Args (4);
9751             First_Optional_Parameter : Node_Id renames Args (5);
9752
9753          begin
9754             GNAT_Pragma;
9755             Gather_Associations (Names, Args);
9756             Process_Extended_Import_Export_Subprogram_Pragma (
9757               Arg_Internal                 => Internal,
9758               Arg_External                 => External,
9759               Arg_Parameter_Types          => Parameter_Types,
9760               Arg_Mechanism                => Mechanism,
9761               Arg_First_Optional_Parameter => First_Optional_Parameter);
9762          end Import_Valued_Procedure;
9763
9764          -----------------
9765          -- Independent --
9766          -----------------
9767
9768          --  pragma Independent (LOCAL_NAME);
9769
9770          when Pragma_Independent => Independent : declare
9771             E_Id : Node_Id;
9772             E    : Entity_Id;
9773             D    : Node_Id;
9774             K    : Node_Kind;
9775
9776          begin
9777             Check_Ada_83_Warning;
9778             Ada_2012_Pragma;
9779             Check_No_Identifiers;
9780             Check_Arg_Count (1);
9781             Check_Arg_Is_Local_Name (Arg1);
9782             E_Id := Get_Pragma_Arg (Arg1);
9783
9784             if Etype (E_Id) = Any_Type then
9785                return;
9786             end if;
9787
9788             E := Entity (E_Id);
9789             D := Declaration_Node (E);
9790             K := Nkind (D);
9791
9792             --  Check duplicate before we chain ourselves!
9793
9794             Check_Duplicate_Pragma (E);
9795
9796             --  Check appropriate entity
9797
9798             if Is_Type (E) then
9799                if Rep_Item_Too_Early (E, N)
9800                     or else
9801                   Rep_Item_Too_Late (E, N)
9802                then
9803                   return;
9804                else
9805                   Check_First_Subtype (Arg1);
9806                end if;
9807
9808             elsif K = N_Object_Declaration
9809               or else (K = N_Component_Declaration
9810                        and then Original_Record_Component (E) = E)
9811             then
9812                if Rep_Item_Too_Late (E, N) then
9813                   return;
9814                end if;
9815
9816             else
9817                Error_Pragma_Arg
9818                  ("inappropriate entity for pragma%", Arg1);
9819             end if;
9820
9821             Independence_Checks.Append ((N, E));
9822          end Independent;
9823
9824          ----------------------------
9825          -- Independent_Components --
9826          ----------------------------
9827
9828          --  pragma Atomic_Components (array_LOCAL_NAME);
9829
9830          --  This processing is shared by Volatile_Components
9831
9832          when Pragma_Independent_Components => Independent_Components : declare
9833             E_Id : Node_Id;
9834             E    : Entity_Id;
9835             D    : Node_Id;
9836             K    : Node_Kind;
9837
9838          begin
9839             Check_Ada_83_Warning;
9840             Ada_2012_Pragma;
9841             Check_No_Identifiers;
9842             Check_Arg_Count (1);
9843             Check_Arg_Is_Local_Name (Arg1);
9844             E_Id := Get_Pragma_Arg (Arg1);
9845
9846             if Etype (E_Id) = Any_Type then
9847                return;
9848             end if;
9849
9850             E := Entity (E_Id);
9851
9852             --  Check duplicate before we chain ourselves!
9853
9854             Check_Duplicate_Pragma (E);
9855
9856             --  Check appropriate entity
9857
9858             if Rep_Item_Too_Early (E, N)
9859                  or else
9860                Rep_Item_Too_Late (E, N)
9861             then
9862                return;
9863             end if;
9864
9865             D := Declaration_Node (E);
9866             K := Nkind (D);
9867
9868             if (K = N_Full_Type_Declaration
9869                  and then (Is_Array_Type (E) or else Is_Record_Type (E)))
9870               or else
9871                 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
9872                    and then Nkind (D) = N_Object_Declaration
9873                    and then Nkind (Object_Definition (D)) =
9874                                        N_Constrained_Array_Definition)
9875             then
9876                Independence_Checks.Append ((N, E));
9877
9878             else
9879                Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
9880             end if;
9881          end Independent_Components;
9882
9883          ------------------------
9884          -- Initialize_Scalars --
9885          ------------------------
9886
9887          --  pragma Initialize_Scalars;
9888
9889          when Pragma_Initialize_Scalars =>
9890             GNAT_Pragma;
9891             Check_Arg_Count (0);
9892             Check_Valid_Configuration_Pragma;
9893             Check_Restriction (No_Initialize_Scalars, N);
9894
9895             --  Initialize_Scalars creates false positives in CodePeer, and
9896             --  incorrect negative results in Alfa mode, so ignore this pragma
9897             --  in these modes.
9898
9899             if not Restriction_Active (No_Initialize_Scalars)
9900               and then not (CodePeer_Mode or Alfa_Mode)
9901             then
9902                Init_Or_Norm_Scalars := True;
9903                Initialize_Scalars := True;
9904             end if;
9905
9906          ------------
9907          -- Inline --
9908          ------------
9909
9910          --  pragma Inline ( NAME {, NAME} );
9911
9912          when Pragma_Inline =>
9913
9914             --  Pragma is active if inlining option is active
9915
9916             Process_Inline (Inline_Active);
9917
9918          -------------------
9919          -- Inline_Always --
9920          -------------------
9921
9922          --  pragma Inline_Always ( NAME {, NAME} );
9923
9924          when Pragma_Inline_Always =>
9925             GNAT_Pragma;
9926
9927             --  Pragma always active unless in CodePeer or Alfa mode, since
9928             --  this causes walk order issues.
9929
9930             if not (CodePeer_Mode or Alfa_Mode) then
9931                Process_Inline (True);
9932             end if;
9933
9934          --------------------
9935          -- Inline_Generic --
9936          --------------------
9937
9938          --  pragma Inline_Generic (NAME {, NAME});
9939
9940          when Pragma_Inline_Generic =>
9941             GNAT_Pragma;
9942             Process_Generic_List;
9943
9944          ----------------------
9945          -- Inspection_Point --
9946          ----------------------
9947
9948          --  pragma Inspection_Point [(object_NAME {, object_NAME})];
9949
9950          when Pragma_Inspection_Point => Inspection_Point : declare
9951             Arg : Node_Id;
9952             Exp : Node_Id;
9953
9954          begin
9955             if Arg_Count > 0 then
9956                Arg := Arg1;
9957                loop
9958                   Exp := Get_Pragma_Arg (Arg);
9959                   Analyze (Exp);
9960
9961                   if not Is_Entity_Name (Exp)
9962                     or else not Is_Object (Entity (Exp))
9963                   then
9964                      Error_Pragma_Arg ("object name required", Arg);
9965                   end if;
9966
9967                   Next (Arg);
9968                   exit when No (Arg);
9969                end loop;
9970             end if;
9971          end Inspection_Point;
9972
9973          ---------------
9974          -- Interface --
9975          ---------------
9976
9977          --  pragma Interface (
9978          --    [   Convention    =>] convention_IDENTIFIER,
9979          --    [   Entity        =>] local_NAME
9980          --    [, [External_Name =>] static_string_EXPRESSION ]
9981          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
9982
9983          when Pragma_Interface =>
9984             GNAT_Pragma;
9985             Check_Arg_Order
9986               ((Name_Convention,
9987                 Name_Entity,
9988                 Name_External_Name,
9989                 Name_Link_Name));
9990             Check_At_Least_N_Arguments (2);
9991             Check_At_Most_N_Arguments  (4);
9992             Process_Import_Or_Interface;
9993
9994             --  In Ada 2005, the permission to use Interface (a reserved word)
9995             --  as a pragma name is considered an obsolescent feature.
9996
9997             if Ada_Version >= Ada_2005 then
9998                Check_Restriction
9999                  (No_Obsolescent_Features, Pragma_Identifier (N));
10000             end if;
10001
10002          --------------------
10003          -- Interface_Name --
10004          --------------------
10005
10006          --  pragma Interface_Name (
10007          --    [  Entity        =>] local_NAME
10008          --    [,[External_Name =>] static_string_EXPRESSION ]
10009          --    [,[Link_Name     =>] static_string_EXPRESSION ]);
10010
10011          when Pragma_Interface_Name => Interface_Name : declare
10012             Id     : Node_Id;
10013             Def_Id : Entity_Id;
10014             Hom_Id : Entity_Id;
10015             Found  : Boolean;
10016
10017          begin
10018             GNAT_Pragma;
10019             Check_Arg_Order
10020               ((Name_Entity, Name_External_Name, Name_Link_Name));
10021             Check_At_Least_N_Arguments (2);
10022             Check_At_Most_N_Arguments  (3);
10023             Id := Get_Pragma_Arg (Arg1);
10024             Analyze (Id);
10025
10026             if not Is_Entity_Name (Id) then
10027                Error_Pragma_Arg
10028                  ("first argument for pragma% must be entity name", Arg1);
10029             elsif Etype (Id) = Any_Type then
10030                return;
10031             else
10032                Def_Id := Entity (Id);
10033             end if;
10034
10035             --  Special DEC-compatible processing for the object case, forces
10036             --  object to be imported.
10037
10038             if Ekind (Def_Id) = E_Variable then
10039                Kill_Size_Check_Code (Def_Id);
10040                Note_Possible_Modification (Id, Sure => False);
10041
10042                --  Initialization is not allowed for imported variable
10043
10044                if Present (Expression (Parent (Def_Id)))
10045                  and then Comes_From_Source (Expression (Parent (Def_Id)))
10046                then
10047                   Error_Msg_Sloc := Sloc (Def_Id);
10048                   Error_Pragma_Arg
10049                     ("no initialization allowed for declaration of& #",
10050                      Arg2);
10051
10052                else
10053                   --  For compatibility, support VADS usage of providing both
10054                   --  pragmas Interface and Interface_Name to obtain the effect
10055                   --  of a single Import pragma.
10056
10057                   if Is_Imported (Def_Id)
10058                     and then Present (First_Rep_Item (Def_Id))
10059                     and then Nkind (First_Rep_Item (Def_Id)) = N_Pragma
10060                     and then
10061                       Pragma_Name (First_Rep_Item (Def_Id)) = Name_Interface
10062                   then
10063                      null;
10064                   else
10065                      Set_Imported (Def_Id);
10066                   end if;
10067
10068                   Set_Is_Public (Def_Id);
10069                   Process_Interface_Name (Def_Id, Arg2, Arg3);
10070                end if;
10071
10072             --  Otherwise must be subprogram
10073
10074             elsif not Is_Subprogram (Def_Id) then
10075                Error_Pragma_Arg
10076                  ("argument of pragma% is not subprogram", Arg1);
10077
10078             else
10079                Check_At_Most_N_Arguments (3);
10080                Hom_Id := Def_Id;
10081                Found := False;
10082
10083                --  Loop through homonyms
10084
10085                loop
10086                   Def_Id := Get_Base_Subprogram (Hom_Id);
10087
10088                   if Is_Imported (Def_Id) then
10089                      Process_Interface_Name (Def_Id, Arg2, Arg3);
10090                      Found := True;
10091                   end if;
10092
10093                   exit when From_Aspect_Specification (N);
10094                   Hom_Id := Homonym (Hom_Id);
10095
10096                   exit when No (Hom_Id)
10097                     or else Scope (Hom_Id) /= Current_Scope;
10098                end loop;
10099
10100                if not Found then
10101                   Error_Pragma_Arg
10102                     ("argument of pragma% is not imported subprogram",
10103                      Arg1);
10104                end if;
10105             end if;
10106          end Interface_Name;
10107
10108          -----------------------
10109          -- Interrupt_Handler --
10110          -----------------------
10111
10112          --  pragma Interrupt_Handler (handler_NAME);
10113
10114          when Pragma_Interrupt_Handler =>
10115             Check_Ada_83_Warning;
10116             Check_Arg_Count (1);
10117             Check_No_Identifiers;
10118
10119             if No_Run_Time_Mode then
10120                Error_Msg_CRT ("Interrupt_Handler pragma", N);
10121             else
10122                Check_Interrupt_Or_Attach_Handler;
10123                Process_Interrupt_Or_Attach_Handler;
10124             end if;
10125
10126          ------------------------
10127          -- Interrupt_Priority --
10128          ------------------------
10129
10130          --  pragma Interrupt_Priority [(EXPRESSION)];
10131
10132          when Pragma_Interrupt_Priority => Interrupt_Priority : declare
10133             P   : constant Node_Id := Parent (N);
10134             Arg : Node_Id;
10135
10136          begin
10137             Check_Ada_83_Warning;
10138
10139             if Arg_Count /= 0 then
10140                Arg := Get_Pragma_Arg (Arg1);
10141                Check_Arg_Count (1);
10142                Check_No_Identifiers;
10143
10144                --  The expression must be analyzed in the special manner
10145                --  described in "Handling of Default and Per-Object
10146                --  Expressions" in sem.ads.
10147
10148                Preanalyze_Spec_Expression (Arg, RTE (RE_Interrupt_Priority));
10149             end if;
10150
10151             if not Nkind_In (P, N_Task_Definition, N_Protected_Definition) then
10152                Pragma_Misplaced;
10153                return;
10154
10155             elsif Has_Pragma_Priority (P) then
10156                Error_Pragma ("duplicate pragma% not allowed");
10157
10158             else
10159                Set_Has_Pragma_Priority (P, True);
10160                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
10161             end if;
10162          end Interrupt_Priority;
10163
10164          ---------------------
10165          -- Interrupt_State --
10166          ---------------------
10167
10168          --  pragma Interrupt_State (
10169          --    [Name  =>] INTERRUPT_ID,
10170          --    [State =>] INTERRUPT_STATE);
10171
10172          --  INTERRUPT_ID => IDENTIFIER | static_integer_EXPRESSION
10173          --  INTERRUPT_STATE => System | Runtime | User
10174
10175          --  Note: if the interrupt id is given as an identifier, then it must
10176          --  be one of the identifiers in Ada.Interrupts.Names. Otherwise it is
10177          --  given as a static integer expression which must be in the range of
10178          --  Ada.Interrupts.Interrupt_ID.
10179
10180          when Pragma_Interrupt_State => Interrupt_State : declare
10181
10182             Int_Id : constant Entity_Id := RTE (RE_Interrupt_ID);
10183             --  This is the entity Ada.Interrupts.Interrupt_ID;
10184
10185             State_Type : Character;
10186             --  Set to 's'/'r'/'u' for System/Runtime/User
10187
10188             IST_Num : Pos;
10189             --  Index to entry in Interrupt_States table
10190
10191             Int_Val : Uint;
10192             --  Value of interrupt
10193
10194             Arg1X : constant Node_Id := Get_Pragma_Arg (Arg1);
10195             --  The first argument to the pragma
10196
10197             Int_Ent : Entity_Id;
10198             --  Interrupt entity in Ada.Interrupts.Names
10199
10200          begin
10201             GNAT_Pragma;
10202             Check_Arg_Order ((Name_Name, Name_State));
10203             Check_Arg_Count (2);
10204
10205             Check_Optional_Identifier (Arg1, Name_Name);
10206             Check_Optional_Identifier (Arg2, Name_State);
10207             Check_Arg_Is_Identifier (Arg2);
10208
10209             --  First argument is identifier
10210
10211             if Nkind (Arg1X) = N_Identifier then
10212
10213                --  Search list of names in Ada.Interrupts.Names
10214
10215                Int_Ent := First_Entity (RTE (RE_Names));
10216                loop
10217                   if No (Int_Ent) then
10218                      Error_Pragma_Arg ("invalid interrupt name", Arg1);
10219
10220                   elsif Chars (Int_Ent) = Chars (Arg1X) then
10221                      Int_Val := Expr_Value (Constant_Value (Int_Ent));
10222                      exit;
10223                   end if;
10224
10225                   Next_Entity (Int_Ent);
10226                end loop;
10227
10228             --  First argument is not an identifier, so it must be a static
10229             --  expression of type Ada.Interrupts.Interrupt_ID.
10230
10231             else
10232                Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
10233                Int_Val := Expr_Value (Arg1X);
10234
10235                if Int_Val < Expr_Value (Type_Low_Bound (Int_Id))
10236                     or else
10237                   Int_Val > Expr_Value (Type_High_Bound (Int_Id))
10238                then
10239                   Error_Pragma_Arg
10240                     ("value not in range of type " &
10241                      """Ada.Interrupts.Interrupt_'I'D""", Arg1);
10242                end if;
10243             end if;
10244
10245             --  Check OK state
10246
10247             case Chars (Get_Pragma_Arg (Arg2)) is
10248                when Name_Runtime => State_Type := 'r';
10249                when Name_System  => State_Type := 's';
10250                when Name_User    => State_Type := 'u';
10251
10252                when others =>
10253                   Error_Pragma_Arg ("invalid interrupt state", Arg2);
10254             end case;
10255
10256             --  Check if entry is already stored
10257
10258             IST_Num := Interrupt_States.First;
10259             loop
10260                --  If entry not found, add it
10261
10262                if IST_Num > Interrupt_States.Last then
10263                   Interrupt_States.Append
10264                     ((Interrupt_Number => UI_To_Int (Int_Val),
10265                       Interrupt_State  => State_Type,
10266                       Pragma_Loc       => Loc));
10267                   exit;
10268
10269                --  Case of entry for the same entry
10270
10271                elsif Int_Val = Interrupt_States.Table (IST_Num).
10272                                                            Interrupt_Number
10273                then
10274                   --  If state matches, done, no need to make redundant entry
10275
10276                   exit when
10277                     State_Type = Interrupt_States.Table (IST_Num).
10278                                                            Interrupt_State;
10279
10280                   --  Otherwise if state does not match, error
10281
10282                   Error_Msg_Sloc :=
10283                     Interrupt_States.Table (IST_Num).Pragma_Loc;
10284                   Error_Pragma_Arg
10285                     ("state conflicts with that given #", Arg2);
10286                   exit;
10287                end if;
10288
10289                IST_Num := IST_Num + 1;
10290             end loop;
10291          end Interrupt_State;
10292
10293          ---------------
10294          -- Invariant --
10295          ---------------
10296
10297          --  pragma Invariant
10298          --    ([Entity =>]    type_LOCAL_NAME,
10299          --     [Check  =>]    EXPRESSION
10300          --     [,[Message =>] String_Expression]);
10301
10302          when Pragma_Invariant => Invariant : declare
10303             Type_Id : Node_Id;
10304             Typ     : Entity_Id;
10305
10306             Discard : Boolean;
10307             pragma Unreferenced (Discard);
10308
10309          begin
10310             GNAT_Pragma;
10311             Check_At_Least_N_Arguments (2);
10312             Check_At_Most_N_Arguments (3);
10313             Check_Optional_Identifier (Arg1, Name_Entity);
10314             Check_Optional_Identifier (Arg2, Name_Check);
10315
10316             if Arg_Count = 3 then
10317                Check_Optional_Identifier (Arg3, Name_Message);
10318                Check_Arg_Is_Static_Expression (Arg3, Standard_String);
10319             end if;
10320
10321             Check_Arg_Is_Local_Name (Arg1);
10322
10323             Type_Id := Get_Pragma_Arg (Arg1);
10324             Find_Type (Type_Id);
10325             Typ := Entity (Type_Id);
10326
10327             if Typ = Any_Type then
10328                return;
10329
10330             --  An invariant must apply to a private type, or appear in the
10331             --  private part of a package spec and apply to a completion.
10332
10333             elsif Ekind_In (Typ, E_Private_Type,
10334                                  E_Record_Type_With_Private,
10335                                  E_Limited_Private_Type)
10336             then
10337                null;
10338
10339             elsif In_Private_Part (Current_Scope)
10340               and then Has_Private_Declaration (Typ)
10341             then
10342                null;
10343
10344             elsif In_Private_Part (Current_Scope) then
10345                Error_Pragma_Arg
10346                  ("pragma% only allowed for private type " &
10347                   "declared in visible part", Arg1);
10348
10349             else
10350                Error_Pragma_Arg
10351                  ("pragma% only allowed for private type", Arg1);
10352             end if;
10353
10354             --  Note that the type has at least one invariant, and also that
10355             --  it has inheritable invariants if we have Invariant'Class.
10356
10357             Set_Has_Invariants (Typ);
10358
10359             if Class_Present (N) then
10360                Set_Has_Inheritable_Invariants (Typ);
10361             end if;
10362
10363             --  The remaining processing is simply to link the pragma on to
10364             --  the rep item chain, for processing when the type is frozen.
10365             --  This is accomplished by a call to Rep_Item_Too_Late.
10366
10367             Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
10368          end Invariant;
10369
10370          ----------------------
10371          -- Java_Constructor --
10372          ----------------------
10373
10374          --  pragma Java_Constructor ([Entity =>] LOCAL_NAME);
10375
10376          --  Also handles pragma CIL_Constructor
10377
10378          when Pragma_CIL_Constructor | Pragma_Java_Constructor =>
10379          Java_Constructor : declare
10380             Convention  : Convention_Id;
10381             Def_Id      : Entity_Id;
10382             Hom_Id      : Entity_Id;
10383             Id          : Entity_Id;
10384             This_Formal : Entity_Id;
10385
10386          begin
10387             GNAT_Pragma;
10388             Check_Arg_Count (1);
10389             Check_Optional_Identifier (Arg1, Name_Entity);
10390             Check_Arg_Is_Local_Name (Arg1);
10391
10392             Id := Get_Pragma_Arg (Arg1);
10393             Find_Program_Unit_Name (Id);
10394
10395             --  If we did not find the name, we are done
10396
10397             if Etype (Id) = Any_Type then
10398                return;
10399             end if;
10400
10401             --  Check wrong use of pragma in wrong VM target
10402
10403             if VM_Target = No_VM then
10404                return;
10405
10406             elsif VM_Target = CLI_Target
10407               and then Prag_Id = Pragma_Java_Constructor
10408             then
10409                Error_Pragma ("must use pragma 'C'I'L_'Constructor");
10410
10411             elsif VM_Target = JVM_Target
10412               and then Prag_Id = Pragma_CIL_Constructor
10413             then
10414                Error_Pragma ("must use pragma 'Java_'Constructor");
10415             end if;
10416
10417             case Prag_Id is
10418                when Pragma_CIL_Constructor  => Convention := Convention_CIL;
10419                when Pragma_Java_Constructor => Convention := Convention_Java;
10420                when others                  => null;
10421             end case;
10422
10423             Hom_Id := Entity (Id);
10424
10425             --  Loop through homonyms
10426
10427             loop
10428                Def_Id := Get_Base_Subprogram (Hom_Id);
10429
10430                --  The constructor is required to be a function
10431
10432                if Ekind (Def_Id) /= E_Function then
10433                   if VM_Target = JVM_Target then
10434                      Error_Pragma_Arg
10435                        ("pragma% requires function returning a " &
10436                         "'Java access type", Def_Id);
10437                   else
10438                      Error_Pragma_Arg
10439                        ("pragma% requires function returning a " &
10440                         "'C'I'L access type", Def_Id);
10441                   end if;
10442                end if;
10443
10444                --  Check arguments: For tagged type the first formal must be
10445                --  named "this" and its type must be a named access type
10446                --  designating a class-wide tagged type that has convention
10447                --  CIL/Java. The first formal must also have a null default
10448                --  value. For example:
10449
10450                --      type Typ is tagged ...
10451                --      type Ref is access all Typ;
10452                --      pragma Convention (CIL, Typ);
10453
10454                --      function New_Typ (This : Ref) return Ref;
10455                --      function New_Typ (This : Ref; I : Integer) return Ref;
10456                --      pragma Cil_Constructor (New_Typ);
10457
10458                --  Reason: The first formal must NOT be a primitive of the
10459                --  tagged type.
10460
10461                --  This rule also applies to constructors of delegates used
10462                --  to interface with standard target libraries. For example:
10463
10464                --      type Delegate is access procedure ...
10465                --      pragma Import (CIL, Delegate, ...);
10466
10467                --      function new_Delegate
10468                --        (This : Delegate := null; ... ) return Delegate;
10469
10470                --  For value-types this rule does not apply.
10471
10472                if not Is_Value_Type (Etype (Def_Id)) then
10473                   if No (First_Formal (Def_Id)) then
10474                      Error_Msg_Name_1 := Pname;
10475                      Error_Msg_N ("% function must have parameters", Def_Id);
10476                      return;
10477                   end if;
10478
10479                   --  In the JRE library we have several occurrences in which
10480                   --  the "this" parameter is not the first formal.
10481
10482                   This_Formal := First_Formal (Def_Id);
10483
10484                   --  In the JRE library we have several occurrences in which
10485                   --  the "this" parameter is not the first formal. Search for
10486                   --  it.
10487
10488                   if VM_Target = JVM_Target then
10489                      while Present (This_Formal)
10490                        and then Get_Name_String (Chars (This_Formal)) /= "this"
10491                      loop
10492                         Next_Formal (This_Formal);
10493                      end loop;
10494
10495                      if No (This_Formal) then
10496                         This_Formal := First_Formal (Def_Id);
10497                      end if;
10498                   end if;
10499
10500                   --  Warning: The first parameter should be named "this".
10501                   --  We temporarily allow it because we have the following
10502                   --  case in the Java runtime (file s-osinte.ads) ???
10503
10504                   --    function new_Thread
10505                   --      (Self_Id : System.Address) return Thread_Id;
10506                   --    pragma Java_Constructor (new_Thread);
10507
10508                   if VM_Target = JVM_Target
10509                     and then Get_Name_String (Chars (First_Formal (Def_Id)))
10510                                = "self_id"
10511                     and then Etype (First_Formal (Def_Id)) = RTE (RE_Address)
10512                   then
10513                      null;
10514
10515                   elsif Get_Name_String (Chars (This_Formal)) /= "this" then
10516                      Error_Msg_Name_1 := Pname;
10517                      Error_Msg_N
10518                        ("first formal of % function must be named `this`",
10519                         Parent (This_Formal));
10520
10521                   elsif not Is_Access_Type (Etype (This_Formal)) then
10522                      Error_Msg_Name_1 := Pname;
10523                      Error_Msg_N
10524                        ("first formal of % function must be an access type",
10525                         Parameter_Type (Parent (This_Formal)));
10526
10527                   --  For delegates the type of the first formal must be a
10528                   --  named access-to-subprogram type (see previous example)
10529
10530                   elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type
10531                     and then Ekind (Etype (This_Formal))
10532                                /= E_Access_Subprogram_Type
10533                   then
10534                      Error_Msg_Name_1 := Pname;
10535                      Error_Msg_N
10536                        ("first formal of % function must be a named access" &
10537                         " to subprogram type",
10538                         Parameter_Type (Parent (This_Formal)));
10539
10540                   --  Warning: We should reject anonymous access types because
10541                   --  the constructor must not be handled as a primitive of the
10542                   --  tagged type. We temporarily allow it because this profile
10543                   --  is currently generated by cil2ada???
10544
10545                   elsif Ekind (Etype (Def_Id)) /= E_Access_Subprogram_Type
10546                     and then not Ekind_In (Etype (This_Formal),
10547                                              E_Access_Type,
10548                                              E_General_Access_Type,
10549                                              E_Anonymous_Access_Type)
10550                   then
10551                      Error_Msg_Name_1 := Pname;
10552                      Error_Msg_N
10553                        ("first formal of % function must be a named access" &
10554                         " type",
10555                         Parameter_Type (Parent (This_Formal)));
10556
10557                   elsif Atree.Convention
10558                          (Designated_Type (Etype (This_Formal))) /= Convention
10559                   then
10560                      Error_Msg_Name_1 := Pname;
10561
10562                      if Convention = Convention_Java then
10563                         Error_Msg_N
10564                           ("pragma% requires convention 'Cil in designated" &
10565                            " type",
10566                            Parameter_Type (Parent (This_Formal)));
10567                      else
10568                         Error_Msg_N
10569                           ("pragma% requires convention 'Java in designated" &
10570                            " type",
10571                            Parameter_Type (Parent (This_Formal)));
10572                      end if;
10573
10574                   elsif No (Expression (Parent (This_Formal)))
10575                     or else Nkind (Expression (Parent (This_Formal))) /= N_Null
10576                   then
10577                      Error_Msg_Name_1 := Pname;
10578                      Error_Msg_N
10579                        ("pragma% requires first formal with default `null`",
10580                         Parameter_Type (Parent (This_Formal)));
10581                   end if;
10582                end if;
10583
10584                --  Check result type: the constructor must be a function
10585                --  returning:
10586                --   * a value type (only allowed in the CIL compiler)
10587                --   * an access-to-subprogram type with convention Java/CIL
10588                --   * an access-type designating a type that has convention
10589                --     Java/CIL.
10590
10591                if Is_Value_Type (Etype (Def_Id)) then
10592                   null;
10593
10594                --  Access-to-subprogram type with convention Java/CIL
10595
10596                elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type then
10597                   if Atree.Convention (Etype (Def_Id)) /= Convention then
10598                      if Convention = Convention_Java then
10599                         Error_Pragma_Arg
10600                           ("pragma% requires function returning a " &
10601                            "'Java access type", Arg1);
10602                      else
10603                         pragma Assert (Convention = Convention_CIL);
10604                         Error_Pragma_Arg
10605                           ("pragma% requires function returning a " &
10606                            "'C'I'L access type", Arg1);
10607                      end if;
10608                   end if;
10609
10610                elsif Ekind (Etype (Def_Id)) in Access_Kind then
10611                   if not Ekind_In (Etype (Def_Id), E_Access_Type,
10612                                                    E_General_Access_Type)
10613                     or else
10614                       Atree.Convention
10615                         (Designated_Type (Etype (Def_Id))) /= Convention
10616                   then
10617                      Error_Msg_Name_1 := Pname;
10618
10619                      if Convention = Convention_Java then
10620                         Error_Pragma_Arg
10621                           ("pragma% requires function returning a named" &
10622                            "'Java access type", Arg1);
10623                      else
10624                         Error_Pragma_Arg
10625                           ("pragma% requires function returning a named" &
10626                            "'C'I'L access type", Arg1);
10627                      end if;
10628                   end if;
10629                end if;
10630
10631                Set_Is_Constructor (Def_Id);
10632                Set_Convention     (Def_Id, Convention);
10633                Set_Is_Imported    (Def_Id);
10634
10635                exit when From_Aspect_Specification (N);
10636                Hom_Id := Homonym (Hom_Id);
10637
10638                exit when No (Hom_Id) or else Scope (Hom_Id) /= Current_Scope;
10639             end loop;
10640          end Java_Constructor;
10641
10642          ----------------------
10643          -- Java_Interface --
10644          ----------------------
10645
10646          --  pragma Java_Interface ([Entity =>] LOCAL_NAME);
10647
10648          when Pragma_Java_Interface => Java_Interface : declare
10649             Arg : Node_Id;
10650             Typ : Entity_Id;
10651
10652          begin
10653             GNAT_Pragma;
10654             Check_Arg_Count (1);
10655             Check_Optional_Identifier (Arg1, Name_Entity);
10656             Check_Arg_Is_Local_Name (Arg1);
10657
10658             Arg := Get_Pragma_Arg (Arg1);
10659             Analyze (Arg);
10660
10661             if Etype (Arg) = Any_Type then
10662                return;
10663             end if;
10664
10665             if not Is_Entity_Name (Arg)
10666               or else not Is_Type (Entity (Arg))
10667             then
10668                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
10669             end if;
10670
10671             Typ := Underlying_Type (Entity (Arg));
10672
10673             --  For now simply check some of the semantic constraints on the
10674             --  type. This currently leaves out some restrictions on interface
10675             --  types, namely that the parent type must be java.lang.Object.Typ
10676             --  and that all primitives of the type should be declared
10677             --  abstract. ???
10678
10679             if not Is_Tagged_Type (Typ) or else not Is_Abstract_Type (Typ) then
10680                Error_Pragma_Arg ("pragma% requires an abstract "
10681                  & "tagged type", Arg1);
10682
10683             elsif not Has_Discriminants (Typ)
10684               or else Ekind (Etype (First_Discriminant (Typ)))
10685                         /= E_Anonymous_Access_Type
10686               or else
10687                 not Is_Class_Wide_Type
10688                       (Designated_Type (Etype (First_Discriminant (Typ))))
10689             then
10690                Error_Pragma_Arg
10691                  ("type must have a class-wide access discriminant", Arg1);
10692             end if;
10693          end Java_Interface;
10694
10695          ----------------
10696          -- Keep_Names --
10697          ----------------
10698
10699          --  pragma Keep_Names ([On => ] local_NAME);
10700
10701          when Pragma_Keep_Names => Keep_Names : declare
10702             Arg : Node_Id;
10703
10704          begin
10705             GNAT_Pragma;
10706             Check_Arg_Count (1);
10707             Check_Optional_Identifier (Arg1, Name_On);
10708             Check_Arg_Is_Local_Name (Arg1);
10709
10710             Arg := Get_Pragma_Arg (Arg1);
10711             Analyze (Arg);
10712
10713             if Etype (Arg) = Any_Type then
10714                return;
10715             end if;
10716
10717             if not Is_Entity_Name (Arg)
10718               or else Ekind (Entity (Arg)) /= E_Enumeration_Type
10719             then
10720                Error_Pragma_Arg
10721                  ("pragma% requires a local enumeration type", Arg1);
10722             end if;
10723
10724             Set_Discard_Names (Entity (Arg), False);
10725          end Keep_Names;
10726
10727          -------------
10728          -- License --
10729          -------------
10730
10731          --  pragma License (RESTRICTED | UNRESTRICTED | GPL | MODIFIED_GPL);
10732
10733          when Pragma_License =>
10734             GNAT_Pragma;
10735             Check_Arg_Count (1);
10736             Check_No_Identifiers;
10737             Check_Valid_Configuration_Pragma;
10738             Check_Arg_Is_Identifier (Arg1);
10739
10740             declare
10741                Sind : constant Source_File_Index :=
10742                         Source_Index (Current_Sem_Unit);
10743
10744             begin
10745                case Chars (Get_Pragma_Arg (Arg1)) is
10746                   when Name_GPL =>
10747                      Set_License (Sind, GPL);
10748
10749                   when Name_Modified_GPL =>
10750                      Set_License (Sind, Modified_GPL);
10751
10752                   when Name_Restricted =>
10753                      Set_License (Sind, Restricted);
10754
10755                   when Name_Unrestricted =>
10756                      Set_License (Sind, Unrestricted);
10757
10758                   when others =>
10759                      Error_Pragma_Arg ("invalid license name", Arg1);
10760                end case;
10761             end;
10762
10763          ---------------
10764          -- Link_With --
10765          ---------------
10766
10767          --  pragma Link_With (string_EXPRESSION {, string_EXPRESSION});
10768
10769          when Pragma_Link_With => Link_With : declare
10770             Arg : Node_Id;
10771
10772          begin
10773             GNAT_Pragma;
10774
10775             if Operating_Mode = Generate_Code
10776               and then In_Extended_Main_Source_Unit (N)
10777             then
10778                Check_At_Least_N_Arguments (1);
10779                Check_No_Identifiers;
10780                Check_Is_In_Decl_Part_Or_Package_Spec;
10781                Check_Arg_Is_Static_Expression (Arg1, Standard_String);
10782                Start_String;
10783
10784                Arg := Arg1;
10785                while Present (Arg) loop
10786                   Check_Arg_Is_Static_Expression (Arg, Standard_String);
10787
10788                   --  Store argument, converting sequences of spaces to a
10789                   --  single null character (this is one of the differences
10790                   --  in processing between Link_With and Linker_Options).
10791
10792                   Arg_Store : declare
10793                      C : constant Char_Code := Get_Char_Code (' ');
10794                      S : constant String_Id :=
10795                            Strval (Expr_Value_S (Get_Pragma_Arg (Arg)));
10796                      L : constant Nat := String_Length (S);
10797                      F : Nat := 1;
10798
10799                      procedure Skip_Spaces;
10800                      --  Advance F past any spaces
10801
10802                      -----------------
10803                      -- Skip_Spaces --
10804                      -----------------
10805
10806                      procedure Skip_Spaces is
10807                      begin
10808                         while F <= L and then Get_String_Char (S, F) = C loop
10809                            F := F + 1;
10810                         end loop;
10811                      end Skip_Spaces;
10812
10813                   --  Start of processing for Arg_Store
10814
10815                   begin
10816                      Skip_Spaces; -- skip leading spaces
10817
10818                      --  Loop through characters, changing any embedded
10819                      --  sequence of spaces to a single null character (this
10820                      --  is how Link_With/Linker_Options differ)
10821
10822                      while F <= L loop
10823                         if Get_String_Char (S, F) = C then
10824                            Skip_Spaces;
10825                            exit when F > L;
10826                            Store_String_Char (ASCII.NUL);
10827
10828                         else
10829                            Store_String_Char (Get_String_Char (S, F));
10830                            F := F + 1;
10831                         end if;
10832                      end loop;
10833                   end Arg_Store;
10834
10835                   Arg := Next (Arg);
10836
10837                   if Present (Arg) then
10838                      Store_String_Char (ASCII.NUL);
10839                   end if;
10840                end loop;
10841
10842                Store_Linker_Option_String (End_String);
10843             end if;
10844          end Link_With;
10845
10846          ------------------
10847          -- Linker_Alias --
10848          ------------------
10849
10850          --  pragma Linker_Alias (
10851          --      [Entity =>]  LOCAL_NAME
10852          --      [Target =>]  static_string_EXPRESSION);
10853
10854          when Pragma_Linker_Alias =>
10855             GNAT_Pragma;
10856             Check_Arg_Order ((Name_Entity, Name_Target));
10857             Check_Arg_Count (2);
10858             Check_Optional_Identifier (Arg1, Name_Entity);
10859             Check_Optional_Identifier (Arg2, Name_Target);
10860             Check_Arg_Is_Library_Level_Local_Name (Arg1);
10861             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10862
10863             --  The only processing required is to link this item on to the
10864             --  list of rep items for the given entity. This is accomplished
10865             --  by the call to Rep_Item_Too_Late (when no error is detected
10866             --  and False is returned).
10867
10868             if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
10869                return;
10870             else
10871                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10872             end if;
10873
10874          ------------------------
10875          -- Linker_Constructor --
10876          ------------------------
10877
10878          --  pragma Linker_Constructor (procedure_LOCAL_NAME);
10879
10880          --  Code is shared with Linker_Destructor
10881
10882          -----------------------
10883          -- Linker_Destructor --
10884          -----------------------
10885
10886          --  pragma Linker_Destructor (procedure_LOCAL_NAME);
10887
10888          when Pragma_Linker_Constructor |
10889               Pragma_Linker_Destructor =>
10890          Linker_Constructor : declare
10891             Arg1_X : Node_Id;
10892             Proc   : Entity_Id;
10893
10894          begin
10895             GNAT_Pragma;
10896             Check_Arg_Count (1);
10897             Check_No_Identifiers;
10898             Check_Arg_Is_Local_Name (Arg1);
10899             Arg1_X := Get_Pragma_Arg (Arg1);
10900             Analyze (Arg1_X);
10901             Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
10902
10903             if not Is_Library_Level_Entity (Proc) then
10904                Error_Pragma_Arg
10905                 ("argument for pragma% must be library level entity", Arg1);
10906             end if;
10907
10908             --  The only processing required is to link this item on to the
10909             --  list of rep items for the given entity. This is accomplished
10910             --  by the call to Rep_Item_Too_Late (when no error is detected
10911             --  and False is returned).
10912
10913             if Rep_Item_Too_Late (Proc, N) then
10914                return;
10915             else
10916                Set_Has_Gigi_Rep_Item (Proc);
10917             end if;
10918          end Linker_Constructor;
10919
10920          --------------------
10921          -- Linker_Options --
10922          --------------------
10923
10924          --  pragma Linker_Options (string_EXPRESSION {, string_EXPRESSION});
10925
10926          when Pragma_Linker_Options => Linker_Options : declare
10927             Arg : Node_Id;
10928
10929          begin
10930             Check_Ada_83_Warning;
10931             Check_No_Identifiers;
10932             Check_Arg_Count (1);
10933             Check_Is_In_Decl_Part_Or_Package_Spec;
10934             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
10935             Start_String (Strval (Expr_Value_S (Get_Pragma_Arg (Arg1))));
10936
10937             Arg := Arg2;
10938             while Present (Arg) loop
10939                Check_Arg_Is_Static_Expression (Arg, Standard_String);
10940                Store_String_Char (ASCII.NUL);
10941                Store_String_Chars
10942                  (Strval (Expr_Value_S (Get_Pragma_Arg (Arg))));
10943                Arg := Next (Arg);
10944             end loop;
10945
10946             if Operating_Mode = Generate_Code
10947               and then In_Extended_Main_Source_Unit (N)
10948             then
10949                Store_Linker_Option_String (End_String);
10950             end if;
10951          end Linker_Options;
10952
10953          --------------------
10954          -- Linker_Section --
10955          --------------------
10956
10957          --  pragma Linker_Section (
10958          --      [Entity  =>]  LOCAL_NAME
10959          --      [Section =>]  static_string_EXPRESSION);
10960
10961          when Pragma_Linker_Section =>
10962             GNAT_Pragma;
10963             Check_Arg_Order ((Name_Entity, Name_Section));
10964             Check_Arg_Count (2);
10965             Check_Optional_Identifier (Arg1, Name_Entity);
10966             Check_Optional_Identifier (Arg2, Name_Section);
10967             Check_Arg_Is_Library_Level_Local_Name (Arg1);
10968             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10969
10970             --  This pragma applies only to objects
10971
10972             if not Is_Object (Entity (Get_Pragma_Arg (Arg1))) then
10973                Error_Pragma_Arg ("pragma% applies only to objects", Arg1);
10974             end if;
10975
10976             --  The only processing required is to link this item on to the
10977             --  list of rep items for the given entity. This is accomplished
10978             --  by the call to Rep_Item_Too_Late (when no error is detected
10979             --  and False is returned).
10980
10981             if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
10982                return;
10983             else
10984                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10985             end if;
10986
10987          ----------
10988          -- List --
10989          ----------
10990
10991          --  pragma List (On | Off)
10992
10993          --  There is nothing to do here, since we did all the processing for
10994          --  this pragma in Par.Prag (so that it works properly even in syntax
10995          --  only mode).
10996
10997          when Pragma_List =>
10998             null;
10999
11000          --------------------
11001          -- Locking_Policy --
11002          --------------------
11003
11004          --  pragma Locking_Policy (policy_IDENTIFIER);
11005
11006          when Pragma_Locking_Policy => declare
11007             subtype LP_Range is Name_Id
11008               range First_Locking_Policy_Name .. Last_Locking_Policy_Name;
11009             LP_Val : LP_Range;
11010             LP     : Character;
11011          begin
11012             Check_Ada_83_Warning;
11013             Check_Arg_Count (1);
11014             Check_No_Identifiers;
11015             Check_Arg_Is_Locking_Policy (Arg1);
11016             Check_Valid_Configuration_Pragma;
11017             LP_Val := Chars (Get_Pragma_Arg (Arg1));
11018
11019             case LP_Val is
11020                when Name_Ceiling_Locking            => LP := 'C';
11021                when Name_Inheritance_Locking        => LP := 'I';
11022                when Name_Concurrent_Readers_Locking => LP := 'R';
11023             end case;
11024
11025             if Locking_Policy /= ' '
11026               and then Locking_Policy /= LP
11027             then
11028                Error_Msg_Sloc := Locking_Policy_Sloc;
11029                Error_Pragma ("locking policy incompatible with policy#");
11030
11031             --  Set new policy, but always preserve System_Location since we
11032             --  like the error message with the run time name.
11033
11034             else
11035                Locking_Policy := LP;
11036
11037                if Locking_Policy_Sloc /= System_Location then
11038                   Locking_Policy_Sloc := Loc;
11039                end if;
11040             end if;
11041          end;
11042
11043          ----------------
11044          -- Long_Float --
11045          ----------------
11046
11047          --  pragma Long_Float (D_Float | G_Float);
11048
11049          when Pragma_Long_Float => Long_Float : declare
11050          begin
11051             GNAT_Pragma;
11052             Check_Valid_Configuration_Pragma;
11053             Check_Arg_Count (1);
11054             Check_No_Identifier (Arg1);
11055             Check_Arg_Is_One_Of (Arg1, Name_D_Float, Name_G_Float);
11056
11057             if not OpenVMS_On_Target then
11058                Error_Pragma ("?pragma% ignored (applies only to Open'V'M'S)");
11059             end if;
11060
11061             --  D_Float case
11062
11063             if Chars (Get_Pragma_Arg (Arg1)) = Name_D_Float then
11064                if Opt.Float_Format_Long = 'G' then
11065                   Error_Pragma_Arg
11066                     ("G_Float previously specified", Arg1);
11067
11068                elsif Current_Sem_Unit /= Main_Unit
11069                  and then Opt.Float_Format_Long /= 'D'
11070                then
11071                   Error_Pragma_Arg
11072                     ("main unit not compiled with pragma Long_Float (D_Float)",
11073                      "\pragma% must be used consistently for whole partition",
11074                      Arg1);
11075
11076                else
11077                   Opt.Float_Format_Long := 'D';
11078                end if;
11079
11080             --  G_Float case (this is the default, does not need overriding)
11081
11082             else
11083                if Opt.Float_Format_Long = 'D' then
11084                   Error_Pragma ("D_Float previously specified");
11085
11086                elsif Current_Sem_Unit /= Main_Unit
11087                  and then Opt.Float_Format_Long /= 'G'
11088                then
11089                   Error_Pragma_Arg
11090                     ("main unit not compiled with pragma Long_Float (G_Float)",
11091                      "\pragma% must be used consistently for whole partition",
11092                      Arg1);
11093
11094                else
11095                   Opt.Float_Format_Long := 'G';
11096                end if;
11097             end if;
11098
11099             Set_Standard_Fpt_Formats;
11100          end Long_Float;
11101
11102          -----------------------
11103          -- Machine_Attribute --
11104          -----------------------
11105
11106          --  pragma Machine_Attribute (
11107          --       [Entity         =>] LOCAL_NAME,
11108          --       [Attribute_Name =>] static_string_EXPRESSION
11109          --    [, [Info           =>] static_EXPRESSION] );
11110
11111          when Pragma_Machine_Attribute => Machine_Attribute : declare
11112             Def_Id : Entity_Id;
11113
11114          begin
11115             GNAT_Pragma;
11116             Check_Arg_Order ((Name_Entity, Name_Attribute_Name, Name_Info));
11117
11118             if Arg_Count = 3 then
11119                Check_Optional_Identifier (Arg3, Name_Info);
11120                Check_Arg_Is_Static_Expression (Arg3);
11121             else
11122                Check_Arg_Count (2);
11123             end if;
11124
11125             Check_Optional_Identifier (Arg1, Name_Entity);
11126             Check_Optional_Identifier (Arg2, Name_Attribute_Name);
11127             Check_Arg_Is_Local_Name (Arg1);
11128             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
11129             Def_Id := Entity (Get_Pragma_Arg (Arg1));
11130
11131             if Is_Access_Type (Def_Id) then
11132                Def_Id := Designated_Type (Def_Id);
11133             end if;
11134
11135             if Rep_Item_Too_Early (Def_Id, N) then
11136                return;
11137             end if;
11138
11139             Def_Id := Underlying_Type (Def_Id);
11140
11141             --  The only processing required is to link this item on to the
11142             --  list of rep items for the given entity. This is accomplished
11143             --  by the call to Rep_Item_Too_Late (when no error is detected
11144             --  and False is returned).
11145
11146             if Rep_Item_Too_Late (Def_Id, N) then
11147                return;
11148             else
11149                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
11150             end if;
11151          end Machine_Attribute;
11152
11153          ----------
11154          -- Main --
11155          ----------
11156
11157          --  pragma Main
11158          --   (MAIN_OPTION [, MAIN_OPTION]);
11159
11160          --  MAIN_OPTION ::=
11161          --    [STACK_SIZE              =>] static_integer_EXPRESSION
11162          --  | [TASK_STACK_SIZE_DEFAULT =>] static_integer_EXPRESSION
11163          --  | [TIME_SLICING_ENABLED    =>] static_boolean_EXPRESSION
11164
11165          when Pragma_Main => Main : declare
11166             Args  : Args_List (1 .. 3);
11167             Names : constant Name_List (1 .. 3) := (
11168                       Name_Stack_Size,
11169                       Name_Task_Stack_Size_Default,
11170                       Name_Time_Slicing_Enabled);
11171
11172             Nod : Node_Id;
11173
11174          begin
11175             GNAT_Pragma;
11176             Gather_Associations (Names, Args);
11177
11178             for J in 1 .. 2 loop
11179                if Present (Args (J)) then
11180                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
11181                end if;
11182             end loop;
11183
11184             if Present (Args (3)) then
11185                Check_Arg_Is_Static_Expression (Args (3), Standard_Boolean);
11186             end if;
11187
11188             Nod := Next (N);
11189             while Present (Nod) loop
11190                if Nkind (Nod) = N_Pragma
11191                  and then Pragma_Name (Nod) = Name_Main
11192                then
11193                   Error_Msg_Name_1 := Pname;
11194                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
11195                end if;
11196
11197                Next (Nod);
11198             end loop;
11199          end Main;
11200
11201          ------------------
11202          -- Main_Storage --
11203          ------------------
11204
11205          --  pragma Main_Storage
11206          --   (MAIN_STORAGE_OPTION [, MAIN_STORAGE_OPTION]);
11207
11208          --  MAIN_STORAGE_OPTION ::=
11209          --    [WORKING_STORAGE =>] static_SIMPLE_EXPRESSION
11210          --  | [TOP_GUARD =>] static_SIMPLE_EXPRESSION
11211
11212          when Pragma_Main_Storage => Main_Storage : declare
11213             Args  : Args_List (1 .. 2);
11214             Names : constant Name_List (1 .. 2) := (
11215                       Name_Working_Storage,
11216                       Name_Top_Guard);
11217
11218             Nod : Node_Id;
11219
11220          begin
11221             GNAT_Pragma;
11222             Gather_Associations (Names, Args);
11223
11224             for J in 1 .. 2 loop
11225                if Present (Args (J)) then
11226                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
11227                end if;
11228             end loop;
11229
11230             Check_In_Main_Program;
11231
11232             Nod := Next (N);
11233             while Present (Nod) loop
11234                if Nkind (Nod) = N_Pragma
11235                  and then Pragma_Name (Nod) = Name_Main_Storage
11236                then
11237                   Error_Msg_Name_1 := Pname;
11238                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
11239                end if;
11240
11241                Next (Nod);
11242             end loop;
11243          end Main_Storage;
11244
11245          -----------------
11246          -- Memory_Size --
11247          -----------------
11248
11249          --  pragma Memory_Size (NUMERIC_LITERAL)
11250
11251          when Pragma_Memory_Size =>
11252             GNAT_Pragma;
11253
11254             --  Memory size is simply ignored
11255
11256             Check_No_Identifiers;
11257             Check_Arg_Count (1);
11258             Check_Arg_Is_Integer_Literal (Arg1);
11259
11260          -------------
11261          -- No_Body --
11262          -------------
11263
11264          --  pragma No_Body;
11265
11266          --  The only correct use of this pragma is on its own in a file, in
11267          --  which case it is specially processed (see Gnat1drv.Check_Bad_Body
11268          --  and Frontend, which use Sinput.L.Source_File_Is_Pragma_No_Body to
11269          --  check for a file containing nothing but a No_Body pragma). If we
11270          --  attempt to process it during normal semantics processing, it means
11271          --  it was misplaced.
11272
11273          when Pragma_No_Body =>
11274             GNAT_Pragma;
11275             Pragma_Misplaced;
11276
11277          ---------------
11278          -- No_Return --
11279          ---------------
11280
11281          --  pragma No_Return (procedure_LOCAL_NAME {, procedure_Local_Name});
11282
11283          when Pragma_No_Return => No_Return : declare
11284             Id    : Node_Id;
11285             E     : Entity_Id;
11286             Found : Boolean;
11287             Arg   : Node_Id;
11288
11289          begin
11290             Ada_2005_Pragma;
11291             Check_At_Least_N_Arguments (1);
11292
11293             --  Loop through arguments of pragma
11294
11295             Arg := Arg1;
11296             while Present (Arg) loop
11297                Check_Arg_Is_Local_Name (Arg);
11298                Id := Get_Pragma_Arg (Arg);
11299                Analyze (Id);
11300
11301                if not Is_Entity_Name (Id) then
11302                   Error_Pragma_Arg ("entity name required", Arg);
11303                end if;
11304
11305                if Etype (Id) = Any_Type then
11306                   raise Pragma_Exit;
11307                end if;
11308
11309                --  Loop to find matching procedures
11310
11311                E := Entity (Id);
11312                Found := False;
11313                while Present (E)
11314                  and then Scope (E) = Current_Scope
11315                loop
11316                   if Ekind_In (E, E_Procedure, E_Generic_Procedure) then
11317                      Set_No_Return (E);
11318
11319                      --  Set flag on any alias as well
11320
11321                      if Is_Overloadable (E) and then Present (Alias (E)) then
11322                         Set_No_Return (Alias (E));
11323                      end if;
11324
11325                      Found := True;
11326                   end if;
11327
11328                   exit when From_Aspect_Specification (N);
11329                   E := Homonym (E);
11330                end loop;
11331
11332                if not Found then
11333                   Error_Pragma_Arg ("no procedure & found for pragma%", Arg);
11334                end if;
11335
11336                Next (Arg);
11337             end loop;
11338          end No_Return;
11339
11340          -----------------
11341          -- No_Run_Time --
11342          -----------------
11343
11344          --  pragma No_Run_Time;
11345
11346          --  Note: this pragma is retained for backwards compatibility. See
11347          --  body of Rtsfind for full details on its handling.
11348
11349          when Pragma_No_Run_Time =>
11350             GNAT_Pragma;
11351             Check_Valid_Configuration_Pragma;
11352             Check_Arg_Count (0);
11353
11354             No_Run_Time_Mode           := True;
11355             Configurable_Run_Time_Mode := True;
11356
11357             --  Set Duration to 32 bits if word size is 32
11358
11359             if Ttypes.System_Word_Size = 32 then
11360                Duration_32_Bits_On_Target := True;
11361             end if;
11362
11363             --  Set appropriate restrictions
11364
11365             Set_Restriction (No_Finalization, N);
11366             Set_Restriction (No_Exception_Handlers, N);
11367             Set_Restriction (Max_Tasks, N, 0);
11368             Set_Restriction (No_Tasking, N);
11369
11370          ------------------------
11371          -- No_Strict_Aliasing --
11372          ------------------------
11373
11374          --  pragma No_Strict_Aliasing [([Entity =>] type_LOCAL_NAME)];
11375
11376          when Pragma_No_Strict_Aliasing => No_Strict_Aliasing : declare
11377             E_Id : Entity_Id;
11378
11379          begin
11380             GNAT_Pragma;
11381             Check_At_Most_N_Arguments (1);
11382
11383             if Arg_Count = 0 then
11384                Check_Valid_Configuration_Pragma;
11385                Opt.No_Strict_Aliasing := True;
11386
11387             else
11388                Check_Optional_Identifier (Arg2, Name_Entity);
11389                Check_Arg_Is_Local_Name (Arg1);
11390                E_Id := Entity (Get_Pragma_Arg (Arg1));
11391
11392                if E_Id = Any_Type then
11393                   return;
11394                elsif No (E_Id) or else not Is_Access_Type (E_Id) then
11395                   Error_Pragma_Arg ("pragma% requires access type", Arg1);
11396                end if;
11397
11398                Set_No_Strict_Aliasing (Implementation_Base_Type (E_Id));
11399             end if;
11400          end No_Strict_Aliasing;
11401
11402          -----------------------
11403          -- Normalize_Scalars --
11404          -----------------------
11405
11406          --  pragma Normalize_Scalars;
11407
11408          when Pragma_Normalize_Scalars =>
11409             Check_Ada_83_Warning;
11410             Check_Arg_Count (0);
11411             Check_Valid_Configuration_Pragma;
11412
11413             --  Normalize_Scalars creates false positives in CodePeer, and
11414             --  incorrect negative results in Alfa mode, so ignore this pragma
11415             --  in these modes.
11416
11417             if not (CodePeer_Mode or Alfa_Mode) then
11418                Normalize_Scalars := True;
11419                Init_Or_Norm_Scalars := True;
11420             end if;
11421
11422          -----------------
11423          -- Obsolescent --
11424          -----------------
11425
11426          --  pragma Obsolescent;
11427
11428          --  pragma Obsolescent (
11429          --    [Message =>] static_string_EXPRESSION
11430          --  [,[Version =>] Ada_05]]);
11431
11432          --  pragma Obsolescent (
11433          --    [Entity  =>] NAME
11434          --  [,[Message =>] static_string_EXPRESSION
11435          --  [,[Version =>] Ada_05]] );
11436
11437          when Pragma_Obsolescent => Obsolescent : declare
11438             Ename : Node_Id;
11439             Decl  : Node_Id;
11440
11441             procedure Set_Obsolescent (E : Entity_Id);
11442             --  Given an entity Ent, mark it as obsolescent if appropriate
11443
11444             ---------------------
11445             -- Set_Obsolescent --
11446             ---------------------
11447
11448             procedure Set_Obsolescent (E : Entity_Id) is
11449                Active : Boolean;
11450                Ent    : Entity_Id;
11451                S      : String_Id;
11452
11453             begin
11454                Active := True;
11455                Ent    := E;
11456
11457                --  Entity name was given
11458
11459                if Present (Ename) then
11460
11461                   --  If entity name matches, we are fine. Save entity in
11462                   --  pragma argument, for ASIS use.
11463
11464                   if Chars (Ename) = Chars (Ent) then
11465                      Set_Entity (Ename, Ent);
11466                      Generate_Reference (Ent, Ename);
11467
11468                   --  If entity name does not match, only possibility is an
11469                   --  enumeration literal from an enumeration type declaration.
11470
11471                   elsif Ekind (Ent) /= E_Enumeration_Type then
11472                      Error_Pragma
11473                        ("pragma % entity name does not match declaration");
11474
11475                   else
11476                      Ent := First_Literal (E);
11477                      loop
11478                         if No (Ent) then
11479                            Error_Pragma
11480                              ("pragma % entity name does not match any " &
11481                               "enumeration literal");
11482
11483                         elsif Chars (Ent) = Chars (Ename) then
11484                            Set_Entity (Ename, Ent);
11485                            Generate_Reference (Ent, Ename);
11486                            exit;
11487
11488                         else
11489                            Ent := Next_Literal (Ent);
11490                         end if;
11491                      end loop;
11492                   end if;
11493                end if;
11494
11495                --  Ent points to entity to be marked
11496
11497                if Arg_Count >= 1 then
11498
11499                   --  Deal with static string argument
11500
11501                   Check_Arg_Is_Static_Expression (Arg1, Standard_String);
11502                   S := Strval (Get_Pragma_Arg (Arg1));
11503
11504                   for J in 1 .. String_Length (S) loop
11505                      if not In_Character_Range (Get_String_Char (S, J)) then
11506                         Error_Pragma_Arg
11507                           ("pragma% argument does not allow wide characters",
11508                            Arg1);
11509                      end if;
11510                   end loop;
11511
11512                   Obsolescent_Warnings.Append
11513                     ((Ent => Ent, Msg => Strval (Get_Pragma_Arg (Arg1))));
11514
11515                   --  Check for Ada_05 parameter
11516
11517                   if Arg_Count /= 1 then
11518                      Check_Arg_Count (2);
11519
11520                      declare
11521                         Argx : constant Node_Id := Get_Pragma_Arg (Arg2);
11522
11523                      begin
11524                         Check_Arg_Is_Identifier (Argx);
11525
11526                         if Chars (Argx) /= Name_Ada_05 then
11527                            Error_Msg_Name_2 := Name_Ada_05;
11528                            Error_Pragma_Arg
11529                              ("only allowed argument for pragma% is %", Argx);
11530                         end if;
11531
11532                         if Ada_Version_Explicit < Ada_2005
11533                           or else not Warn_On_Ada_2005_Compatibility
11534                         then
11535                            Active := False;
11536                         end if;
11537                      end;
11538                   end if;
11539                end if;
11540
11541                --  Set flag if pragma active
11542
11543                if Active then
11544                   Set_Is_Obsolescent (Ent);
11545                end if;
11546
11547                return;
11548             end Set_Obsolescent;
11549
11550          --  Start of processing for pragma Obsolescent
11551
11552          begin
11553             GNAT_Pragma;
11554
11555             Check_At_Most_N_Arguments (3);
11556
11557             --  See if first argument specifies an entity name
11558
11559             if Arg_Count >= 1
11560               and then
11561                 (Chars (Arg1) = Name_Entity
11562                    or else
11563                      Nkind_In (Get_Pragma_Arg (Arg1), N_Character_Literal,
11564                                                       N_Identifier,
11565                                                       N_Operator_Symbol))
11566             then
11567                Ename := Get_Pragma_Arg (Arg1);
11568
11569                --  Eliminate first argument, so we can share processing
11570
11571                Arg1 := Arg2;
11572                Arg2 := Arg3;
11573                Arg_Count := Arg_Count - 1;
11574
11575             --  No Entity name argument given
11576
11577             else
11578                Ename := Empty;
11579             end if;
11580
11581             if Arg_Count >= 1 then
11582                Check_Optional_Identifier (Arg1, Name_Message);
11583
11584                if Arg_Count = 2 then
11585                   Check_Optional_Identifier (Arg2, Name_Version);
11586                end if;
11587             end if;
11588
11589             --  Get immediately preceding declaration
11590
11591             Decl := Prev (N);
11592             while Present (Decl) and then Nkind (Decl) = N_Pragma loop
11593                Prev (Decl);
11594             end loop;
11595
11596             --  Cases where we do not follow anything other than another pragma
11597
11598             if No (Decl) then
11599
11600                --  First case: library level compilation unit declaration with
11601                --  the pragma immediately following the declaration.
11602
11603                if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
11604                   Set_Obsolescent
11605                     (Defining_Entity (Unit (Parent (Parent (N)))));
11606                   return;
11607
11608                --  Case 2: library unit placement for package
11609
11610                else
11611                   declare
11612                      Ent : constant Entity_Id := Find_Lib_Unit_Name;
11613                   begin
11614                      if Is_Package_Or_Generic_Package (Ent) then
11615                         Set_Obsolescent (Ent);
11616                         return;
11617                      end if;
11618                   end;
11619                end if;
11620
11621             --  Cases where we must follow a declaration
11622
11623             else
11624                if         Nkind (Decl) not in N_Declaration
11625                  and then Nkind (Decl) not in N_Later_Decl_Item
11626                  and then Nkind (Decl) not in N_Generic_Declaration
11627                  and then Nkind (Decl) not in N_Renaming_Declaration
11628                then
11629                   Error_Pragma
11630                     ("pragma% misplaced, "
11631                      & "must immediately follow a declaration");
11632
11633                else
11634                   Set_Obsolescent (Defining_Entity (Decl));
11635                   return;
11636                end if;
11637             end if;
11638          end Obsolescent;
11639
11640          --------------
11641          -- Optimize --
11642          --------------
11643
11644          --  pragma Optimize (Time | Space | Off);
11645
11646          --  The actual check for optimize is done in Gigi. Note that this
11647          --  pragma does not actually change the optimization setting, it
11648          --  simply checks that it is consistent with the pragma.
11649
11650          when Pragma_Optimize =>
11651             Check_No_Identifiers;
11652             Check_Arg_Count (1);
11653             Check_Arg_Is_One_Of (Arg1, Name_Time, Name_Space, Name_Off);
11654
11655          ------------------------
11656          -- Optimize_Alignment --
11657          ------------------------
11658
11659          --  pragma Optimize_Alignment (Time | Space | Off);
11660
11661          when Pragma_Optimize_Alignment => Optimize_Alignment : begin
11662             GNAT_Pragma;
11663             Check_No_Identifiers;
11664             Check_Arg_Count (1);
11665             Check_Valid_Configuration_Pragma;
11666
11667             declare
11668                Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
11669             begin
11670                case Nam is
11671                   when Name_Time =>
11672                      Opt.Optimize_Alignment := 'T';
11673                   when Name_Space =>
11674                      Opt.Optimize_Alignment := 'S';
11675                   when Name_Off =>
11676                      Opt.Optimize_Alignment := 'O';
11677                   when others =>
11678                      Error_Pragma_Arg ("invalid argument for pragma%", Arg1);
11679                end case;
11680             end;
11681
11682             --  Set indication that mode is set locally. If we are in fact in a
11683             --  configuration pragma file, this setting is harmless since the
11684             --  switch will get reset anyway at the start of each unit.
11685
11686             Optimize_Alignment_Local := True;
11687          end Optimize_Alignment;
11688
11689          -------------
11690          -- Ordered --
11691          -------------
11692
11693          --  pragma Ordered (first_enumeration_subtype_LOCAL_NAME);
11694
11695          when Pragma_Ordered => Ordered : declare
11696             Assoc   : constant Node_Id := Arg1;
11697             Type_Id : Node_Id;
11698             Typ     : Entity_Id;
11699
11700          begin
11701             GNAT_Pragma;
11702             Check_No_Identifiers;
11703             Check_Arg_Count (1);
11704             Check_Arg_Is_Local_Name (Arg1);
11705
11706             Type_Id := Get_Pragma_Arg (Assoc);
11707             Find_Type (Type_Id);
11708             Typ := Entity (Type_Id);
11709
11710             if Typ = Any_Type then
11711                return;
11712             else
11713                Typ := Underlying_Type (Typ);
11714             end if;
11715
11716             if not Is_Enumeration_Type (Typ) then
11717                Error_Pragma ("pragma% must specify enumeration type");
11718             end if;
11719
11720             Check_First_Subtype (Arg1);
11721             Set_Has_Pragma_Ordered (Base_Type (Typ));
11722          end Ordered;
11723
11724          ----------
11725          -- Pack --
11726          ----------
11727
11728          --  pragma Pack (first_subtype_LOCAL_NAME);
11729
11730          when Pragma_Pack => Pack : declare
11731             Assoc   : constant Node_Id := Arg1;
11732             Type_Id : Node_Id;
11733             Typ     : Entity_Id;
11734             Ctyp    : Entity_Id;
11735             Ignore  : Boolean := False;
11736
11737          begin
11738             Check_No_Identifiers;
11739             Check_Arg_Count (1);
11740             Check_Arg_Is_Local_Name (Arg1);
11741
11742             Type_Id := Get_Pragma_Arg (Assoc);
11743             Find_Type (Type_Id);
11744             Typ := Entity (Type_Id);
11745
11746             if Typ = Any_Type
11747               or else Rep_Item_Too_Early (Typ, N)
11748             then
11749                return;
11750             else
11751                Typ := Underlying_Type (Typ);
11752             end if;
11753
11754             if not Is_Array_Type (Typ) and then not Is_Record_Type (Typ) then
11755                Error_Pragma ("pragma% must specify array or record type");
11756             end if;
11757
11758             Check_First_Subtype (Arg1);
11759             Check_Duplicate_Pragma (Typ);
11760
11761             --  Array type
11762
11763             if Is_Array_Type (Typ) then
11764                Ctyp := Component_Type (Typ);
11765
11766                --  Ignore pack that does nothing
11767
11768                if Known_Static_Esize (Ctyp)
11769                  and then Known_Static_RM_Size (Ctyp)
11770                  and then Esize (Ctyp) = RM_Size (Ctyp)
11771                  and then Addressable (Esize (Ctyp))
11772                then
11773                   Ignore := True;
11774                end if;
11775
11776                --  Process OK pragma Pack. Note that if there is a separate
11777                --  component clause present, the Pack will be cancelled. This
11778                --  processing is in Freeze.
11779
11780                if not Rep_Item_Too_Late (Typ, N) then
11781
11782                   --  In the context of static code analysis, we do not need
11783                   --  complex front-end expansions related to pragma Pack,
11784                   --  so disable handling of pragma Pack in these cases.
11785
11786                   if CodePeer_Mode or Alfa_Mode then
11787                      null;
11788
11789                   --  Don't attempt any packing for VM targets. We possibly
11790                   --  could deal with some cases of array bit-packing, but we
11791                   --  don't bother, since this is not a typical kind of
11792                   --  representation in the VM context anyway (and would not
11793                   --  for example work nicely with the debugger).
11794
11795                   elsif VM_Target /= No_VM then
11796                      if not GNAT_Mode then
11797                         Error_Pragma
11798                           ("?pragma% ignored in this configuration");
11799                      end if;
11800
11801                   --  Normal case where we do the pack action
11802
11803                   else
11804                      if not Ignore then
11805                         Set_Is_Packed            (Base_Type (Typ));
11806                         Set_Has_Non_Standard_Rep (Base_Type (Typ));
11807                      end if;
11808
11809                      Set_Has_Pragma_Pack (Base_Type (Typ));
11810                   end if;
11811                end if;
11812
11813             --  For record types, the pack is always effective
11814
11815             else pragma Assert (Is_Record_Type (Typ));
11816                if not Rep_Item_Too_Late (Typ, N) then
11817
11818                   --  Ignore pack request with warning in VM mode (skip warning
11819                   --  if we are compiling GNAT run time library).
11820
11821                   if VM_Target /= No_VM then
11822                      if not GNAT_Mode then
11823                         Error_Pragma
11824                           ("?pragma% ignored in this configuration");
11825                      end if;
11826
11827                   --  Normal case of pack request active
11828
11829                   else
11830                      Set_Is_Packed            (Base_Type (Typ));
11831                      Set_Has_Pragma_Pack      (Base_Type (Typ));
11832                      Set_Has_Non_Standard_Rep (Base_Type (Typ));
11833                   end if;
11834                end if;
11835             end if;
11836          end Pack;
11837
11838          ----------
11839          -- Page --
11840          ----------
11841
11842          --  pragma Page;
11843
11844          --  There is nothing to do here, since we did all the processing for
11845          --  this pragma in Par.Prag (so that it works properly even in syntax
11846          --  only mode).
11847
11848          when Pragma_Page =>
11849             null;
11850
11851          -------------
11852          -- Passive --
11853          -------------
11854
11855          --  pragma Passive [(PASSIVE_FORM)];
11856
11857          --  PASSIVE_FORM ::= Semaphore | No
11858
11859          when Pragma_Passive =>
11860             GNAT_Pragma;
11861
11862             if Nkind (Parent (N)) /= N_Task_Definition then
11863                Error_Pragma ("pragma% must be within task definition");
11864             end if;
11865
11866             if Arg_Count /= 0 then
11867                Check_Arg_Count (1);
11868                Check_Arg_Is_One_Of (Arg1, Name_Semaphore, Name_No);
11869             end if;
11870
11871          ----------------------------------
11872          -- Preelaborable_Initialization --
11873          ----------------------------------
11874
11875          --  pragma Preelaborable_Initialization (DIRECT_NAME);
11876
11877          when Pragma_Preelaborable_Initialization => Preelab_Init : declare
11878             Ent : Entity_Id;
11879
11880          begin
11881             Ada_2005_Pragma;
11882             Check_Arg_Count (1);
11883             Check_No_Identifiers;
11884             Check_Arg_Is_Identifier (Arg1);
11885             Check_Arg_Is_Local_Name (Arg1);
11886             Check_First_Subtype (Arg1);
11887             Ent := Entity (Get_Pragma_Arg (Arg1));
11888
11889             if not (Is_Private_Type (Ent)
11890                       or else
11891                     Is_Protected_Type (Ent)
11892                       or else
11893                     (Is_Generic_Type (Ent) and then Is_Derived_Type (Ent)))
11894             then
11895                Error_Pragma_Arg
11896                  ("pragma % can only be applied to private, formal derived or "
11897                   & "protected type",
11898                   Arg1);
11899             end if;
11900
11901             --  Give an error if the pragma is applied to a protected type that
11902             --  does not qualify (due to having entries, or due to components
11903             --  that do not qualify).
11904
11905             if Is_Protected_Type (Ent)
11906               and then not Has_Preelaborable_Initialization (Ent)
11907             then
11908                Error_Msg_N
11909                  ("protected type & does not have preelaborable " &
11910                   "initialization", Ent);
11911
11912             --  Otherwise mark the type as definitely having preelaborable
11913             --  initialization.
11914
11915             else
11916                Set_Known_To_Have_Preelab_Init (Ent);
11917             end if;
11918
11919             if Has_Pragma_Preelab_Init (Ent)
11920               and then Warn_On_Redundant_Constructs
11921             then
11922                Error_Pragma ("?duplicate pragma%!");
11923             else
11924                Set_Has_Pragma_Preelab_Init (Ent);
11925             end if;
11926          end Preelab_Init;
11927
11928          --------------------
11929          -- Persistent_BSS --
11930          --------------------
11931
11932          --  pragma Persistent_BSS [(object_NAME)];
11933
11934          when Pragma_Persistent_BSS => Persistent_BSS :  declare
11935             Decl : Node_Id;
11936             Ent  : Entity_Id;
11937             Prag : Node_Id;
11938
11939          begin
11940             GNAT_Pragma;
11941             Check_At_Most_N_Arguments (1);
11942
11943             --  Case of application to specific object (one argument)
11944
11945             if Arg_Count = 1 then
11946                Check_Arg_Is_Library_Level_Local_Name (Arg1);
11947
11948                if not Is_Entity_Name (Get_Pragma_Arg (Arg1))
11949                  or else not
11950                   Ekind_In (Entity (Get_Pragma_Arg (Arg1)), E_Variable,
11951                                                             E_Constant)
11952                then
11953                   Error_Pragma_Arg ("pragma% only applies to objects", Arg1);
11954                end if;
11955
11956                Ent := Entity (Get_Pragma_Arg (Arg1));
11957                Decl := Parent (Ent);
11958
11959                if Rep_Item_Too_Late (Ent, N) then
11960                   return;
11961                end if;
11962
11963                if Present (Expression (Decl)) then
11964                   Error_Pragma_Arg
11965                     ("object for pragma% cannot have initialization", Arg1);
11966                end if;
11967
11968                if not Is_Potentially_Persistent_Type (Etype (Ent)) then
11969                   Error_Pragma_Arg
11970                     ("object type for pragma% is not potentially persistent",
11971                      Arg1);
11972                end if;
11973
11974                Check_Duplicate_Pragma (Ent);
11975
11976                Prag :=
11977                  Make_Linker_Section_Pragma
11978                    (Ent, Sloc (N), ".persistent.bss");
11979                Insert_After (N, Prag);
11980                Analyze (Prag);
11981
11982             --  Case of use as configuration pragma with no arguments
11983
11984             else
11985                Check_Valid_Configuration_Pragma;
11986                Persistent_BSS_Mode := True;
11987             end if;
11988          end Persistent_BSS;
11989
11990          -------------
11991          -- Polling --
11992          -------------
11993
11994          --  pragma Polling (ON | OFF);
11995
11996          when Pragma_Polling =>
11997             GNAT_Pragma;
11998             Check_Arg_Count (1);
11999             Check_No_Identifiers;
12000             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
12001             Polling_Required := (Chars (Get_Pragma_Arg (Arg1)) = Name_On);
12002
12003          -------------------
12004          -- Postcondition --
12005          -------------------
12006
12007          --  pragma Postcondition ([Check   =>] Boolean_EXPRESSION
12008          --                      [,[Message =>] String_EXPRESSION]);
12009
12010          when Pragma_Postcondition => Postcondition : declare
12011             In_Body : Boolean;
12012             pragma Warnings (Off, In_Body);
12013
12014          begin
12015             GNAT_Pragma;
12016             Check_At_Least_N_Arguments (1);
12017             Check_At_Most_N_Arguments (2);
12018             Check_Optional_Identifier (Arg1, Name_Check);
12019
12020             --  All we need to do here is call the common check procedure,
12021             --  the remainder of the processing is found in Sem_Ch6/Sem_Ch7.
12022
12023             Check_Precondition_Postcondition (In_Body);
12024          end Postcondition;
12025
12026          ------------------
12027          -- Precondition --
12028          ------------------
12029
12030          --  pragma Precondition ([Check   =>] Boolean_EXPRESSION
12031          --                     [,[Message =>] String_EXPRESSION]);
12032
12033          when Pragma_Precondition => Precondition : declare
12034             In_Body : Boolean;
12035
12036          begin
12037             GNAT_Pragma;
12038             Check_At_Least_N_Arguments (1);
12039             Check_At_Most_N_Arguments (2);
12040             Check_Optional_Identifier (Arg1, Name_Check);
12041             Check_Precondition_Postcondition (In_Body);
12042
12043             --  If in spec, nothing more to do. If in body, then we convert the
12044             --  pragma to pragma Check (Precondition, cond [, msg]). Note we do
12045             --  this whether or not precondition checks are enabled. That works
12046             --  fine since pragma Check will do this check, and will also
12047             --  analyze the condition itself in the proper context.
12048
12049             if In_Body then
12050                Rewrite (N,
12051                  Make_Pragma (Loc,
12052                    Chars => Name_Check,
12053                    Pragma_Argument_Associations => New_List (
12054                      Make_Pragma_Argument_Association (Loc,
12055                        Expression => Make_Identifier (Loc, Name_Precondition)),
12056
12057                      Make_Pragma_Argument_Association (Sloc (Arg1),
12058                        Expression => Relocate_Node (Get_Pragma_Arg (Arg1))))));
12059
12060                if Arg_Count = 2 then
12061                   Append_To (Pragma_Argument_Associations (N),
12062                     Make_Pragma_Argument_Association (Sloc (Arg2),
12063                       Expression => Relocate_Node (Get_Pragma_Arg (Arg2))));
12064                end if;
12065
12066                Analyze (N);
12067             end if;
12068          end Precondition;
12069
12070          ---------------
12071          -- Predicate --
12072          ---------------
12073
12074          --  pragma Predicate
12075          --    ([Entity =>] type_LOCAL_NAME,
12076          --     [Check  =>] EXPRESSION);
12077
12078          when Pragma_Predicate => Predicate : declare
12079             Type_Id : Node_Id;
12080             Typ     : Entity_Id;
12081
12082             Discard : Boolean;
12083             pragma Unreferenced (Discard);
12084
12085          begin
12086             GNAT_Pragma;
12087             Check_Arg_Count (2);
12088             Check_Optional_Identifier (Arg1, Name_Entity);
12089             Check_Optional_Identifier (Arg2, Name_Check);
12090
12091             Check_Arg_Is_Local_Name (Arg1);
12092
12093             Type_Id := Get_Pragma_Arg (Arg1);
12094             Find_Type (Type_Id);
12095             Typ := Entity (Type_Id);
12096
12097             if Typ = Any_Type then
12098                return;
12099             end if;
12100
12101             --  The remaining processing is simply to link the pragma on to
12102             --  the rep item chain, for processing when the type is frozen.
12103             --  This is accomplished by a call to Rep_Item_Too_Late. We also
12104             --  mark the type as having predicates.
12105
12106             Set_Has_Predicates (Typ);
12107             Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
12108          end Predicate;
12109
12110          ------------------
12111          -- Preelaborate --
12112          ------------------
12113
12114          --  pragma Preelaborate [(library_unit_NAME)];
12115
12116          --  Set the flag Is_Preelaborated of program unit name entity
12117
12118          when Pragma_Preelaborate => Preelaborate : declare
12119             Pa  : constant Node_Id   := Parent (N);
12120             Pk  : constant Node_Kind := Nkind (Pa);
12121             Ent : Entity_Id;
12122
12123          begin
12124             Check_Ada_83_Warning;
12125             Check_Valid_Library_Unit_Pragma;
12126
12127             if Nkind (N) = N_Null_Statement then
12128                return;
12129             end if;
12130
12131             Ent := Find_Lib_Unit_Name;
12132             Check_Duplicate_Pragma (Ent);
12133
12134             --  This filters out pragmas inside generic parent then
12135             --  show up inside instantiation
12136
12137             if Present (Ent)
12138               and then not (Pk = N_Package_Specification
12139                              and then Present (Generic_Parent (Pa)))
12140             then
12141                if not Debug_Flag_U then
12142                   Set_Is_Preelaborated (Ent);
12143                   Set_Suppress_Elaboration_Warnings (Ent);
12144                end if;
12145             end if;
12146          end Preelaborate;
12147
12148          ---------------------
12149          -- Preelaborate_05 --
12150          ---------------------
12151
12152          --  pragma Preelaborate_05 [(library_unit_NAME)];
12153
12154          --  This pragma is useable only in GNAT_Mode, where it is used like
12155          --  pragma Preelaborate but it is only effective in Ada 2005 mode
12156          --  (otherwise it is ignored). This is used to implement AI-362 which
12157          --  recategorizes some run-time packages in Ada 2005 mode.
12158
12159          when Pragma_Preelaborate_05 => Preelaborate_05 : declare
12160             Ent : Entity_Id;
12161
12162          begin
12163             GNAT_Pragma;
12164             Check_Valid_Library_Unit_Pragma;
12165
12166             if not GNAT_Mode then
12167                Error_Pragma ("pragma% only available in GNAT mode");
12168             end if;
12169
12170             if Nkind (N) = N_Null_Statement then
12171                return;
12172             end if;
12173
12174             --  This is one of the few cases where we need to test the value of
12175             --  Ada_Version_Explicit rather than Ada_Version (which is always
12176             --  set to Ada_2012 in a predefined unit), we need to know the
12177             --  explicit version set to know if this pragma is active.
12178
12179             if Ada_Version_Explicit >= Ada_2005 then
12180                Ent := Find_Lib_Unit_Name;
12181                Set_Is_Preelaborated (Ent);
12182                Set_Suppress_Elaboration_Warnings (Ent);
12183             end if;
12184          end Preelaborate_05;
12185
12186          --------------
12187          -- Priority --
12188          --------------
12189
12190          --  pragma Priority (EXPRESSION);
12191
12192          when Pragma_Priority => Priority : declare
12193             P   : constant Node_Id := Parent (N);
12194             Arg : Node_Id;
12195
12196          begin
12197             Check_No_Identifiers;
12198             Check_Arg_Count (1);
12199
12200             --  Subprogram case
12201
12202             if Nkind (P) = N_Subprogram_Body then
12203                Check_In_Main_Program;
12204
12205                Arg := Get_Pragma_Arg (Arg1);
12206                Analyze_And_Resolve (Arg, Standard_Integer);
12207
12208                --  Must be static
12209
12210                if not Is_Static_Expression (Arg) then
12211                   Flag_Non_Static_Expr
12212                     ("main subprogram priority is not static!", Arg);
12213                   raise Pragma_Exit;
12214
12215                --  If constraint error, then we already signalled an error
12216
12217                elsif Raises_Constraint_Error (Arg) then
12218                   null;
12219
12220                --  Otherwise check in range
12221
12222                else
12223                   declare
12224                      Val : constant Uint := Expr_Value (Arg);
12225
12226                   begin
12227                      if Val < 0
12228                        or else Val > Expr_Value (Expression
12229                                        (Parent (RTE (RE_Max_Priority))))
12230                      then
12231                         Error_Pragma_Arg
12232                           ("main subprogram priority is out of range", Arg1);
12233                      end if;
12234                   end;
12235                end if;
12236
12237                Set_Main_Priority
12238                     (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
12239
12240                --  Load an arbitrary entity from System.Tasking to make sure
12241                --  this package is implicitly with'ed, since we need to have
12242                --  the tasking run-time active for the pragma Priority to have
12243                --  any effect.
12244
12245                declare
12246                   Discard : Entity_Id;
12247                   pragma Warnings (Off, Discard);
12248                begin
12249                   Discard := RTE (RE_Task_List);
12250                end;
12251
12252             --  Task or Protected, must be of type Integer
12253
12254             elsif Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
12255                Arg := Get_Pragma_Arg (Arg1);
12256
12257                --  The expression must be analyzed in the special manner
12258                --  described in "Handling of Default and Per-Object
12259                --  Expressions" in sem.ads.
12260
12261                Preanalyze_Spec_Expression (Arg, Standard_Integer);
12262
12263                if not Is_Static_Expression (Arg) then
12264                   Check_Restriction (Static_Priorities, Arg);
12265                end if;
12266
12267             --  Anything else is incorrect
12268
12269             else
12270                Pragma_Misplaced;
12271             end if;
12272
12273             if Has_Pragma_Priority (P) then
12274                Error_Pragma ("duplicate pragma% not allowed");
12275             else
12276                Set_Has_Pragma_Priority (P, True);
12277
12278                if Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
12279                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
12280                   --  exp_ch9 should use this ???
12281                end if;
12282             end if;
12283          end Priority;
12284
12285          -----------------------------------
12286          -- Priority_Specific_Dispatching --
12287          -----------------------------------
12288
12289          --  pragma Priority_Specific_Dispatching (
12290          --    policy_IDENTIFIER,
12291          --    first_priority_EXPRESSION,
12292          --    last_priority_EXPRESSION);
12293
12294          when Pragma_Priority_Specific_Dispatching =>
12295          Priority_Specific_Dispatching : declare
12296             Prio_Id : constant Entity_Id := RTE (RE_Any_Priority);
12297             --  This is the entity System.Any_Priority;
12298
12299             DP          : Character;
12300             Lower_Bound : Node_Id;
12301             Upper_Bound : Node_Id;
12302             Lower_Val   : Uint;
12303             Upper_Val   : Uint;
12304
12305          begin
12306             Ada_2005_Pragma;
12307             Check_Arg_Count (3);
12308             Check_No_Identifiers;
12309             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
12310             Check_Valid_Configuration_Pragma;
12311             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
12312             DP := Fold_Upper (Name_Buffer (1));
12313
12314             Lower_Bound := Get_Pragma_Arg (Arg2);
12315             Check_Arg_Is_Static_Expression (Lower_Bound, Standard_Integer);
12316             Lower_Val := Expr_Value (Lower_Bound);
12317
12318             Upper_Bound := Get_Pragma_Arg (Arg3);
12319             Check_Arg_Is_Static_Expression (Upper_Bound, Standard_Integer);
12320             Upper_Val := Expr_Value (Upper_Bound);
12321
12322             --  It is not allowed to use Task_Dispatching_Policy and
12323             --  Priority_Specific_Dispatching in the same partition.
12324
12325             if Task_Dispatching_Policy /= ' ' then
12326                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
12327                Error_Pragma
12328                  ("pragma% incompatible with Task_Dispatching_Policy#");
12329
12330             --  Check lower bound in range
12331
12332             elsif Lower_Val < Expr_Value (Type_Low_Bound (Prio_Id))
12333                     or else
12334                   Lower_Val > Expr_Value (Type_High_Bound (Prio_Id))
12335             then
12336                Error_Pragma_Arg
12337                  ("first_priority is out of range", Arg2);
12338
12339             --  Check upper bound in range
12340
12341             elsif Upper_Val < Expr_Value (Type_Low_Bound (Prio_Id))
12342                     or else
12343                   Upper_Val > Expr_Value (Type_High_Bound (Prio_Id))
12344             then
12345                Error_Pragma_Arg
12346                  ("last_priority is out of range", Arg3);
12347
12348             --  Check that the priority range is valid
12349
12350             elsif Lower_Val > Upper_Val then
12351                Error_Pragma
12352                  ("last_priority_expression must be greater than" &
12353                   " or equal to first_priority_expression");
12354
12355             --  Store the new policy, but always preserve System_Location since
12356             --  we like the error message with the run-time name.
12357
12358             else
12359                --  Check overlapping in the priority ranges specified in other
12360                --  Priority_Specific_Dispatching pragmas within the same
12361                --  partition. We can only check those we know about!
12362
12363                for J in
12364                   Specific_Dispatching.First .. Specific_Dispatching.Last
12365                loop
12366                   if Specific_Dispatching.Table (J).First_Priority in
12367                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
12368                   or else Specific_Dispatching.Table (J).Last_Priority in
12369                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
12370                   then
12371                      Error_Msg_Sloc :=
12372                        Specific_Dispatching.Table (J).Pragma_Loc;
12373                         Error_Pragma
12374                           ("priority range overlaps with "
12375                            & "Priority_Specific_Dispatching#");
12376                   end if;
12377                end loop;
12378
12379                --  The use of Priority_Specific_Dispatching is incompatible
12380                --  with Task_Dispatching_Policy.
12381
12382                if Task_Dispatching_Policy /= ' ' then
12383                   Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
12384                      Error_Pragma
12385                        ("Priority_Specific_Dispatching incompatible "
12386                         & "with Task_Dispatching_Policy#");
12387                end if;
12388
12389                --  The use of Priority_Specific_Dispatching forces ceiling
12390                --  locking policy.
12391
12392                if Locking_Policy /= ' ' and then Locking_Policy /= 'C' then
12393                   Error_Msg_Sloc := Locking_Policy_Sloc;
12394                      Error_Pragma
12395                        ("Priority_Specific_Dispatching incompatible "
12396                         & "with Locking_Policy#");
12397
12398                --  Set the Ceiling_Locking policy, but preserve System_Location
12399                --  since we like the error message with the run time name.
12400
12401                else
12402                   Locking_Policy := 'C';
12403
12404                   if Locking_Policy_Sloc /= System_Location then
12405                      Locking_Policy_Sloc := Loc;
12406                   end if;
12407                end if;
12408
12409                --  Add entry in the table
12410
12411                Specific_Dispatching.Append
12412                     ((Dispatching_Policy => DP,
12413                       First_Priority     => UI_To_Int (Lower_Val),
12414                       Last_Priority      => UI_To_Int (Upper_Val),
12415                       Pragma_Loc         => Loc));
12416             end if;
12417          end Priority_Specific_Dispatching;
12418
12419          -------------
12420          -- Profile --
12421          -------------
12422
12423          --  pragma Profile (profile_IDENTIFIER);
12424
12425          --  profile_IDENTIFIER => Restricted | Ravenscar
12426
12427          when Pragma_Profile =>
12428             Ada_2005_Pragma;
12429             Check_Arg_Count (1);
12430             Check_Valid_Configuration_Pragma;
12431             Check_No_Identifiers;
12432
12433             declare
12434                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
12435
12436             begin
12437                if Chars (Argx) = Name_Ravenscar then
12438                   Set_Ravenscar_Profile (N);
12439
12440                elsif Chars (Argx) = Name_Restricted then
12441                   Set_Profile_Restrictions
12442                     (Restricted,
12443                      N, Warn => Treat_Restrictions_As_Warnings);
12444
12445                elsif Chars (Argx) = Name_No_Implementation_Extensions then
12446                   Set_Profile_Restrictions
12447                     (No_Implementation_Extensions,
12448                      N, Warn => Treat_Restrictions_As_Warnings);
12449
12450                else
12451                   Error_Pragma_Arg ("& is not a valid profile", Argx);
12452                end if;
12453             end;
12454
12455          ----------------------
12456          -- Profile_Warnings --
12457          ----------------------
12458
12459          --  pragma Profile_Warnings (profile_IDENTIFIER);
12460
12461          --  profile_IDENTIFIER => Restricted | Ravenscar
12462
12463          when Pragma_Profile_Warnings =>
12464             GNAT_Pragma;
12465             Check_Arg_Count (1);
12466             Check_Valid_Configuration_Pragma;
12467             Check_No_Identifiers;
12468
12469             declare
12470                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
12471
12472             begin
12473                if Chars (Argx) = Name_Ravenscar then
12474                   Set_Profile_Restrictions (Ravenscar, N, Warn => True);
12475
12476                elsif Chars (Argx) = Name_Restricted then
12477                   Set_Profile_Restrictions (Restricted, N, Warn => True);
12478
12479                elsif Chars (Argx) = Name_No_Implementation_Extensions then
12480                   Set_Profile_Restrictions
12481                     (No_Implementation_Extensions, N, Warn => True);
12482
12483                else
12484                   Error_Pragma_Arg ("& is not a valid profile", Argx);
12485                end if;
12486             end;
12487
12488          --------------------------
12489          -- Propagate_Exceptions --
12490          --------------------------
12491
12492          --  pragma Propagate_Exceptions;
12493
12494          --  Note: this pragma is obsolete and has no effect
12495
12496          when Pragma_Propagate_Exceptions =>
12497             GNAT_Pragma;
12498             Check_Arg_Count (0);
12499
12500             if In_Extended_Main_Source_Unit (N) then
12501                Propagate_Exceptions := True;
12502             end if;
12503
12504          ------------------
12505          -- Psect_Object --
12506          ------------------
12507
12508          --  pragma Psect_Object (
12509          --        [Internal =>] LOCAL_NAME,
12510          --     [, [External =>] EXTERNAL_SYMBOL]
12511          --     [, [Size     =>] EXTERNAL_SYMBOL]);
12512
12513          when Pragma_Psect_Object | Pragma_Common_Object =>
12514          Psect_Object : declare
12515             Args  : Args_List (1 .. 3);
12516             Names : constant Name_List (1 .. 3) := (
12517                       Name_Internal,
12518                       Name_External,
12519                       Name_Size);
12520
12521             Internal : Node_Id renames Args (1);
12522             External : Node_Id renames Args (2);
12523             Size     : Node_Id renames Args (3);
12524
12525             Def_Id : Entity_Id;
12526
12527             procedure Check_Too_Long (Arg : Node_Id);
12528             --  Posts message if the argument is an identifier with more
12529             --  than 31 characters, or a string literal with more than
12530             --  31 characters, and we are operating under VMS
12531
12532             --------------------
12533             -- Check_Too_Long --
12534             --------------------
12535
12536             procedure Check_Too_Long (Arg : Node_Id) is
12537                X : constant Node_Id := Original_Node (Arg);
12538
12539             begin
12540                if not Nkind_In (X, N_String_Literal, N_Identifier) then
12541                   Error_Pragma_Arg
12542                     ("inappropriate argument for pragma %", Arg);
12543                end if;
12544
12545                if OpenVMS_On_Target then
12546                   if (Nkind (X) = N_String_Literal
12547                        and then String_Length (Strval (X)) > 31)
12548                     or else
12549                      (Nkind (X) = N_Identifier
12550                        and then Length_Of_Name (Chars (X)) > 31)
12551                   then
12552                      Error_Pragma_Arg
12553                        ("argument for pragma % is longer than 31 characters",
12554                         Arg);
12555                   end if;
12556                end if;
12557             end Check_Too_Long;
12558
12559          --  Start of processing for Common_Object/Psect_Object
12560
12561          begin
12562             GNAT_Pragma;
12563             Gather_Associations (Names, Args);
12564             Process_Extended_Import_Export_Internal_Arg (Internal);
12565
12566             Def_Id := Entity (Internal);
12567
12568             if not Ekind_In (Def_Id, E_Constant, E_Variable) then
12569                Error_Pragma_Arg
12570                  ("pragma% must designate an object", Internal);
12571             end if;
12572
12573             Check_Too_Long (Internal);
12574
12575             if Is_Imported (Def_Id) or else Is_Exported (Def_Id) then
12576                Error_Pragma_Arg
12577                  ("cannot use pragma% for imported/exported object",
12578                   Internal);
12579             end if;
12580
12581             if Is_Concurrent_Type (Etype (Internal)) then
12582                Error_Pragma_Arg
12583                  ("cannot specify pragma % for task/protected object",
12584                   Internal);
12585             end if;
12586
12587             if Has_Rep_Pragma (Def_Id, Name_Common_Object)
12588                  or else
12589                Has_Rep_Pragma (Def_Id, Name_Psect_Object)
12590             then
12591                Error_Msg_N ("?duplicate Common/Psect_Object pragma", N);
12592             end if;
12593
12594             if Ekind (Def_Id) = E_Constant then
12595                Error_Pragma_Arg
12596                  ("cannot specify pragma % for a constant", Internal);
12597             end if;
12598
12599             if Is_Record_Type (Etype (Internal)) then
12600                declare
12601                   Ent  : Entity_Id;
12602                   Decl : Entity_Id;
12603
12604                begin
12605                   Ent := First_Entity (Etype (Internal));
12606                   while Present (Ent) loop
12607                      Decl := Declaration_Node (Ent);
12608
12609                      if Ekind (Ent) = E_Component
12610                        and then Nkind (Decl) = N_Component_Declaration
12611                        and then Present (Expression (Decl))
12612                        and then Warn_On_Export_Import
12613                      then
12614                         Error_Msg_N
12615                           ("?object for pragma % has defaults", Internal);
12616                         exit;
12617
12618                      else
12619                         Next_Entity (Ent);
12620                      end if;
12621                   end loop;
12622                end;
12623             end if;
12624
12625             if Present (Size) then
12626                Check_Too_Long (Size);
12627             end if;
12628
12629             if Present (External) then
12630                Check_Arg_Is_External_Name (External);
12631                Check_Too_Long (External);
12632             end if;
12633
12634             --  If all error tests pass, link pragma on to the rep item chain
12635
12636             Record_Rep_Item (Def_Id, N);
12637          end Psect_Object;
12638
12639          ----------
12640          -- Pure --
12641          ----------
12642
12643          --  pragma Pure [(library_unit_NAME)];
12644
12645          when Pragma_Pure => Pure : declare
12646             Ent : Entity_Id;
12647
12648          begin
12649             Check_Ada_83_Warning;
12650             Check_Valid_Library_Unit_Pragma;
12651
12652             if Nkind (N) = N_Null_Statement then
12653                return;
12654             end if;
12655
12656             Ent := Find_Lib_Unit_Name;
12657             Set_Is_Pure (Ent);
12658             Set_Has_Pragma_Pure (Ent);
12659             Set_Suppress_Elaboration_Warnings (Ent);
12660          end Pure;
12661
12662          -------------
12663          -- Pure_05 --
12664          -------------
12665
12666          --  pragma Pure_05 [(library_unit_NAME)];
12667
12668          --  This pragma is useable only in GNAT_Mode, where it is used like
12669          --  pragma Pure but it is only effective in Ada 2005 mode (otherwise
12670          --  it is ignored). It may be used after a pragma Preelaborate, in
12671          --  which case it overrides the effect of the pragma Preelaborate.
12672          --  This is used to implement AI-362 which recategorizes some run-time
12673          --  packages in Ada 2005 mode.
12674
12675          when Pragma_Pure_05 => Pure_05 : declare
12676             Ent : Entity_Id;
12677
12678          begin
12679             GNAT_Pragma;
12680             Check_Valid_Library_Unit_Pragma;
12681
12682             if not GNAT_Mode then
12683                Error_Pragma ("pragma% only available in GNAT mode");
12684             end if;
12685
12686             if Nkind (N) = N_Null_Statement then
12687                return;
12688             end if;
12689
12690             --  This is one of the few cases where we need to test the value of
12691             --  Ada_Version_Explicit rather than Ada_Version (which is always
12692             --  set to Ada_2012 in a predefined unit), we need to know the
12693             --  explicit version set to know if this pragma is active.
12694
12695             if Ada_Version_Explicit >= Ada_2005 then
12696                Ent := Find_Lib_Unit_Name;
12697                Set_Is_Preelaborated (Ent, False);
12698                Set_Is_Pure (Ent);
12699                Set_Suppress_Elaboration_Warnings (Ent);
12700             end if;
12701          end Pure_05;
12702
12703          -------------
12704          -- Pure_12 --
12705          -------------
12706
12707          --  pragma Pure_12 [(library_unit_NAME)];
12708
12709          --  This pragma is useable only in GNAT_Mode, where it is used like
12710          --  pragma Pure but it is only effective in Ada 2012 mode (otherwise
12711          --  it is ignored). It may be used after a pragma Preelaborate, in
12712          --  which case it overrides the effect of the pragma Preelaborate.
12713          --  This is used to implement AI05-0212 which recategorizes some
12714          --  run-time packages in Ada 2012 mode.
12715
12716          when Pragma_Pure_12 => Pure_12 : declare
12717             Ent : Entity_Id;
12718
12719          begin
12720             GNAT_Pragma;
12721             Check_Valid_Library_Unit_Pragma;
12722
12723             if not GNAT_Mode then
12724                Error_Pragma ("pragma% only available in GNAT mode");
12725             end if;
12726
12727             if Nkind (N) = N_Null_Statement then
12728                return;
12729             end if;
12730
12731             --  This is one of the few cases where we need to test the value of
12732             --  Ada_Version_Explicit rather than Ada_Version (which is always
12733             --  set to Ada_2012 in a predefined unit), we need to know the
12734             --  explicit version set to know if this pragma is active.
12735
12736             if Ada_Version_Explicit >= Ada_2012 then
12737                Ent := Find_Lib_Unit_Name;
12738                Set_Is_Preelaborated (Ent, False);
12739                Set_Is_Pure (Ent);
12740                Set_Suppress_Elaboration_Warnings (Ent);
12741             end if;
12742          end Pure_12;
12743
12744          -------------------
12745          -- Pure_Function --
12746          -------------------
12747
12748          --  pragma Pure_Function ([Entity =>] function_LOCAL_NAME);
12749
12750          when Pragma_Pure_Function => Pure_Function : declare
12751             E_Id      : Node_Id;
12752             E         : Entity_Id;
12753             Def_Id    : Entity_Id;
12754             Effective : Boolean := False;
12755
12756          begin
12757             GNAT_Pragma;
12758             Check_Arg_Count (1);
12759             Check_Optional_Identifier (Arg1, Name_Entity);
12760             Check_Arg_Is_Local_Name (Arg1);
12761             E_Id := Get_Pragma_Arg (Arg1);
12762
12763             if Error_Posted (E_Id) then
12764                return;
12765             end if;
12766
12767             --  Loop through homonyms (overloadings) of referenced entity
12768
12769             E := Entity (E_Id);
12770
12771             if Present (E) then
12772                loop
12773                   Def_Id := Get_Base_Subprogram (E);
12774
12775                   if not Ekind_In (Def_Id, E_Function,
12776                                            E_Generic_Function,
12777                                            E_Operator)
12778                   then
12779                      Error_Pragma_Arg
12780                        ("pragma% requires a function name", Arg1);
12781                   end if;
12782
12783                   Set_Is_Pure (Def_Id);
12784
12785                   if not Has_Pragma_Pure_Function (Def_Id) then
12786                      Set_Has_Pragma_Pure_Function (Def_Id);
12787                      Effective := True;
12788                   end if;
12789
12790                   exit when From_Aspect_Specification (N);
12791                   E := Homonym (E);
12792                   exit when No (E) or else Scope (E) /= Current_Scope;
12793                end loop;
12794
12795                if not Effective
12796                  and then Warn_On_Redundant_Constructs
12797                then
12798                   Error_Msg_NE
12799                     ("pragma Pure_Function on& is redundant?",
12800                      N, Entity (E_Id));
12801                end if;
12802             end if;
12803          end Pure_Function;
12804
12805          --------------------
12806          -- Queuing_Policy --
12807          --------------------
12808
12809          --  pragma Queuing_Policy (policy_IDENTIFIER);
12810
12811          when Pragma_Queuing_Policy => declare
12812             QP : Character;
12813
12814          begin
12815             Check_Ada_83_Warning;
12816             Check_Arg_Count (1);
12817             Check_No_Identifiers;
12818             Check_Arg_Is_Queuing_Policy (Arg1);
12819             Check_Valid_Configuration_Pragma;
12820             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
12821             QP := Fold_Upper (Name_Buffer (1));
12822
12823             if Queuing_Policy /= ' '
12824               and then Queuing_Policy /= QP
12825             then
12826                Error_Msg_Sloc := Queuing_Policy_Sloc;
12827                Error_Pragma ("queuing policy incompatible with policy#");
12828
12829             --  Set new policy, but always preserve System_Location since we
12830             --  like the error message with the run time name.
12831
12832             else
12833                Queuing_Policy := QP;
12834
12835                if Queuing_Policy_Sloc /= System_Location then
12836                   Queuing_Policy_Sloc := Loc;
12837                end if;
12838             end if;
12839          end;
12840
12841          -----------------------
12842          -- Relative_Deadline --
12843          -----------------------
12844
12845          --  pragma Relative_Deadline (time_span_EXPRESSION);
12846
12847          when Pragma_Relative_Deadline => Relative_Deadline : declare
12848             P   : constant Node_Id := Parent (N);
12849             Arg : Node_Id;
12850
12851          begin
12852             Ada_2005_Pragma;
12853             Check_No_Identifiers;
12854             Check_Arg_Count (1);
12855
12856             Arg := Get_Pragma_Arg (Arg1);
12857
12858             --  The expression must be analyzed in the special manner described
12859             --  in "Handling of Default and Per-Object Expressions" in sem.ads.
12860
12861             Preanalyze_Spec_Expression (Arg, RTE (RE_Time_Span));
12862
12863             --  Subprogram case
12864
12865             if Nkind (P) = N_Subprogram_Body then
12866                Check_In_Main_Program;
12867
12868             --  Tasks
12869
12870             elsif Nkind (P) = N_Task_Definition then
12871                null;
12872
12873             --  Anything else is incorrect
12874
12875             else
12876                Pragma_Misplaced;
12877             end if;
12878
12879             if Has_Relative_Deadline_Pragma (P) then
12880                Error_Pragma ("duplicate pragma% not allowed");
12881             else
12882                Set_Has_Relative_Deadline_Pragma (P, True);
12883
12884                if Nkind (P) = N_Task_Definition then
12885                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
12886                end if;
12887             end if;
12888          end Relative_Deadline;
12889
12890          ---------------------------
12891          -- Remote_Call_Interface --
12892          ---------------------------
12893
12894          --  pragma Remote_Call_Interface [(library_unit_NAME)];
12895
12896          when Pragma_Remote_Call_Interface => Remote_Call_Interface : declare
12897             Cunit_Node : Node_Id;
12898             Cunit_Ent  : Entity_Id;
12899             K          : Node_Kind;
12900
12901          begin
12902             Check_Ada_83_Warning;
12903             Check_Valid_Library_Unit_Pragma;
12904
12905             if Nkind (N) = N_Null_Statement then
12906                return;
12907             end if;
12908
12909             Cunit_Node := Cunit (Current_Sem_Unit);
12910             K          := Nkind (Unit (Cunit_Node));
12911             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12912
12913             if K = N_Package_Declaration
12914               or else K = N_Generic_Package_Declaration
12915               or else K = N_Subprogram_Declaration
12916               or else K = N_Generic_Subprogram_Declaration
12917               or else (K = N_Subprogram_Body
12918                          and then Acts_As_Spec (Unit (Cunit_Node)))
12919             then
12920                null;
12921             else
12922                Error_Pragma (
12923                  "pragma% must apply to package or subprogram declaration");
12924             end if;
12925
12926             Set_Is_Remote_Call_Interface (Cunit_Ent);
12927          end Remote_Call_Interface;
12928
12929          ------------------
12930          -- Remote_Types --
12931          ------------------
12932
12933          --  pragma Remote_Types [(library_unit_NAME)];
12934
12935          when Pragma_Remote_Types => Remote_Types : declare
12936             Cunit_Node : Node_Id;
12937             Cunit_Ent  : Entity_Id;
12938
12939          begin
12940             Check_Ada_83_Warning;
12941             Check_Valid_Library_Unit_Pragma;
12942
12943             if Nkind (N) = N_Null_Statement then
12944                return;
12945             end if;
12946
12947             Cunit_Node := Cunit (Current_Sem_Unit);
12948             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12949
12950             if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
12951                                                 N_Generic_Package_Declaration)
12952             then
12953                Error_Pragma
12954                  ("pragma% can only apply to a package declaration");
12955             end if;
12956
12957             Set_Is_Remote_Types (Cunit_Ent);
12958          end Remote_Types;
12959
12960          ---------------
12961          -- Ravenscar --
12962          ---------------
12963
12964          --  pragma Ravenscar;
12965
12966          when Pragma_Ravenscar =>
12967             GNAT_Pragma;
12968             Check_Arg_Count (0);
12969             Check_Valid_Configuration_Pragma;
12970             Set_Ravenscar_Profile (N);
12971
12972             if Warn_On_Obsolescent_Feature then
12973                Error_Msg_N ("pragma Ravenscar is an obsolescent feature?", N);
12974                Error_Msg_N ("|use pragma Profile (Ravenscar) instead", N);
12975             end if;
12976
12977          -------------------------
12978          -- Restricted_Run_Time --
12979          -------------------------
12980
12981          --  pragma Restricted_Run_Time;
12982
12983          when Pragma_Restricted_Run_Time =>
12984             GNAT_Pragma;
12985             Check_Arg_Count (0);
12986             Check_Valid_Configuration_Pragma;
12987             Set_Profile_Restrictions
12988               (Restricted, N, Warn => Treat_Restrictions_As_Warnings);
12989
12990             if Warn_On_Obsolescent_Feature then
12991                Error_Msg_N
12992                  ("pragma Restricted_Run_Time is an obsolescent feature?", N);
12993                Error_Msg_N ("|use pragma Profile (Restricted) instead", N);
12994             end if;
12995
12996          ------------------
12997          -- Restrictions --
12998          ------------------
12999
13000          --  pragma Restrictions (RESTRICTION {, RESTRICTION});
13001
13002          --  RESTRICTION ::=
13003          --    restriction_IDENTIFIER
13004          --  | restriction_parameter_IDENTIFIER => EXPRESSION
13005
13006          when Pragma_Restrictions =>
13007             Process_Restrictions_Or_Restriction_Warnings
13008               (Warn => Treat_Restrictions_As_Warnings);
13009
13010          --------------------------
13011          -- Restriction_Warnings --
13012          --------------------------
13013
13014          --  pragma Restriction_Warnings (RESTRICTION {, RESTRICTION});
13015
13016          --  RESTRICTION ::=
13017          --    restriction_IDENTIFIER
13018          --  | restriction_parameter_IDENTIFIER => EXPRESSION
13019
13020          when Pragma_Restriction_Warnings =>
13021             GNAT_Pragma;
13022             Process_Restrictions_Or_Restriction_Warnings (Warn => True);
13023
13024          ----------------
13025          -- Reviewable --
13026          ----------------
13027
13028          --  pragma Reviewable;
13029
13030          when Pragma_Reviewable =>
13031             Check_Ada_83_Warning;
13032             Check_Arg_Count (0);
13033
13034             --  Call dummy debugging function rv. This is done to assist front
13035             --  end debugging. By placing a Reviewable pragma in the source
13036             --  program, a breakpoint on rv catches this place in the source,
13037             --  allowing convenient stepping to the point of interest.
13038
13039             rv;
13040
13041          --------------------------
13042          -- Short_Circuit_And_Or --
13043          --------------------------
13044
13045          when Pragma_Short_Circuit_And_Or =>
13046             GNAT_Pragma;
13047             Check_Arg_Count (0);
13048             Check_Valid_Configuration_Pragma;
13049             Short_Circuit_And_Or := True;
13050
13051          -------------------
13052          -- Share_Generic --
13053          -------------------
13054
13055          --  pragma Share_Generic (NAME {, NAME});
13056
13057          when Pragma_Share_Generic =>
13058             GNAT_Pragma;
13059             Process_Generic_List;
13060
13061          ------------
13062          -- Shared --
13063          ------------
13064
13065          --  pragma Shared (LOCAL_NAME);
13066
13067          when Pragma_Shared =>
13068             GNAT_Pragma;
13069             Process_Atomic_Shared_Volatile;
13070
13071          --------------------
13072          -- Shared_Passive --
13073          --------------------
13074
13075          --  pragma Shared_Passive [(library_unit_NAME)];
13076
13077          --  Set the flag Is_Shared_Passive of program unit name entity
13078
13079          when Pragma_Shared_Passive => Shared_Passive : declare
13080             Cunit_Node : Node_Id;
13081             Cunit_Ent  : Entity_Id;
13082
13083          begin
13084             Check_Ada_83_Warning;
13085             Check_Valid_Library_Unit_Pragma;
13086
13087             if Nkind (N) = N_Null_Statement then
13088                return;
13089             end if;
13090
13091             Cunit_Node := Cunit (Current_Sem_Unit);
13092             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
13093
13094             if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
13095                                                 N_Generic_Package_Declaration)
13096             then
13097                Error_Pragma
13098                  ("pragma% can only apply to a package declaration");
13099             end if;
13100
13101             Set_Is_Shared_Passive (Cunit_Ent);
13102          end Shared_Passive;
13103
13104          -----------------------
13105          -- Short_Descriptors --
13106          -----------------------
13107
13108          --  pragma Short_Descriptors;
13109
13110          when Pragma_Short_Descriptors =>
13111             GNAT_Pragma;
13112             Check_Arg_Count (0);
13113             Check_Valid_Configuration_Pragma;
13114             Short_Descriptors := True;
13115
13116          ----------------------
13117          -- Source_File_Name --
13118          ----------------------
13119
13120          --  There are five forms for this pragma:
13121
13122          --  pragma Source_File_Name (
13123          --    [UNIT_NAME      =>] unit_NAME,
13124          --     BODY_FILE_NAME =>  STRING_LITERAL
13125          --    [, [INDEX =>] INTEGER_LITERAL]);
13126
13127          --  pragma Source_File_Name (
13128          --    [UNIT_NAME      =>] unit_NAME,
13129          --     SPEC_FILE_NAME =>  STRING_LITERAL
13130          --    [, [INDEX =>] INTEGER_LITERAL]);
13131
13132          --  pragma Source_File_Name (
13133          --     BODY_FILE_NAME  => STRING_LITERAL
13134          --  [, DOT_REPLACEMENT => STRING_LITERAL]
13135          --  [, CASING          => CASING_SPEC]);
13136
13137          --  pragma Source_File_Name (
13138          --     SPEC_FILE_NAME  => STRING_LITERAL
13139          --  [, DOT_REPLACEMENT => STRING_LITERAL]
13140          --  [, CASING          => CASING_SPEC]);
13141
13142          --  pragma Source_File_Name (
13143          --     SUBUNIT_FILE_NAME  => STRING_LITERAL
13144          --  [, DOT_REPLACEMENT    => STRING_LITERAL]
13145          --  [, CASING             => CASING_SPEC]);
13146
13147          --  CASING_SPEC ::= Uppercase | Lowercase | Mixedcase
13148
13149          --  Pragma Source_File_Name_Project (SFNP) is equivalent to pragma
13150          --  Source_File_Name (SFN), however their usage is exclusive: SFN can
13151          --  only be used when no project file is used, while SFNP can only be
13152          --  used when a project file is used.
13153
13154          --  No processing here. Processing was completed during parsing, since
13155          --  we need to have file names set as early as possible. Units are
13156          --  loaded well before semantic processing starts.
13157
13158          --  The only processing we defer to this point is the check for
13159          --  correct placement.
13160
13161          when Pragma_Source_File_Name =>
13162             GNAT_Pragma;
13163             Check_Valid_Configuration_Pragma;
13164
13165          ------------------------------
13166          -- Source_File_Name_Project --
13167          ------------------------------
13168
13169          --  See Source_File_Name for syntax
13170
13171          --  No processing here. Processing was completed during parsing, since
13172          --  we need to have file names set as early as possible. Units are
13173          --  loaded well before semantic processing starts.
13174
13175          --  The only processing we defer to this point is the check for
13176          --  correct placement.
13177
13178          when Pragma_Source_File_Name_Project =>
13179             GNAT_Pragma;
13180             Check_Valid_Configuration_Pragma;
13181
13182             --  Check that a pragma Source_File_Name_Project is used only in a
13183             --  configuration pragmas file.
13184
13185             --  Pragmas Source_File_Name_Project should only be generated by
13186             --  the Project Manager in configuration pragmas files.
13187
13188             --  This is really an ugly test. It seems to depend on some
13189             --  accidental and undocumented property. At the very least it
13190             --  needs to be documented, but it would be better to have a
13191             --  clean way of testing if we are in a configuration file???
13192
13193             if Present (Parent (N)) then
13194                Error_Pragma
13195                  ("pragma% can only appear in a configuration pragmas file");
13196             end if;
13197
13198          ----------------------
13199          -- Source_Reference --
13200          ----------------------
13201
13202          --  pragma Source_Reference (INTEGER_LITERAL [, STRING_LITERAL]);
13203
13204          --  Nothing to do, all processing completed in Par.Prag, since we need
13205          --  the information for possible parser messages that are output.
13206
13207          when Pragma_Source_Reference =>
13208             GNAT_Pragma;
13209
13210          --------------------------------
13211          -- Static_Elaboration_Desired --
13212          --------------------------------
13213
13214          --  pragma Static_Elaboration_Desired (DIRECT_NAME);
13215
13216          when Pragma_Static_Elaboration_Desired =>
13217             GNAT_Pragma;
13218             Check_At_Most_N_Arguments (1);
13219
13220             if Is_Compilation_Unit (Current_Scope)
13221               and then Ekind (Current_Scope) = E_Package
13222             then
13223                Set_Static_Elaboration_Desired (Current_Scope, True);
13224             else
13225                Error_Pragma ("pragma% must apply to a library-level package");
13226             end if;
13227
13228          ------------------
13229          -- Storage_Size --
13230          ------------------
13231
13232          --  pragma Storage_Size (EXPRESSION);
13233
13234          when Pragma_Storage_Size => Storage_Size : declare
13235             P   : constant Node_Id := Parent (N);
13236             Arg : Node_Id;
13237
13238          begin
13239             Check_No_Identifiers;
13240             Check_Arg_Count (1);
13241
13242             --  The expression must be analyzed in the special manner described
13243             --  in "Handling of Default Expressions" in sem.ads.
13244
13245             Arg := Get_Pragma_Arg (Arg1);
13246             Preanalyze_Spec_Expression (Arg, Any_Integer);
13247
13248             if not Is_Static_Expression (Arg) then
13249                Check_Restriction (Static_Storage_Size, Arg);
13250             end if;
13251
13252             if Nkind (P) /= N_Task_Definition then
13253                Pragma_Misplaced;
13254                return;
13255
13256             else
13257                if Has_Storage_Size_Pragma (P) then
13258                   Error_Pragma ("duplicate pragma% not allowed");
13259                else
13260                   Set_Has_Storage_Size_Pragma (P, True);
13261                end if;
13262
13263                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
13264                --  ???  exp_ch9 should use this!
13265             end if;
13266          end Storage_Size;
13267
13268          ------------------
13269          -- Storage_Unit --
13270          ------------------
13271
13272          --  pragma Storage_Unit (NUMERIC_LITERAL);
13273
13274          --  Only permitted argument is System'Storage_Unit value
13275
13276          when Pragma_Storage_Unit =>
13277             Check_No_Identifiers;
13278             Check_Arg_Count (1);
13279             Check_Arg_Is_Integer_Literal (Arg1);
13280
13281             if Intval (Get_Pragma_Arg (Arg1)) /=
13282               UI_From_Int (Ttypes.System_Storage_Unit)
13283             then
13284                Error_Msg_Uint_1 := UI_From_Int (Ttypes.System_Storage_Unit);
13285                Error_Pragma_Arg
13286                  ("the only allowed argument for pragma% is ^", Arg1);
13287             end if;
13288
13289          --------------------
13290          -- Stream_Convert --
13291          --------------------
13292
13293          --  pragma Stream_Convert (
13294          --    [Entity =>] type_LOCAL_NAME,
13295          --    [Read   =>] function_NAME,
13296          --    [Write  =>] function NAME);
13297
13298          when Pragma_Stream_Convert => Stream_Convert : declare
13299
13300             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id);
13301             --  Check that the given argument is the name of a local function
13302             --  of one argument that is not overloaded earlier in the current
13303             --  local scope. A check is also made that the argument is a
13304             --  function with one parameter.
13305
13306             --------------------------------------
13307             -- Check_OK_Stream_Convert_Function --
13308             --------------------------------------
13309
13310             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id) is
13311                Ent : Entity_Id;
13312
13313             begin
13314                Check_Arg_Is_Local_Name (Arg);
13315                Ent := Entity (Get_Pragma_Arg (Arg));
13316
13317                if Has_Homonym (Ent) then
13318                   Error_Pragma_Arg
13319                     ("argument for pragma% may not be overloaded", Arg);
13320                end if;
13321
13322                if Ekind (Ent) /= E_Function
13323                  or else No (First_Formal (Ent))
13324                  or else Present (Next_Formal (First_Formal (Ent)))
13325                then
13326                   Error_Pragma_Arg
13327                     ("argument for pragma% must be" &
13328                      " function of one argument", Arg);
13329                end if;
13330             end Check_OK_Stream_Convert_Function;
13331
13332          --  Start of processing for Stream_Convert
13333
13334          begin
13335             GNAT_Pragma;
13336             Check_Arg_Order ((Name_Entity, Name_Read, Name_Write));
13337             Check_Arg_Count (3);
13338             Check_Optional_Identifier (Arg1, Name_Entity);
13339             Check_Optional_Identifier (Arg2, Name_Read);
13340             Check_Optional_Identifier (Arg3, Name_Write);
13341             Check_Arg_Is_Local_Name (Arg1);
13342             Check_OK_Stream_Convert_Function (Arg2);
13343             Check_OK_Stream_Convert_Function (Arg3);
13344
13345             declare
13346                Typ   : constant Entity_Id :=
13347                          Underlying_Type (Entity (Get_Pragma_Arg (Arg1)));
13348                Read  : constant Entity_Id := Entity (Get_Pragma_Arg (Arg2));
13349                Write : constant Entity_Id := Entity (Get_Pragma_Arg (Arg3));
13350
13351             begin
13352                Check_First_Subtype (Arg1);
13353
13354                --  Check for too early or too late. Note that we don't enforce
13355                --  the rule about primitive operations in this case, since, as
13356                --  is the case for explicit stream attributes themselves, these
13357                --  restrictions are not appropriate. Note that the chaining of
13358                --  the pragma by Rep_Item_Too_Late is actually the critical
13359                --  processing done for this pragma.
13360
13361                if Rep_Item_Too_Early (Typ, N)
13362                     or else
13363                   Rep_Item_Too_Late (Typ, N, FOnly => True)
13364                then
13365                   return;
13366                end if;
13367
13368                --  Return if previous error
13369
13370                if Etype (Typ) = Any_Type
13371                     or else
13372                   Etype (Read) = Any_Type
13373                     or else
13374                   Etype (Write) = Any_Type
13375                then
13376                   return;
13377                end if;
13378
13379                --  Error checks
13380
13381                if Underlying_Type (Etype (Read)) /= Typ then
13382                   Error_Pragma_Arg
13383                     ("incorrect return type for function&", Arg2);
13384                end if;
13385
13386                if Underlying_Type (Etype (First_Formal (Write))) /= Typ then
13387                   Error_Pragma_Arg
13388                     ("incorrect parameter type for function&", Arg3);
13389                end if;
13390
13391                if Underlying_Type (Etype (First_Formal (Read))) /=
13392                   Underlying_Type (Etype (Write))
13393                then
13394                   Error_Pragma_Arg
13395                     ("result type of & does not match Read parameter type",
13396                      Arg3);
13397                end if;
13398             end;
13399          end Stream_Convert;
13400
13401          -------------------------
13402          -- Style_Checks (GNAT) --
13403          -------------------------
13404
13405          --  pragma Style_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
13406
13407          --  This is processed by the parser since some of the style checks
13408          --  take place during source scanning and parsing. This means that
13409          --  we don't need to issue error messages here.
13410
13411          when Pragma_Style_Checks => Style_Checks : declare
13412             A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
13413             S  : String_Id;
13414             C  : Char_Code;
13415
13416          begin
13417             GNAT_Pragma;
13418             Check_No_Identifiers;
13419
13420             --  Two argument form
13421
13422             if Arg_Count = 2 then
13423                Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
13424
13425                declare
13426                   E_Id : Node_Id;
13427                   E    : Entity_Id;
13428
13429                begin
13430                   E_Id := Get_Pragma_Arg (Arg2);
13431                   Analyze (E_Id);
13432
13433                   if not Is_Entity_Name (E_Id) then
13434                      Error_Pragma_Arg
13435                        ("second argument of pragma% must be entity name",
13436                         Arg2);
13437                   end if;
13438
13439                   E := Entity (E_Id);
13440
13441                   if E = Any_Id then
13442                      return;
13443                   else
13444                      loop
13445                         Set_Suppress_Style_Checks (E,
13446                           (Chars (Get_Pragma_Arg (Arg1)) = Name_Off));
13447                         exit when No (Homonym (E));
13448                         E := Homonym (E);
13449                      end loop;
13450                   end if;
13451                end;
13452
13453             --  One argument form
13454
13455             else
13456                Check_Arg_Count (1);
13457
13458                if Nkind (A) = N_String_Literal then
13459                   S   := Strval (A);
13460
13461                   declare
13462                      Slen    : constant Natural := Natural (String_Length (S));
13463                      Options : String (1 .. Slen);
13464                      J       : Natural;
13465
13466                   begin
13467                      J := 1;
13468                      loop
13469                         C := Get_String_Char (S, Int (J));
13470                         exit when not In_Character_Range (C);
13471                         Options (J) := Get_Character (C);
13472
13473                         --  If at end of string, set options. As per discussion
13474                         --  above, no need to check for errors, since we issued
13475                         --  them in the parser.
13476
13477                         if J = Slen then
13478                            Set_Style_Check_Options (Options);
13479                            exit;
13480                         end if;
13481
13482                         J := J + 1;
13483                      end loop;
13484                   end;
13485
13486                elsif Nkind (A) = N_Identifier then
13487                   if Chars (A) = Name_All_Checks then
13488                      if GNAT_Mode then
13489                         Set_GNAT_Style_Check_Options;
13490                      else
13491                         Set_Default_Style_Check_Options;
13492                      end if;
13493
13494                   elsif Chars (A) = Name_On then
13495                      Style_Check := True;
13496
13497                   elsif Chars (A) = Name_Off then
13498                      Style_Check := False;
13499                   end if;
13500                end if;
13501             end if;
13502          end Style_Checks;
13503
13504          --------------
13505          -- Subtitle --
13506          --------------
13507
13508          --  pragma Subtitle ([Subtitle =>] STRING_LITERAL);
13509
13510          when Pragma_Subtitle =>
13511             GNAT_Pragma;
13512             Check_Arg_Count (1);
13513             Check_Optional_Identifier (Arg1, Name_Subtitle);
13514             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
13515             Store_Note (N);
13516
13517          --------------
13518          -- Suppress --
13519          --------------
13520
13521          --  pragma Suppress (IDENTIFIER [, [On =>] NAME]);
13522
13523          when Pragma_Suppress =>
13524             Process_Suppress_Unsuppress (True);
13525
13526          ------------------
13527          -- Suppress_All --
13528          ------------------
13529
13530          --  pragma Suppress_All;
13531
13532          --  The only check made here is that the pragma has no arguments.
13533          --  There are no placement rules, and the processing required (setting
13534          --  the Has_Pragma_Suppress_All flag in the compilation unit node was
13535          --  taken care of by the parser). Process_Compilation_Unit_Pragmas
13536          --  then creates and inserts a pragma Suppress (All_Checks).
13537
13538          when Pragma_Suppress_All =>
13539             GNAT_Pragma;
13540             Check_Arg_Count (0);
13541
13542          -------------------------
13543          -- Suppress_Debug_Info --
13544          -------------------------
13545
13546          --  pragma Suppress_Debug_Info ([Entity =>] LOCAL_NAME);
13547
13548          when Pragma_Suppress_Debug_Info =>
13549             GNAT_Pragma;
13550             Check_Arg_Count (1);
13551             Check_Optional_Identifier (Arg1, Name_Entity);
13552             Check_Arg_Is_Local_Name (Arg1);
13553             Set_Debug_Info_Off (Entity (Get_Pragma_Arg (Arg1)));
13554
13555          ----------------------------------
13556          -- Suppress_Exception_Locations --
13557          ----------------------------------
13558
13559          --  pragma Suppress_Exception_Locations;
13560
13561          when Pragma_Suppress_Exception_Locations =>
13562             GNAT_Pragma;
13563             Check_Arg_Count (0);
13564             Check_Valid_Configuration_Pragma;
13565             Exception_Locations_Suppressed := True;
13566
13567          -----------------------------
13568          -- Suppress_Initialization --
13569          -----------------------------
13570
13571          --  pragma Suppress_Initialization ([Entity =>] type_Name);
13572
13573          when Pragma_Suppress_Initialization => Suppress_Init : declare
13574             E_Id : Node_Id;
13575             E    : Entity_Id;
13576
13577          begin
13578             GNAT_Pragma;
13579             Check_Arg_Count (1);
13580             Check_Optional_Identifier (Arg1, Name_Entity);
13581             Check_Arg_Is_Local_Name (Arg1);
13582
13583             E_Id := Get_Pragma_Arg (Arg1);
13584
13585             if Etype (E_Id) = Any_Type then
13586                return;
13587             end if;
13588
13589             E := Entity (E_Id);
13590
13591             if not Is_Type (E) then
13592                Error_Pragma_Arg ("pragma% requires type or subtype", Arg1);
13593             end if;
13594
13595             if Rep_Item_Too_Early (E, N)
13596                  or else
13597                Rep_Item_Too_Late (E, N, FOnly => True)
13598             then
13599                return;
13600             end if;
13601
13602             --  For incomplete/private type, set flag on full view
13603
13604             if Is_Incomplete_Or_Private_Type (E) then
13605                if No (Full_View (Base_Type (E))) then
13606                   Error_Pragma_Arg
13607                     ("argument of pragma% cannot be an incomplete type", Arg1);
13608                else
13609                   Set_Suppress_Initialization (Full_View (Base_Type (E)));
13610                end if;
13611
13612             --  For first subtype, set flag on base type
13613
13614             elsif Is_First_Subtype (E) then
13615                Set_Suppress_Initialization (Base_Type (E));
13616
13617             --  For other than first subtype, set flag on subtype itself
13618
13619             else
13620                Set_Suppress_Initialization (E);
13621             end if;
13622          end Suppress_Init;
13623
13624          -----------------
13625          -- System_Name --
13626          -----------------
13627
13628          --  pragma System_Name (DIRECT_NAME);
13629
13630          --  Syntax check: one argument, which must be the identifier GNAT or
13631          --  the identifier GCC, no other identifiers are acceptable.
13632
13633          when Pragma_System_Name =>
13634             GNAT_Pragma;
13635             Check_No_Identifiers;
13636             Check_Arg_Count (1);
13637             Check_Arg_Is_One_Of (Arg1, Name_Gcc, Name_Gnat);
13638
13639          -----------------------------
13640          -- Task_Dispatching_Policy --
13641          -----------------------------
13642
13643          --  pragma Task_Dispatching_Policy (policy_IDENTIFIER);
13644
13645          when Pragma_Task_Dispatching_Policy => declare
13646             DP : Character;
13647
13648          begin
13649             Check_Ada_83_Warning;
13650             Check_Arg_Count (1);
13651             Check_No_Identifiers;
13652             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
13653             Check_Valid_Configuration_Pragma;
13654             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
13655             DP := Fold_Upper (Name_Buffer (1));
13656
13657             if Task_Dispatching_Policy /= ' '
13658               and then Task_Dispatching_Policy /= DP
13659             then
13660                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
13661                Error_Pragma
13662                  ("task dispatching policy incompatible with policy#");
13663
13664             --  Set new policy, but always preserve System_Location since we
13665             --  like the error message with the run time name.
13666
13667             else
13668                Task_Dispatching_Policy := DP;
13669
13670                if Task_Dispatching_Policy_Sloc /= System_Location then
13671                   Task_Dispatching_Policy_Sloc := Loc;
13672                end if;
13673             end if;
13674          end;
13675
13676          ---------------
13677          -- Task_Info --
13678          ---------------
13679
13680          --  pragma Task_Info (EXPRESSION);
13681
13682          when Pragma_Task_Info => Task_Info : declare
13683             P : constant Node_Id := Parent (N);
13684
13685          begin
13686             GNAT_Pragma;
13687
13688             if Nkind (P) /= N_Task_Definition then
13689                Error_Pragma ("pragma% must appear in task definition");
13690             end if;
13691
13692             Check_No_Identifiers;
13693             Check_Arg_Count (1);
13694
13695             Analyze_And_Resolve
13696               (Get_Pragma_Arg (Arg1), RTE (RE_Task_Info_Type));
13697
13698             if Etype (Get_Pragma_Arg (Arg1)) = Any_Type then
13699                return;
13700             end if;
13701
13702             if Has_Task_Info_Pragma (P) then
13703                Error_Pragma ("duplicate pragma% not allowed");
13704             else
13705                Set_Has_Task_Info_Pragma (P, True);
13706             end if;
13707          end Task_Info;
13708
13709          ---------------
13710          -- Task_Name --
13711          ---------------
13712
13713          --  pragma Task_Name (string_EXPRESSION);
13714
13715          when Pragma_Task_Name => Task_Name : declare
13716             P   : constant Node_Id := Parent (N);
13717             Arg : Node_Id;
13718
13719          begin
13720             Check_No_Identifiers;
13721             Check_Arg_Count (1);
13722
13723             Arg := Get_Pragma_Arg (Arg1);
13724
13725             --  The expression is used in the call to Create_Task, and must be
13726             --  expanded there, not in the context of the current spec. It must
13727             --  however be analyzed to capture global references, in case it
13728             --  appears in a generic context.
13729
13730             Preanalyze_And_Resolve (Arg, Standard_String);
13731
13732             if Nkind (P) /= N_Task_Definition then
13733                Pragma_Misplaced;
13734             end if;
13735
13736             if Has_Task_Name_Pragma (P) then
13737                Error_Pragma ("duplicate pragma% not allowed");
13738             else
13739                Set_Has_Task_Name_Pragma (P, True);
13740                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
13741             end if;
13742          end Task_Name;
13743
13744          ------------------
13745          -- Task_Storage --
13746          ------------------
13747
13748          --  pragma Task_Storage (
13749          --     [Task_Type =>] LOCAL_NAME,
13750          --     [Top_Guard =>] static_integer_EXPRESSION);
13751
13752          when Pragma_Task_Storage => Task_Storage : declare
13753             Args  : Args_List (1 .. 2);
13754             Names : constant Name_List (1 .. 2) := (
13755                       Name_Task_Type,
13756                       Name_Top_Guard);
13757
13758             Task_Type : Node_Id renames Args (1);
13759             Top_Guard : Node_Id renames Args (2);
13760
13761             Ent : Entity_Id;
13762
13763          begin
13764             GNAT_Pragma;
13765             Gather_Associations (Names, Args);
13766
13767             if No (Task_Type) then
13768                Error_Pragma
13769                  ("missing task_type argument for pragma%");
13770             end if;
13771
13772             Check_Arg_Is_Local_Name (Task_Type);
13773
13774             Ent := Entity (Task_Type);
13775
13776             if not Is_Task_Type (Ent) then
13777                Error_Pragma_Arg
13778                  ("argument for pragma% must be task type", Task_Type);
13779             end if;
13780
13781             if No (Top_Guard) then
13782                Error_Pragma_Arg
13783                  ("pragma% takes two arguments", Task_Type);
13784             else
13785                Check_Arg_Is_Static_Expression (Top_Guard, Any_Integer);
13786             end if;
13787
13788             Check_First_Subtype (Task_Type);
13789
13790             if Rep_Item_Too_Late (Ent, N) then
13791                raise Pragma_Exit;
13792             end if;
13793          end Task_Storage;
13794
13795          ---------------
13796          -- Test_Case --
13797          ---------------
13798
13799          --  pragma Test_Case ([Name     =>] Static_String_EXPRESSION
13800          --                   ,[Mode     =>] MODE_TYPE
13801          --                  [, Requires =>  Boolean_EXPRESSION]
13802          --                  [, Ensures  =>  Boolean_EXPRESSION]);
13803
13804          --  MODE_TYPE ::= Nominal | Robustness
13805
13806          when Pragma_Test_Case => Test_Case : declare
13807          begin
13808             GNAT_Pragma;
13809             Check_At_Least_N_Arguments (2);
13810             Check_At_Most_N_Arguments (4);
13811             Check_Arg_Order
13812                  ((Name_Name, Name_Mode, Name_Requires, Name_Ensures));
13813
13814             Check_Optional_Identifier (Arg1, Name_Name);
13815             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
13816
13817             --  In ASIS mode, for a pragma generated from a source aspect, also
13818             --  analyze the original aspect expression.
13819
13820             if ASIS_Mode
13821               and then Present (Corresponding_Aspect (N))
13822             then
13823                Check_Expr_Is_Static_Expression
13824                  (Original_Node (Get_Pragma_Arg (Arg1)), Standard_String);
13825             end if;
13826
13827             Check_Optional_Identifier (Arg2, Name_Mode);
13828             Check_Arg_Is_One_Of (Arg2, Name_Nominal, Name_Robustness);
13829
13830             if Arg_Count = 4 then
13831                Check_Identifier (Arg3, Name_Requires);
13832                Check_Identifier (Arg4, Name_Ensures);
13833
13834             elsif Arg_Count = 3 then
13835                Check_Identifier_Is_One_Of (Arg3, Name_Requires, Name_Ensures);
13836             end if;
13837
13838             Check_Test_Case;
13839          end Test_Case;
13840
13841          --------------------------
13842          -- Thread_Local_Storage --
13843          --------------------------
13844
13845          --  pragma Thread_Local_Storage ([Entity =>] LOCAL_NAME);
13846
13847          when Pragma_Thread_Local_Storage => Thread_Local_Storage : declare
13848             Id : Node_Id;
13849             E  : Entity_Id;
13850
13851          begin
13852             GNAT_Pragma;
13853             Check_Arg_Count (1);
13854             Check_Optional_Identifier (Arg1, Name_Entity);
13855             Check_Arg_Is_Library_Level_Local_Name (Arg1);
13856
13857             Id := Get_Pragma_Arg (Arg1);
13858             Analyze (Id);
13859
13860             if not Is_Entity_Name (Id)
13861               or else Ekind (Entity (Id)) /= E_Variable
13862             then
13863                Error_Pragma_Arg ("local variable name required", Arg1);
13864             end if;
13865
13866             E := Entity (Id);
13867
13868             if Rep_Item_Too_Early (E, N)
13869               or else Rep_Item_Too_Late (E, N)
13870             then
13871                raise Pragma_Exit;
13872             end if;
13873
13874             Set_Has_Pragma_Thread_Local_Storage (E);
13875             Set_Has_Gigi_Rep_Item (E);
13876          end Thread_Local_Storage;
13877
13878          ----------------
13879          -- Time_Slice --
13880          ----------------
13881
13882          --  pragma Time_Slice (static_duration_EXPRESSION);
13883
13884          when Pragma_Time_Slice => Time_Slice : declare
13885             Val : Ureal;
13886             Nod : Node_Id;
13887
13888          begin
13889             GNAT_Pragma;
13890             Check_Arg_Count (1);
13891             Check_No_Identifiers;
13892             Check_In_Main_Program;
13893             Check_Arg_Is_Static_Expression (Arg1, Standard_Duration);
13894
13895             if not Error_Posted (Arg1) then
13896                Nod := Next (N);
13897                while Present (Nod) loop
13898                   if Nkind (Nod) = N_Pragma
13899                     and then Pragma_Name (Nod) = Name_Time_Slice
13900                   then
13901                      Error_Msg_Name_1 := Pname;
13902                      Error_Msg_N ("duplicate pragma% not permitted", Nod);
13903                   end if;
13904
13905                   Next (Nod);
13906                end loop;
13907             end if;
13908
13909             --  Process only if in main unit
13910
13911             if Get_Source_Unit (Loc) = Main_Unit then
13912                Opt.Time_Slice_Set := True;
13913                Val := Expr_Value_R (Get_Pragma_Arg (Arg1));
13914
13915                if Val <= Ureal_0 then
13916                   Opt.Time_Slice_Value := 0;
13917
13918                elsif Val > UR_From_Uint (UI_From_Int (1000)) then
13919                   Opt.Time_Slice_Value := 1_000_000_000;
13920
13921                else
13922                   Opt.Time_Slice_Value :=
13923                     UI_To_Int (UR_To_Uint (Val * UI_From_Int (1_000_000)));
13924                end if;
13925             end if;
13926          end Time_Slice;
13927
13928          -----------
13929          -- Title --
13930          -----------
13931
13932          --  pragma Title (TITLING_OPTION [, TITLING OPTION]);
13933
13934          --   TITLING_OPTION ::=
13935          --     [Title =>] STRING_LITERAL
13936          --   | [Subtitle =>] STRING_LITERAL
13937
13938          when Pragma_Title => Title : declare
13939             Args  : Args_List (1 .. 2);
13940             Names : constant Name_List (1 .. 2) := (
13941                       Name_Title,
13942                       Name_Subtitle);
13943
13944          begin
13945             GNAT_Pragma;
13946             Gather_Associations (Names, Args);
13947             Store_Note (N);
13948
13949             for J in 1 .. 2 loop
13950                if Present (Args (J)) then
13951                   Check_Arg_Is_Static_Expression (Args (J), Standard_String);
13952                end if;
13953             end loop;
13954          end Title;
13955
13956          ---------------------
13957          -- Unchecked_Union --
13958          ---------------------
13959
13960          --  pragma Unchecked_Union (first_subtype_LOCAL_NAME)
13961
13962          when Pragma_Unchecked_Union => Unchecked_Union : declare
13963             Assoc   : constant Node_Id := Arg1;
13964             Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
13965             Typ     : Entity_Id;
13966             Discr   : Entity_Id;
13967             Tdef    : Node_Id;
13968             Clist   : Node_Id;
13969             Vpart   : Node_Id;
13970             Comp    : Node_Id;
13971             Variant : Node_Id;
13972
13973          begin
13974             Ada_2005_Pragma;
13975             Check_No_Identifiers;
13976             Check_Arg_Count (1);
13977             Check_Arg_Is_Local_Name (Arg1);
13978
13979             Find_Type (Type_Id);
13980             Typ := Entity (Type_Id);
13981
13982             if Typ = Any_Type
13983               or else Rep_Item_Too_Early (Typ, N)
13984             then
13985                return;
13986             else
13987                Typ := Underlying_Type (Typ);
13988             end if;
13989
13990             if Rep_Item_Too_Late (Typ, N) then
13991                return;
13992             end if;
13993
13994             Check_First_Subtype (Arg1);
13995
13996             --  Note remaining cases are references to a type in the current
13997             --  declarative part. If we find an error, we post the error on
13998             --  the relevant type declaration at an appropriate point.
13999
14000             if not Is_Record_Type (Typ) then
14001                Error_Msg_N ("Unchecked_Union must be record type", Typ);
14002                return;
14003
14004             elsif Is_Tagged_Type (Typ) then
14005                Error_Msg_N ("Unchecked_Union must not be tagged", Typ);
14006                return;
14007
14008             elsif not Has_Discriminants (Typ) then
14009                Error_Msg_N
14010                 ("Unchecked_Union must have one discriminant", Typ);
14011                return;
14012
14013             --  Note: in previous versions of GNAT we used to check for limited
14014             --  types and give an error, but in fact the standard does allow
14015             --  Unchecked_Union on limited types, so this check was removed.
14016
14017             --  Proceed with basic error checks completed
14018
14019             else
14020                Discr := First_Discriminant (Typ);
14021                while Present (Discr) loop
14022                   if No (Discriminant_Default_Value (Discr)) then
14023                      Error_Msg_N
14024                        ("Unchecked_Union discriminant must have default value",
14025                         Discr);
14026                   end if;
14027
14028                   Next_Discriminant (Discr);
14029                end loop;
14030
14031                Tdef  := Type_Definition (Declaration_Node (Typ));
14032                Clist := Component_List (Tdef);
14033
14034                Comp := First (Component_Items (Clist));
14035                while Present (Comp) loop
14036                   Check_Component (Comp, Typ);
14037                   Next (Comp);
14038                end loop;
14039
14040                if No (Clist) or else No (Variant_Part (Clist)) then
14041                   Error_Msg_N
14042                     ("Unchecked_Union must have variant part",
14043                      Tdef);
14044                   return;
14045                end if;
14046
14047                Vpart := Variant_Part (Clist);
14048
14049                Variant := First (Variants (Vpart));
14050                while Present (Variant) loop
14051                   Check_Variant (Variant, Typ);
14052                   Next (Variant);
14053                end loop;
14054             end if;
14055
14056             Set_Is_Unchecked_Union  (Typ);
14057             Set_Convention (Typ, Convention_C);
14058             Set_Has_Unchecked_Union (Base_Type (Typ));
14059             Set_Is_Unchecked_Union  (Base_Type (Typ));
14060          end Unchecked_Union;
14061
14062          ------------------------
14063          -- Unimplemented_Unit --
14064          ------------------------
14065
14066          --  pragma Unimplemented_Unit;
14067
14068          --  Note: this only gives an error if we are generating code, or if
14069          --  we are in a generic library unit (where the pragma appears in the
14070          --  body, not in the spec).
14071
14072          when Pragma_Unimplemented_Unit => Unimplemented_Unit : declare
14073             Cunitent : constant Entity_Id :=
14074                          Cunit_Entity (Get_Source_Unit (Loc));
14075             Ent_Kind : constant Entity_Kind :=
14076                          Ekind (Cunitent);
14077
14078          begin
14079             GNAT_Pragma;
14080             Check_Arg_Count (0);
14081
14082             if Operating_Mode = Generate_Code
14083               or else Ent_Kind = E_Generic_Function
14084               or else Ent_Kind = E_Generic_Procedure
14085               or else Ent_Kind = E_Generic_Package
14086             then
14087                Get_Name_String (Chars (Cunitent));
14088                Set_Casing (Mixed_Case);
14089                Write_Str (Name_Buffer (1 .. Name_Len));
14090                Write_Str (" is not supported in this configuration");
14091                Write_Eol;
14092                raise Unrecoverable_Error;
14093             end if;
14094          end Unimplemented_Unit;
14095
14096          ------------------------
14097          -- Universal_Aliasing --
14098          ------------------------
14099
14100          --  pragma Universal_Aliasing [([Entity =>] type_LOCAL_NAME)];
14101
14102          when Pragma_Universal_Aliasing => Universal_Alias : declare
14103             E_Id : Entity_Id;
14104
14105          begin
14106             GNAT_Pragma;
14107             Check_Arg_Count (1);
14108             Check_Optional_Identifier (Arg2, Name_Entity);
14109             Check_Arg_Is_Local_Name (Arg1);
14110             E_Id := Entity (Get_Pragma_Arg (Arg1));
14111
14112             if E_Id = Any_Type then
14113                return;
14114             elsif No (E_Id) or else not Is_Type (E_Id) then
14115                Error_Pragma_Arg ("pragma% requires type", Arg1);
14116             end if;
14117
14118             Set_Universal_Aliasing (Implementation_Base_Type (E_Id));
14119          end Universal_Alias;
14120
14121          --------------------
14122          -- Universal_Data --
14123          --------------------
14124
14125          --  pragma Universal_Data [(library_unit_NAME)];
14126
14127          when Pragma_Universal_Data =>
14128             GNAT_Pragma;
14129
14130             --  If this is a configuration pragma, then set the universal
14131             --  addressing option, otherwise confirm that the pragma satisfies
14132             --  the requirements of library unit pragma placement and leave it
14133             --  to the GNAAMP back end to detect the pragma (avoids transitive
14134             --  setting of the option due to withed units).
14135
14136             if Is_Configuration_Pragma then
14137                Universal_Addressing_On_AAMP := True;
14138             else
14139                Check_Valid_Library_Unit_Pragma;
14140             end if;
14141
14142             if not AAMP_On_Target then
14143                Error_Pragma ("?pragma% ignored (applies only to AAMP)");
14144             end if;
14145
14146          ----------------
14147          -- Unmodified --
14148          ----------------
14149
14150          --  pragma Unmodified (local_Name {, local_Name});
14151
14152          when Pragma_Unmodified => Unmodified : declare
14153             Arg_Node : Node_Id;
14154             Arg_Expr : Node_Id;
14155             Arg_Ent  : Entity_Id;
14156
14157          begin
14158             GNAT_Pragma;
14159             Check_At_Least_N_Arguments (1);
14160
14161             --  Loop through arguments
14162
14163             Arg_Node := Arg1;
14164             while Present (Arg_Node) loop
14165                Check_No_Identifier (Arg_Node);
14166
14167                --  Note: the analyze call done by Check_Arg_Is_Local_Name will
14168                --  in fact generate reference, so that the entity will have a
14169                --  reference, which will inhibit any warnings about it not
14170                --  being referenced, and also properly show up in the ali file
14171                --  as a reference. But this reference is recorded before the
14172                --  Has_Pragma_Unreferenced flag is set, so that no warning is
14173                --  generated for this reference.
14174
14175                Check_Arg_Is_Local_Name (Arg_Node);
14176                Arg_Expr := Get_Pragma_Arg (Arg_Node);
14177
14178                if Is_Entity_Name (Arg_Expr) then
14179                   Arg_Ent := Entity (Arg_Expr);
14180
14181                   if not Is_Assignable (Arg_Ent) then
14182                      Error_Pragma_Arg
14183                        ("pragma% can only be applied to a variable",
14184                         Arg_Expr);
14185                   else
14186                      Set_Has_Pragma_Unmodified (Arg_Ent);
14187                   end if;
14188                end if;
14189
14190                Next (Arg_Node);
14191             end loop;
14192          end Unmodified;
14193
14194          ------------------
14195          -- Unreferenced --
14196          ------------------
14197
14198          --  pragma Unreferenced (local_Name {, local_Name});
14199
14200          --    or when used in a context clause:
14201
14202          --  pragma Unreferenced (library_unit_NAME {, library_unit_NAME}
14203
14204          when Pragma_Unreferenced => Unreferenced : declare
14205             Arg_Node : Node_Id;
14206             Arg_Expr : Node_Id;
14207             Arg_Ent  : Entity_Id;
14208             Citem    : Node_Id;
14209
14210          begin
14211             GNAT_Pragma;
14212             Check_At_Least_N_Arguments (1);
14213
14214             --  Check case of appearing within context clause
14215
14216             if Is_In_Context_Clause then
14217
14218                --  The arguments must all be units mentioned in a with clause
14219                --  in the same context clause. Note we already checked (in
14220                --  Par.Prag) that the arguments are either identifiers or
14221                --  selected components.
14222
14223                Arg_Node := Arg1;
14224                while Present (Arg_Node) loop
14225                   Citem := First (List_Containing (N));
14226                   while Citem /= N loop
14227                      if Nkind (Citem) = N_With_Clause
14228                        and then
14229                          Same_Name (Name (Citem), Get_Pragma_Arg (Arg_Node))
14230                      then
14231                         Set_Has_Pragma_Unreferenced
14232                           (Cunit_Entity
14233                              (Get_Source_Unit
14234                                 (Library_Unit (Citem))));
14235                         Set_Unit_Name
14236                           (Get_Pragma_Arg (Arg_Node), Name (Citem));
14237                         exit;
14238                      end if;
14239
14240                      Next (Citem);
14241                   end loop;
14242
14243                   if Citem = N then
14244                      Error_Pragma_Arg
14245                        ("argument of pragma% is not with'ed unit", Arg_Node);
14246                   end if;
14247
14248                   Next (Arg_Node);
14249                end loop;
14250
14251             --  Case of not in list of context items
14252
14253             else
14254                Arg_Node := Arg1;
14255                while Present (Arg_Node) loop
14256                   Check_No_Identifier (Arg_Node);
14257
14258                   --  Note: the analyze call done by Check_Arg_Is_Local_Name
14259                   --  will in fact generate reference, so that the entity will
14260                   --  have a reference, which will inhibit any warnings about
14261                   --  it not being referenced, and also properly show up in the
14262                   --  ali file as a reference. But this reference is recorded
14263                   --  before the Has_Pragma_Unreferenced flag is set, so that
14264                   --  no warning is generated for this reference.
14265
14266                   Check_Arg_Is_Local_Name (Arg_Node);
14267                   Arg_Expr := Get_Pragma_Arg (Arg_Node);
14268
14269                   if Is_Entity_Name (Arg_Expr) then
14270                      Arg_Ent := Entity (Arg_Expr);
14271
14272                      --  If the entity is overloaded, the pragma applies to the
14273                      --  most recent overloading, as documented. In this case,
14274                      --  name resolution does not generate a reference, so it
14275                      --  must be done here explicitly.
14276
14277                      if Is_Overloaded (Arg_Expr) then
14278                         Generate_Reference (Arg_Ent, N);
14279                      end if;
14280
14281                      Set_Has_Pragma_Unreferenced (Arg_Ent);
14282                   end if;
14283
14284                   Next (Arg_Node);
14285                end loop;
14286             end if;
14287          end Unreferenced;
14288
14289          --------------------------
14290          -- Unreferenced_Objects --
14291          --------------------------
14292
14293          --  pragma Unreferenced_Objects (local_Name {, local_Name});
14294
14295          when Pragma_Unreferenced_Objects => Unreferenced_Objects : declare
14296             Arg_Node : Node_Id;
14297             Arg_Expr : Node_Id;
14298
14299          begin
14300             GNAT_Pragma;
14301             Check_At_Least_N_Arguments (1);
14302
14303             Arg_Node := Arg1;
14304             while Present (Arg_Node) loop
14305                Check_No_Identifier (Arg_Node);
14306                Check_Arg_Is_Local_Name (Arg_Node);
14307                Arg_Expr := Get_Pragma_Arg (Arg_Node);
14308
14309                if not Is_Entity_Name (Arg_Expr)
14310                  or else not Is_Type (Entity (Arg_Expr))
14311                then
14312                   Error_Pragma_Arg
14313                     ("argument for pragma% must be type or subtype", Arg_Node);
14314                end if;
14315
14316                Set_Has_Pragma_Unreferenced_Objects (Entity (Arg_Expr));
14317                Next (Arg_Node);
14318             end loop;
14319          end Unreferenced_Objects;
14320
14321          ------------------------------
14322          -- Unreserve_All_Interrupts --
14323          ------------------------------
14324
14325          --  pragma Unreserve_All_Interrupts;
14326
14327          when Pragma_Unreserve_All_Interrupts =>
14328             GNAT_Pragma;
14329             Check_Arg_Count (0);
14330
14331             if In_Extended_Main_Code_Unit (Main_Unit_Entity) then
14332                Unreserve_All_Interrupts := True;
14333             end if;
14334
14335          ----------------
14336          -- Unsuppress --
14337          ----------------
14338
14339          --  pragma Unsuppress (IDENTIFIER [, [On =>] NAME]);
14340
14341          when Pragma_Unsuppress =>
14342             Ada_2005_Pragma;
14343             Process_Suppress_Unsuppress (False);
14344
14345          -------------------
14346          -- Use_VADS_Size --
14347          -------------------
14348
14349          --  pragma Use_VADS_Size;
14350
14351          when Pragma_Use_VADS_Size =>
14352             GNAT_Pragma;
14353             Check_Arg_Count (0);
14354             Check_Valid_Configuration_Pragma;
14355             Use_VADS_Size := True;
14356
14357          ---------------------
14358          -- Validity_Checks --
14359          ---------------------
14360
14361          --  pragma Validity_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
14362
14363          when Pragma_Validity_Checks => Validity_Checks : declare
14364             A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
14365             S  : String_Id;
14366             C  : Char_Code;
14367
14368          begin
14369             GNAT_Pragma;
14370             Check_Arg_Count (1);
14371             Check_No_Identifiers;
14372
14373             if Nkind (A) = N_String_Literal then
14374                S   := Strval (A);
14375
14376                declare
14377                   Slen    : constant Natural := Natural (String_Length (S));
14378                   Options : String (1 .. Slen);
14379                   J       : Natural;
14380
14381                begin
14382                   J := 1;
14383                   loop
14384                      C := Get_String_Char (S, Int (J));
14385                      exit when not In_Character_Range (C);
14386                      Options (J) := Get_Character (C);
14387
14388                      if J = Slen then
14389                         Set_Validity_Check_Options (Options);
14390                         exit;
14391                      else
14392                         J := J + 1;
14393                      end if;
14394                   end loop;
14395                end;
14396
14397             elsif Nkind (A) = N_Identifier then
14398                if Chars (A) = Name_All_Checks then
14399                   Set_Validity_Check_Options ("a");
14400                elsif Chars (A) = Name_On then
14401                   Validity_Checks_On := True;
14402                elsif Chars (A) = Name_Off then
14403                   Validity_Checks_On := False;
14404                end if;
14405             end if;
14406          end Validity_Checks;
14407
14408          --------------
14409          -- Volatile --
14410          --------------
14411
14412          --  pragma Volatile (LOCAL_NAME);
14413
14414          when Pragma_Volatile =>
14415             Process_Atomic_Shared_Volatile;
14416
14417          -------------------------
14418          -- Volatile_Components --
14419          -------------------------
14420
14421          --  pragma Volatile_Components (array_LOCAL_NAME);
14422
14423          --  Volatile is handled by the same circuit as Atomic_Components
14424
14425          --------------
14426          -- Warnings --
14427          --------------
14428
14429          --  pragma Warnings (On | Off);
14430          --  pragma Warnings (On | Off, LOCAL_NAME);
14431          --  pragma Warnings (static_string_EXPRESSION);
14432          --  pragma Warnings (On | Off, STRING_LITERAL);
14433
14434          when Pragma_Warnings => Warnings : begin
14435             GNAT_Pragma;
14436             Check_At_Least_N_Arguments (1);
14437             Check_No_Identifiers;
14438
14439             --  If debug flag -gnatd.i is set, pragma is ignored
14440
14441             if Debug_Flag_Dot_I then
14442                return;
14443             end if;
14444
14445             --  Process various forms of the pragma
14446
14447             declare
14448                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
14449
14450             begin
14451                --  One argument case
14452
14453                if Arg_Count = 1 then
14454
14455                   --  On/Off one argument case was processed by parser
14456
14457                   if Nkind (Argx) = N_Identifier
14458                     and then
14459                       (Chars (Argx) = Name_On
14460                          or else
14461                        Chars (Argx) = Name_Off)
14462                   then
14463                      null;
14464
14465                   --  One argument case must be ON/OFF or static string expr
14466
14467                   elsif not Is_Static_String_Expression (Arg1) then
14468                      Error_Pragma_Arg
14469                        ("argument of pragma% must be On/Off or " &
14470                         "static string expression", Arg1);
14471
14472                   --  One argument string expression case
14473
14474                   else
14475                      declare
14476                         Lit : constant Node_Id   := Expr_Value_S (Argx);
14477                         Str : constant String_Id := Strval (Lit);
14478                         Len : constant Nat       := String_Length (Str);
14479                         C   : Char_Code;
14480                         J   : Nat;
14481                         OK  : Boolean;
14482                         Chr : Character;
14483
14484                      begin
14485                         J := 1;
14486                         while J <= Len loop
14487                            C := Get_String_Char (Str, J);
14488                            OK := In_Character_Range (C);
14489
14490                            if OK then
14491                               Chr := Get_Character (C);
14492
14493                               --  Dot case
14494
14495                               if J < Len and then Chr = '.' then
14496                                  J := J + 1;
14497                                  C := Get_String_Char (Str, J);
14498                                  Chr := Get_Character (C);
14499
14500                                  if not Set_Dot_Warning_Switch (Chr) then
14501                                     Error_Pragma_Arg
14502                                       ("invalid warning switch character " &
14503                                        '.' & Chr, Arg1);
14504                                  end if;
14505
14506                               --  Non-Dot case
14507
14508                               else
14509                                  OK := Set_Warning_Switch (Chr);
14510                               end if;
14511                            end if;
14512
14513                            if not OK then
14514                               Error_Pragma_Arg
14515                                 ("invalid warning switch character " & Chr,
14516                                  Arg1);
14517                            end if;
14518
14519                            J := J + 1;
14520                         end loop;
14521                      end;
14522                   end if;
14523
14524                   --  Two or more arguments (must be two)
14525
14526                else
14527                   Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
14528                   Check_At_Most_N_Arguments (2);
14529
14530                   declare
14531                      E_Id : Node_Id;
14532                      E    : Entity_Id;
14533                      Err  : Boolean;
14534
14535                   begin
14536                      E_Id := Get_Pragma_Arg (Arg2);
14537                      Analyze (E_Id);
14538
14539                      --  In the expansion of an inlined body, a reference to
14540                      --  the formal may be wrapped in a conversion if the
14541                      --  actual is a conversion. Retrieve the real entity name.
14542
14543                      if (In_Instance_Body
14544                           or else In_Inlined_Body)
14545                        and then Nkind (E_Id) = N_Unchecked_Type_Conversion
14546                      then
14547                         E_Id := Expression (E_Id);
14548                      end if;
14549
14550                      --  Entity name case
14551
14552                      if Is_Entity_Name (E_Id) then
14553                         E := Entity (E_Id);
14554
14555                         if E = Any_Id then
14556                            return;
14557                         else
14558                            loop
14559                               Set_Warnings_Off
14560                                 (E, (Chars (Get_Pragma_Arg (Arg1)) =
14561                                                               Name_Off));
14562
14563                               if Chars (Get_Pragma_Arg (Arg1)) = Name_Off
14564                                 and then Warn_On_Warnings_Off
14565                               then
14566                                  Warnings_Off_Pragmas.Append ((N, E));
14567                               end if;
14568
14569                               if Is_Enumeration_Type (E) then
14570                                  declare
14571                                     Lit : Entity_Id;
14572                                  begin
14573                                     Lit := First_Literal (E);
14574                                     while Present (Lit) loop
14575                                        Set_Warnings_Off (Lit);
14576                                        Next_Literal (Lit);
14577                                     end loop;
14578                                  end;
14579                               end if;
14580
14581                               exit when No (Homonym (E));
14582                               E := Homonym (E);
14583                            end loop;
14584                         end if;
14585
14586                      --  Error if not entity or static string literal case
14587
14588                      elsif not Is_Static_String_Expression (Arg2) then
14589                         Error_Pragma_Arg
14590                           ("second argument of pragma% must be entity " &
14591                            "name or static string expression", Arg2);
14592
14593                      --  String literal case
14594
14595                      else
14596                         String_To_Name_Buffer
14597                           (Strval (Expr_Value_S (Get_Pragma_Arg (Arg2))));
14598
14599                         --  Note on configuration pragma case: If this is a
14600                         --  configuration pragma, then for an OFF pragma, we
14601                         --  just set Config True in the call, which is all
14602                         --  that needs to be done. For the case of ON, this
14603                         --  is normally an error, unless it is canceling the
14604                         --  effect of a previous OFF pragma in the same file.
14605                         --  In any other case, an error will be signalled (ON
14606                         --  with no matching OFF).
14607
14608                         if Chars (Argx) = Name_Off then
14609                            Set_Specific_Warning_Off
14610                              (Loc, Name_Buffer (1 .. Name_Len),
14611                               Config => Is_Configuration_Pragma);
14612
14613                         elsif Chars (Argx) = Name_On then
14614                            Set_Specific_Warning_On
14615                              (Loc, Name_Buffer (1 .. Name_Len), Err);
14616
14617                            if Err then
14618                               Error_Msg
14619                                 ("?pragma Warnings On with no " &
14620                                  "matching Warnings Off",
14621                                  Loc);
14622                            end if;
14623                         end if;
14624                      end if;
14625                   end;
14626                end if;
14627             end;
14628          end Warnings;
14629
14630          -------------------
14631          -- Weak_External --
14632          -------------------
14633
14634          --  pragma Weak_External ([Entity =>] LOCAL_NAME);
14635
14636          when Pragma_Weak_External => Weak_External : declare
14637             Ent : Entity_Id;
14638
14639          begin
14640             GNAT_Pragma;
14641             Check_Arg_Count (1);
14642             Check_Optional_Identifier (Arg1, Name_Entity);
14643             Check_Arg_Is_Library_Level_Local_Name (Arg1);
14644             Ent := Entity (Get_Pragma_Arg (Arg1));
14645
14646             if Rep_Item_Too_Early (Ent, N) then
14647                return;
14648             else
14649                Ent := Underlying_Type (Ent);
14650             end if;
14651
14652             --  The only processing required is to link this item on to the
14653             --  list of rep items for the given entity. This is accomplished
14654             --  by the call to Rep_Item_Too_Late (when no error is detected
14655             --  and False is returned).
14656
14657             if Rep_Item_Too_Late (Ent, N) then
14658                return;
14659             else
14660                Set_Has_Gigi_Rep_Item (Ent);
14661             end if;
14662          end Weak_External;
14663
14664          -----------------------------
14665          -- Wide_Character_Encoding --
14666          -----------------------------
14667
14668          --  pragma Wide_Character_Encoding (IDENTIFIER);
14669
14670          when Pragma_Wide_Character_Encoding =>
14671             GNAT_Pragma;
14672
14673             --  Nothing to do, handled in parser. Note that we do not enforce
14674             --  configuration pragma placement, this pragma can appear at any
14675             --  place in the source, allowing mixed encodings within a single
14676             --  source program.
14677
14678             null;
14679
14680          --------------------
14681          -- Unknown_Pragma --
14682          --------------------
14683
14684          --  Should be impossible, since the case of an unknown pragma is
14685          --  separately processed before the case statement is entered.
14686
14687          when Unknown_Pragma =>
14688             raise Program_Error;
14689       end case;
14690
14691       --  AI05-0144: detect dangerous order dependence. Disabled for now,
14692       --  until AI is formally approved.
14693
14694       --  Check_Order_Dependence;
14695
14696    exception
14697       when Pragma_Exit => null;
14698    end Analyze_Pragma;
14699
14700    -----------------------------
14701    -- Analyze_TC_In_Decl_Part --
14702    -----------------------------
14703
14704    procedure Analyze_TC_In_Decl_Part (N : Node_Id; S : Entity_Id) is
14705    begin
14706       --  Install formals and push subprogram spec onto scope stack so that we
14707       --  can see the formals from the pragma.
14708
14709       Install_Formals (S);
14710       Push_Scope (S);
14711
14712       --  Preanalyze the boolean expressions, we treat these as spec
14713       --  expressions (i.e. similar to a default expression).
14714
14715       Preanalyze_TC_Args (N,
14716                           Get_Requires_From_Test_Case_Pragma (N),
14717                           Get_Ensures_From_Test_Case_Pragma (N));
14718
14719       --  Remove the subprogram from the scope stack now that the pre-analysis
14720       --  of the expressions in the test-case is done.
14721
14722       End_Scope;
14723    end Analyze_TC_In_Decl_Part;
14724
14725    --------------------
14726    -- Check_Disabled --
14727    --------------------
14728
14729    function Check_Disabled (Nam : Name_Id) return Boolean is
14730       PP : Node_Id;
14731
14732    begin
14733       --  Loop through entries in check policy list
14734
14735       PP := Opt.Check_Policy_List;
14736       loop
14737          --  If there are no specific entries that matched, then nothing is
14738          --  disabled, so return False.
14739
14740          if No (PP) then
14741             return False;
14742
14743          --  Here we have an entry see if it matches
14744
14745          else
14746             declare
14747                PPA : constant List_Id := Pragma_Argument_Associations (PP);
14748             begin
14749                if Nam = Chars (Get_Pragma_Arg (First (PPA))) then
14750                   return Chars (Get_Pragma_Arg (Last (PPA))) = Name_Disable;
14751                else
14752                   PP := Next_Pragma (PP);
14753                end if;
14754             end;
14755          end if;
14756       end loop;
14757    end Check_Disabled;
14758
14759    -------------------
14760    -- Check_Enabled --
14761    -------------------
14762
14763    function Check_Enabled (Nam : Name_Id) return Boolean is
14764       PP : Node_Id;
14765
14766    begin
14767       --  Loop through entries in check policy list
14768
14769       PP := Opt.Check_Policy_List;
14770       loop
14771          --  If there are no specific entries that matched, then we let the
14772          --  setting of assertions govern. Note that this provides the needed
14773          --  compatibility with the RM for the cases of assertion, invariant,
14774          --  precondition, predicate, and postcondition.
14775
14776          if No (PP) then
14777             return Assertions_Enabled;
14778
14779          --  Here we have an entry see if it matches
14780
14781          else
14782             declare
14783                PPA : constant List_Id := Pragma_Argument_Associations (PP);
14784
14785             begin
14786                if Nam = Chars (Get_Pragma_Arg (First (PPA))) then
14787                   case (Chars (Get_Pragma_Arg (Last (PPA)))) is
14788                      when Name_On | Name_Check =>
14789                         return True;
14790                      when Name_Off | Name_Ignore =>
14791                         return False;
14792                      when others =>
14793                         raise Program_Error;
14794                   end case;
14795
14796                else
14797                   PP := Next_Pragma (PP);
14798                end if;
14799             end;
14800          end if;
14801       end loop;
14802    end Check_Enabled;
14803
14804    ---------------------------------
14805    -- Delay_Config_Pragma_Analyze --
14806    ---------------------------------
14807
14808    function Delay_Config_Pragma_Analyze (N : Node_Id) return Boolean is
14809    begin
14810       return Pragma_Name (N) = Name_Interrupt_State
14811                or else
14812              Pragma_Name (N) = Name_Priority_Specific_Dispatching;
14813    end Delay_Config_Pragma_Analyze;
14814
14815    -------------------------
14816    -- Get_Base_Subprogram --
14817    -------------------------
14818
14819    function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id is
14820       Result : Entity_Id;
14821
14822    begin
14823       --  Follow subprogram renaming chain
14824
14825       Result := Def_Id;
14826       while Is_Subprogram (Result)
14827         and then
14828           Nkind (Parent (Declaration_Node (Result))) =
14829                                          N_Subprogram_Renaming_Declaration
14830         and then Present (Alias (Result))
14831       loop
14832          Result := Alias (Result);
14833       end loop;
14834
14835       return Result;
14836    end Get_Base_Subprogram;
14837
14838    ----------------
14839    -- Initialize --
14840    ----------------
14841
14842    procedure Initialize is
14843    begin
14844       Externals.Init;
14845    end Initialize;
14846
14847    -----------------------------
14848    -- Is_Config_Static_String --
14849    -----------------------------
14850
14851    function Is_Config_Static_String (Arg : Node_Id) return Boolean is
14852
14853       function Add_Config_Static_String (Arg : Node_Id) return Boolean;
14854       --  This is an internal recursive function that is just like the outer
14855       --  function except that it adds the string to the name buffer rather
14856       --  than placing the string in the name buffer.
14857
14858       ------------------------------
14859       -- Add_Config_Static_String --
14860       ------------------------------
14861
14862       function Add_Config_Static_String (Arg : Node_Id) return Boolean is
14863          N : Node_Id;
14864          C : Char_Code;
14865
14866       begin
14867          N := Arg;
14868
14869          if Nkind (N) = N_Op_Concat then
14870             if Add_Config_Static_String (Left_Opnd (N)) then
14871                N := Right_Opnd (N);
14872             else
14873                return False;
14874             end if;
14875          end if;
14876
14877          if Nkind (N) /= N_String_Literal then
14878             Error_Msg_N ("string literal expected for pragma argument", N);
14879             return False;
14880
14881          else
14882             for J in 1 .. String_Length (Strval (N)) loop
14883                C := Get_String_Char (Strval (N), J);
14884
14885                if not In_Character_Range (C) then
14886                   Error_Msg
14887                     ("string literal contains invalid wide character",
14888                      Sloc (N) + 1 + Source_Ptr (J));
14889                   return False;
14890                end if;
14891
14892                Add_Char_To_Name_Buffer (Get_Character (C));
14893             end loop;
14894          end if;
14895
14896          return True;
14897       end Add_Config_Static_String;
14898
14899    --  Start of processing for Is_Config_Static_String
14900
14901    begin
14902
14903       Name_Len := 0;
14904       return Add_Config_Static_String (Arg);
14905    end Is_Config_Static_String;
14906
14907    -----------------------------------------
14908    -- Is_Non_Significant_Pragma_Reference --
14909    -----------------------------------------
14910
14911    --  This function makes use of the following static table which indicates
14912    --  whether a given pragma is significant.
14913
14914    --  -1  indicates that references in any argument position are significant
14915    --  0   indicates that appearance in any argument is not significant
14916    --  +n  indicates that appearance as argument n is significant, but all
14917    --      other arguments are not significant
14918    --  99  special processing required (e.g. for pragma Check)
14919
14920    Sig_Flags : constant array (Pragma_Id) of Int :=
14921      (Pragma_AST_Entry                      => -1,
14922       Pragma_Abort_Defer                    => -1,
14923       Pragma_Ada_83                         => -1,
14924       Pragma_Ada_95                         => -1,
14925       Pragma_Ada_05                         => -1,
14926       Pragma_Ada_2005                       => -1,
14927       Pragma_Ada_12                         => -1,
14928       Pragma_Ada_2012                       => -1,
14929       Pragma_All_Calls_Remote               => -1,
14930       Pragma_Annotate                       => -1,
14931       Pragma_Assert                         => -1,
14932       Pragma_Assertion_Policy               =>  0,
14933       Pragma_Assume_No_Invalid_Values       =>  0,
14934       Pragma_Asynchronous                   => -1,
14935       Pragma_Atomic                         =>  0,
14936       Pragma_Atomic_Components              =>  0,
14937       Pragma_Attach_Handler                 => -1,
14938       Pragma_Check                          => 99,
14939       Pragma_Check_Name                     =>  0,
14940       Pragma_Check_Policy                   =>  0,
14941       Pragma_CIL_Constructor                => -1,
14942       Pragma_CPP_Class                      =>  0,
14943       Pragma_CPP_Constructor                =>  0,
14944       Pragma_CPP_Virtual                    =>  0,
14945       Pragma_CPP_Vtable                     =>  0,
14946       Pragma_CPU                            => -1,
14947       Pragma_C_Pass_By_Copy                 =>  0,
14948       Pragma_Comment                        =>  0,
14949       Pragma_Common_Object                  => -1,
14950       Pragma_Compile_Time_Error             => -1,
14951       Pragma_Compile_Time_Warning           => -1,
14952       Pragma_Compiler_Unit                  =>  0,
14953       Pragma_Complete_Representation        =>  0,
14954       Pragma_Complex_Representation         =>  0,
14955       Pragma_Component_Alignment            => -1,
14956       Pragma_Controlled                     =>  0,
14957       Pragma_Convention                     =>  0,
14958       Pragma_Convention_Identifier          =>  0,
14959       Pragma_Debug                          => -1,
14960       Pragma_Debug_Policy                   =>  0,
14961       Pragma_Detect_Blocking                => -1,
14962       Pragma_Default_Storage_Pool           => -1,
14963       Pragma_Dimension                      => -1,
14964       Pragma_Disable_Atomic_Synchronization => -1,
14965       Pragma_Discard_Names                  =>  0,
14966       Pragma_Dispatching_Domain             => -1,
14967       Pragma_Elaborate                      => -1,
14968       Pragma_Elaborate_All                  => -1,
14969       Pragma_Elaborate_Body                 => -1,
14970       Pragma_Elaboration_Checks             => -1,
14971       Pragma_Eliminate                      => -1,
14972       Pragma_Enable_Atomic_Synchronization  => -1,
14973       Pragma_Export                         => -1,
14974       Pragma_Export_Exception               => -1,
14975       Pragma_Export_Function                => -1,
14976       Pragma_Export_Object                  => -1,
14977       Pragma_Export_Procedure               => -1,
14978       Pragma_Export_Value                   => -1,
14979       Pragma_Export_Valued_Procedure        => -1,
14980       Pragma_Extend_System                  => -1,
14981       Pragma_Extensions_Allowed             => -1,
14982       Pragma_External                       => -1,
14983       Pragma_Favor_Top_Level                => -1,
14984       Pragma_External_Name_Casing           => -1,
14985       Pragma_Fast_Math                      => -1,
14986       Pragma_Finalize_Storage_Only          =>  0,
14987       Pragma_Float_Representation           =>  0,
14988       Pragma_Ident                          => -1,
14989       Pragma_Implementation_Defined         => -1,
14990       Pragma_Implemented                    => -1,
14991       Pragma_Implicit_Packing               =>  0,
14992       Pragma_Import                         => +2,
14993       Pragma_Import_Exception               =>  0,
14994       Pragma_Import_Function                =>  0,
14995       Pragma_Import_Object                  =>  0,
14996       Pragma_Import_Procedure               =>  0,
14997       Pragma_Import_Valued_Procedure        =>  0,
14998       Pragma_Independent                    =>  0,
14999       Pragma_Independent_Components         =>  0,
15000       Pragma_Initialize_Scalars             => -1,
15001       Pragma_Inline                         =>  0,
15002       Pragma_Inline_Always                  =>  0,
15003       Pragma_Inline_Generic                 =>  0,
15004       Pragma_Inspection_Point               => -1,
15005       Pragma_Interface                      => +2,
15006       Pragma_Interface_Name                 => +2,
15007       Pragma_Interrupt_Handler              => -1,
15008       Pragma_Interrupt_Priority             => -1,
15009       Pragma_Interrupt_State                => -1,
15010       Pragma_Invariant                      => -1,
15011       Pragma_Java_Constructor               => -1,
15012       Pragma_Java_Interface                 => -1,
15013       Pragma_Keep_Names                     =>  0,
15014       Pragma_License                        => -1,
15015       Pragma_Link_With                      => -1,
15016       Pragma_Linker_Alias                   => -1,
15017       Pragma_Linker_Constructor             => -1,
15018       Pragma_Linker_Destructor              => -1,
15019       Pragma_Linker_Options                 => -1,
15020       Pragma_Linker_Section                 => -1,
15021       Pragma_List                           => -1,
15022       Pragma_Locking_Policy                 => -1,
15023       Pragma_Long_Float                     => -1,
15024       Pragma_Machine_Attribute              => -1,
15025       Pragma_Main                           => -1,
15026       Pragma_Main_Storage                   => -1,
15027       Pragma_Memory_Size                    => -1,
15028       Pragma_No_Return                      =>  0,
15029       Pragma_No_Body                        =>  0,
15030       Pragma_No_Run_Time                    => -1,
15031       Pragma_No_Strict_Aliasing             => -1,
15032       Pragma_Normalize_Scalars              => -1,
15033       Pragma_Obsolescent                    =>  0,
15034       Pragma_Optimize                       => -1,
15035       Pragma_Optimize_Alignment             => -1,
15036       Pragma_Ordered                        =>  0,
15037       Pragma_Pack                           =>  0,
15038       Pragma_Page                           => -1,
15039       Pragma_Passive                        => -1,
15040       Pragma_Preelaborable_Initialization   => -1,
15041       Pragma_Polling                        => -1,
15042       Pragma_Persistent_BSS                 =>  0,
15043       Pragma_Postcondition                  => -1,
15044       Pragma_Precondition                   => -1,
15045       Pragma_Predicate                      => -1,
15046       Pragma_Preelaborate                   => -1,
15047       Pragma_Preelaborate_05                => -1,
15048       Pragma_Priority                       => -1,
15049       Pragma_Priority_Specific_Dispatching  => -1,
15050       Pragma_Profile                        =>  0,
15051       Pragma_Profile_Warnings               =>  0,
15052       Pragma_Propagate_Exceptions           => -1,
15053       Pragma_Psect_Object                   => -1,
15054       Pragma_Pure                           => -1,
15055       Pragma_Pure_05                        => -1,
15056       Pragma_Pure_12                        => -1,
15057       Pragma_Pure_Function                  => -1,
15058       Pragma_Queuing_Policy                 => -1,
15059       Pragma_Ravenscar                      => -1,
15060       Pragma_Relative_Deadline              => -1,
15061       Pragma_Remote_Call_Interface          => -1,
15062       Pragma_Remote_Types                   => -1,
15063       Pragma_Restricted_Run_Time            => -1,
15064       Pragma_Restriction_Warnings           => -1,
15065       Pragma_Restrictions                   => -1,
15066       Pragma_Reviewable                     => -1,
15067       Pragma_Short_Circuit_And_Or           => -1,
15068       Pragma_Share_Generic                  => -1,
15069       Pragma_Shared                         => -1,
15070       Pragma_Shared_Passive                 => -1,
15071       Pragma_Short_Descriptors              =>  0,
15072       Pragma_Source_File_Name               => -1,
15073       Pragma_Source_File_Name_Project       => -1,
15074       Pragma_Source_Reference               => -1,
15075       Pragma_Storage_Size                   => -1,
15076       Pragma_Storage_Unit                   => -1,
15077       Pragma_Static_Elaboration_Desired     => -1,
15078       Pragma_Stream_Convert                 => -1,
15079       Pragma_Style_Checks                   => -1,
15080       Pragma_Subtitle                       => -1,
15081       Pragma_Suppress                       =>  0,
15082       Pragma_Suppress_Exception_Locations   =>  0,
15083       Pragma_Suppress_All                   => -1,
15084       Pragma_Suppress_Debug_Info            =>  0,
15085       Pragma_Suppress_Initialization        =>  0,
15086       Pragma_System_Name                    => -1,
15087       Pragma_Task_Dispatching_Policy        => -1,
15088       Pragma_Task_Info                      => -1,
15089       Pragma_Task_Name                      => -1,
15090       Pragma_Task_Storage                   =>  0,
15091       Pragma_Test_Case                      => -1,
15092       Pragma_Thread_Local_Storage           =>  0,
15093       Pragma_Time_Slice                     => -1,
15094       Pragma_Title                          => -1,
15095       Pragma_Unchecked_Union                =>  0,
15096       Pragma_Unimplemented_Unit             => -1,
15097       Pragma_Universal_Aliasing             => -1,
15098       Pragma_Universal_Data                 => -1,
15099       Pragma_Unmodified                     => -1,
15100       Pragma_Unreferenced                   => -1,
15101       Pragma_Unreferenced_Objects           => -1,
15102       Pragma_Unreserve_All_Interrupts       => -1,
15103       Pragma_Unsuppress                     =>  0,
15104       Pragma_Use_VADS_Size                  => -1,
15105       Pragma_Validity_Checks                => -1,
15106       Pragma_Volatile                       =>  0,
15107       Pragma_Volatile_Components            =>  0,
15108       Pragma_Warnings                       => -1,
15109       Pragma_Weak_External                  => -1,
15110       Pragma_Wide_Character_Encoding        =>  0,
15111       Unknown_Pragma                        =>  0);
15112
15113    function Is_Non_Significant_Pragma_Reference (N : Node_Id) return Boolean is
15114       Id : Pragma_Id;
15115       P  : Node_Id;
15116       C  : Int;
15117       A  : Node_Id;
15118
15119    begin
15120       P := Parent (N);
15121
15122       if Nkind (P) /= N_Pragma_Argument_Association then
15123          return False;
15124
15125       else
15126          Id := Get_Pragma_Id (Parent (P));
15127          C := Sig_Flags (Id);
15128
15129          case C is
15130             when -1 =>
15131                return False;
15132
15133             when 0 =>
15134                return True;
15135
15136             when 99 =>
15137                case Id is
15138
15139                   --  For pragma Check, the first argument is not significant,
15140                   --  the second and the third (if present) arguments are
15141                   --  significant.
15142
15143                   when Pragma_Check =>
15144                      return
15145                        P = First (Pragma_Argument_Associations (Parent (P)));
15146
15147                   when others =>
15148                      raise Program_Error;
15149                end case;
15150
15151             when others =>
15152                A := First (Pragma_Argument_Associations (Parent (P)));
15153                for J in 1 .. C - 1 loop
15154                   if No (A) then
15155                      return False;
15156                   end if;
15157
15158                   Next (A);
15159                end loop;
15160
15161                return A = P; -- is this wrong way round ???
15162          end case;
15163       end if;
15164    end Is_Non_Significant_Pragma_Reference;
15165
15166    ------------------------------
15167    -- Is_Pragma_String_Literal --
15168    ------------------------------
15169
15170    --  This function returns true if the corresponding pragma argument is a
15171    --  static string expression. These are the only cases in which string
15172    --  literals can appear as pragma arguments. We also allow a string literal
15173    --  as the first argument to pragma Assert (although it will of course
15174    --  always generate a type error).
15175
15176    function Is_Pragma_String_Literal (Par : Node_Id) return Boolean is
15177       Pragn : constant Node_Id := Parent (Par);
15178       Assoc : constant List_Id := Pragma_Argument_Associations (Pragn);
15179       Pname : constant Name_Id := Pragma_Name (Pragn);
15180       Argn  : Natural;
15181       N     : Node_Id;
15182
15183    begin
15184       Argn := 1;
15185       N := First (Assoc);
15186       loop
15187          exit when N = Par;
15188          Argn := Argn + 1;
15189          Next (N);
15190       end loop;
15191
15192       if Pname = Name_Assert then
15193          return True;
15194
15195       elsif Pname = Name_Export then
15196          return Argn > 2;
15197
15198       elsif Pname = Name_Ident then
15199          return Argn = 1;
15200
15201       elsif Pname = Name_Import then
15202          return Argn > 2;
15203
15204       elsif Pname = Name_Interface_Name then
15205          return Argn > 1;
15206
15207       elsif Pname = Name_Linker_Alias then
15208          return Argn = 2;
15209
15210       elsif Pname = Name_Linker_Section then
15211          return Argn = 2;
15212
15213       elsif Pname = Name_Machine_Attribute then
15214          return Argn = 2;
15215
15216       elsif Pname = Name_Source_File_Name then
15217          return True;
15218
15219       elsif Pname = Name_Source_Reference then
15220          return Argn = 2;
15221
15222       elsif Pname = Name_Title then
15223          return True;
15224
15225       elsif Pname = Name_Subtitle then
15226          return True;
15227
15228       else
15229          return False;
15230       end if;
15231    end Is_Pragma_String_Literal;
15232
15233    ------------------------
15234    -- Preanalyze_TC_Args --
15235    ------------------------
15236
15237    procedure Preanalyze_TC_Args (N, Arg_Req, Arg_Ens : Node_Id) is
15238    begin
15239       --  Preanalyze the boolean expressions, we treat these as spec
15240       --  expressions (i.e. similar to a default expression).
15241
15242       if Present (Arg_Req) then
15243          Preanalyze_Spec_Expression
15244            (Get_Pragma_Arg (Arg_Req), Standard_Boolean);
15245
15246          --  In ASIS mode, for a pragma generated from a source aspect, also
15247          --  analyze the original aspect expression.
15248
15249          if ASIS_Mode
15250            and then Present (Corresponding_Aspect (N))
15251          then
15252             Preanalyze_Spec_Expression
15253               (Original_Node (Get_Pragma_Arg (Arg_Req)), Standard_Boolean);
15254          end if;
15255       end if;
15256
15257       if Present (Arg_Ens) then
15258          Preanalyze_Spec_Expression
15259            (Get_Pragma_Arg (Arg_Ens), Standard_Boolean);
15260
15261          --  In ASIS mode, for a pragma generated from a source aspect, also
15262          --  analyze the original aspect expression.
15263
15264          if ASIS_Mode
15265            and then Present (Corresponding_Aspect (N))
15266          then
15267             Preanalyze_Spec_Expression
15268               (Original_Node (Get_Pragma_Arg (Arg_Ens)), Standard_Boolean);
15269          end if;
15270       end if;
15271    end Preanalyze_TC_Args;
15272
15273    --------------------------------------
15274    -- Process_Compilation_Unit_Pragmas --
15275    --------------------------------------
15276
15277    procedure Process_Compilation_Unit_Pragmas (N : Node_Id) is
15278    begin
15279       --  A special check for pragma Suppress_All, a very strange DEC pragma,
15280       --  strange because it comes at the end of the unit. Rational has the
15281       --  same name for a pragma, but treats it as a program unit pragma, In
15282       --  GNAT we just decide to allow it anywhere at all. If it appeared then
15283       --  the flag Has_Pragma_Suppress_All was set on the compilation unit
15284       --  node, and we insert a pragma Suppress (All_Checks) at the start of
15285       --  the context clause to ensure the correct processing.
15286
15287       if Has_Pragma_Suppress_All (N) then
15288          Prepend_To (Context_Items (N),
15289            Make_Pragma (Sloc (N),
15290              Chars                        => Name_Suppress,
15291              Pragma_Argument_Associations => New_List (
15292                Make_Pragma_Argument_Association (Sloc (N),
15293                  Expression => Make_Identifier (Sloc (N), Name_All_Checks)))));
15294       end if;
15295
15296       --  Nothing else to do at the current time!
15297
15298    end Process_Compilation_Unit_Pragmas;
15299
15300    --------
15301    -- rv --
15302    --------
15303
15304    procedure rv is
15305    begin
15306       null;
15307    end rv;
15308
15309    --------------------------------
15310    -- Set_Encoded_Interface_Name --
15311    --------------------------------
15312
15313    procedure Set_Encoded_Interface_Name (E : Entity_Id; S : Node_Id) is
15314       Str : constant String_Id := Strval (S);
15315       Len : constant Int       := String_Length (Str);
15316       CC  : Char_Code;
15317       C   : Character;
15318       J   : Int;
15319
15320       Hex : constant array (0 .. 15) of Character := "0123456789abcdef";
15321
15322       procedure Encode;
15323       --  Stores encoded value of character code CC. The encoding we use an
15324       --  underscore followed by four lower case hex digits.
15325
15326       ------------
15327       -- Encode --
15328       ------------
15329
15330       procedure Encode is
15331       begin
15332          Store_String_Char (Get_Char_Code ('_'));
15333          Store_String_Char
15334            (Get_Char_Code (Hex (Integer (CC / 2 ** 12))));
15335          Store_String_Char
15336            (Get_Char_Code (Hex (Integer (CC / 2 ** 8 and 16#0F#))));
15337          Store_String_Char
15338            (Get_Char_Code (Hex (Integer (CC / 2 ** 4 and 16#0F#))));
15339          Store_String_Char
15340            (Get_Char_Code (Hex (Integer (CC and 16#0F#))));
15341       end Encode;
15342
15343    --  Start of processing for Set_Encoded_Interface_Name
15344
15345    begin
15346       --  If first character is asterisk, this is a link name, and we leave it
15347       --  completely unmodified. We also ignore null strings (the latter case
15348       --  happens only in error cases) and no encoding should occur for Java or
15349       --  AAMP interface names.
15350
15351       if Len = 0
15352         or else Get_String_Char (Str, 1) = Get_Char_Code ('*')
15353         or else VM_Target /= No_VM
15354         or else AAMP_On_Target
15355       then
15356          Set_Interface_Name (E, S);
15357
15358       else
15359          J := 1;
15360          loop
15361             CC := Get_String_Char (Str, J);
15362
15363             exit when not In_Character_Range (CC);
15364
15365             C := Get_Character (CC);
15366
15367             exit when C /= '_' and then C /= '$'
15368               and then C not in '0' .. '9'
15369               and then C not in 'a' .. 'z'
15370               and then C not in 'A' .. 'Z';
15371
15372             if J = Len then
15373                Set_Interface_Name (E, S);
15374                return;
15375
15376             else
15377                J := J + 1;
15378             end if;
15379          end loop;
15380
15381          --  Here we need to encode. The encoding we use as follows:
15382          --     three underscores  + four hex digits (lower case)
15383
15384          Start_String;
15385
15386          for J in 1 .. String_Length (Str) loop
15387             CC := Get_String_Char (Str, J);
15388
15389             if not In_Character_Range (CC) then
15390                Encode;
15391             else
15392                C := Get_Character (CC);
15393
15394                if C = '_' or else C = '$'
15395                  or else C in '0' .. '9'
15396                  or else C in 'a' .. 'z'
15397                  or else C in 'A' .. 'Z'
15398                then
15399                   Store_String_Char (CC);
15400                else
15401                   Encode;
15402                end if;
15403             end if;
15404          end loop;
15405
15406          Set_Interface_Name (E,
15407            Make_String_Literal (Sloc (S),
15408              Strval => End_String));
15409       end if;
15410    end Set_Encoded_Interface_Name;
15411
15412    -------------------
15413    -- Set_Unit_Name --
15414    -------------------
15415
15416    procedure Set_Unit_Name (N : Node_Id; With_Item : Node_Id) is
15417       Pref : Node_Id;
15418       Scop : Entity_Id;
15419
15420    begin
15421       if Nkind (N) = N_Identifier
15422         and then Nkind (With_Item) = N_Identifier
15423       then
15424          Set_Entity (N, Entity (With_Item));
15425
15426       elsif Nkind (N) = N_Selected_Component then
15427          Change_Selected_Component_To_Expanded_Name (N);
15428          Set_Entity (N, Entity (With_Item));
15429          Set_Entity (Selector_Name (N), Entity (N));
15430
15431          Pref := Prefix (N);
15432          Scop := Scope (Entity (N));
15433          while Nkind (Pref) = N_Selected_Component loop
15434             Change_Selected_Component_To_Expanded_Name (Pref);
15435             Set_Entity (Selector_Name (Pref), Scop);
15436             Set_Entity (Pref, Scop);
15437             Pref := Prefix (Pref);
15438             Scop := Scope (Scop);
15439          end loop;
15440
15441          Set_Entity (Pref, Scop);
15442       end if;
15443    end Set_Unit_Name;
15444
15445 end Sem_Prag;