OSDN Git Service

2012-02-17 Yannick Moy <moy@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_prag.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                             S E M _ P R A G                              --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2012, Free Software Foundation, Inc.         --
10 --                                                                          --
11 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
12 -- terms of the  GNU General Public License as published  by the Free Soft- --
13 -- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14 -- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17 -- for  more details.  You should have  received  a copy of the GNU General --
18 -- Public License  distributed with GNAT; see file COPYING3.  If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license.          --
20 --                                                                          --
21 -- GNAT was originally developed  by the GNAT team at  New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
23 --                                                                          --
24 ------------------------------------------------------------------------------
25
26 --  This unit contains the semantic processing for all pragmas, both language
27 --  and implementation defined. For most pragmas, the parser only does the
28 --  most basic job of checking the syntax, so Sem_Prag also contains the code
29 --  to complete the syntax checks. Certain pragmas are handled partially or
30 --  completely by the parser (see Par.Prag for further details).
31
32 with Aspects;  use Aspects;
33 with Atree;    use Atree;
34 with Casing;   use Casing;
35 with Checks;   use Checks;
36 with Csets;    use Csets;
37 with Debug;    use Debug;
38 with Einfo;    use Einfo;
39 with Elists;   use Elists;
40 with Errout;   use Errout;
41 with Exp_Dist; use Exp_Dist;
42 with Exp_Util; use Exp_Util;
43 with Freeze;   use Freeze;
44 with Lib;      use Lib;
45 with Lib.Writ; use Lib.Writ;
46 with Lib.Xref; use Lib.Xref;
47 with Namet.Sp; use Namet.Sp;
48 with Nlists;   use Nlists;
49 with Nmake;    use Nmake;
50 with Opt;      use Opt;
51 with Output;   use Output;
52 with Par_SCO;  use Par_SCO;
53 with Restrict; use Restrict;
54 with Rident;   use Rident;
55 with Rtsfind;  use Rtsfind;
56 with Sem;      use Sem;
57 with Sem_Aux;  use Sem_Aux;
58 with Sem_Ch3;  use Sem_Ch3;
59 with Sem_Ch6;  use Sem_Ch6;
60 with Sem_Ch8;  use Sem_Ch8;
61 with Sem_Ch12; use Sem_Ch12;
62 with Sem_Ch13; use Sem_Ch13;
63 with Sem_Disp; use Sem_Disp;
64 with Sem_Dist; use Sem_Dist;
65 with Sem_Elim; use Sem_Elim;
66 with Sem_Eval; use Sem_Eval;
67 with Sem_Intr; use Sem_Intr;
68 with Sem_Mech; use Sem_Mech;
69 with Sem_Res;  use Sem_Res;
70 with Sem_Type; use Sem_Type;
71 with Sem_Util; use Sem_Util;
72 with Sem_VFpt; use Sem_VFpt;
73 with Sem_Warn; use Sem_Warn;
74 with Stand;    use Stand;
75 with Sinfo;    use Sinfo;
76 with Sinfo.CN; use Sinfo.CN;
77 with Sinput;   use Sinput;
78 with Snames;   use Snames;
79 with Stringt;  use Stringt;
80 with Stylesw;  use Stylesw;
81 with Table;
82 with Targparm; use Targparm;
83 with Tbuild;   use Tbuild;
84 with Ttypes;
85 with Uintp;    use Uintp;
86 with Uname;    use Uname;
87 with Urealp;   use Urealp;
88 with Validsw;  use Validsw;
89 with Warnsw;   use Warnsw;
90
91 package body Sem_Prag is
92
93    ----------------------------------------------
94    -- Common Handling of Import-Export Pragmas --
95    ----------------------------------------------
96
97    --  In the following section, a number of Import_xxx and Export_xxx pragmas
98    --  are defined by GNAT. These are compatible with the DEC pragmas of the
99    --  same name, and all have the following common form and processing:
100
101    --  pragma Export_xxx
102    --        [Internal                 =>] LOCAL_NAME
103    --     [, [External                 =>] EXTERNAL_SYMBOL]
104    --     [, other optional parameters   ]);
105
106    --  pragma Import_xxx
107    --        [Internal                 =>] LOCAL_NAME
108    --     [, [External                 =>] EXTERNAL_SYMBOL]
109    --     [, other optional parameters   ]);
110
111    --   EXTERNAL_SYMBOL ::=
112    --     IDENTIFIER
113    --   | static_string_EXPRESSION
114
115    --  The internal LOCAL_NAME designates the entity that is imported or
116    --  exported, and must refer to an entity in the current declarative
117    --  part (as required by the rules for LOCAL_NAME).
118
119    --  The external linker name is designated by the External parameter if
120    --  given, or the Internal parameter if not (if there is no External
121    --  parameter, the External parameter is a copy of the Internal name).
122
123    --  If the External parameter is given as a string, then this string is
124    --  treated as an external name (exactly as though it had been given as an
125    --  External_Name parameter for a normal Import pragma).
126
127    --  If the External parameter is given as an identifier (or there is no
128    --  External parameter, so that the Internal identifier is used), then
129    --  the external name is the characters of the identifier, translated
130    --  to all upper case letters for OpenVMS versions of GNAT, and to all
131    --  lower case letters for all other versions
132
133    --  Note: the external name specified or implied by any of these special
134    --  Import_xxx or Export_xxx pragmas override an external or link name
135    --  specified in a previous Import or Export pragma.
136
137    --  Note: these and all other DEC-compatible GNAT pragmas allow full use of
138    --  named notation, following the standard rules for subprogram calls, i.e.
139    --  parameters can be given in any order if named notation is used, and
140    --  positional and named notation can be mixed, subject to the rule that all
141    --  positional parameters must appear first.
142
143    --  Note: All these pragmas are implemented exactly following the DEC design
144    --  and implementation and are intended to be fully compatible with the use
145    --  of these pragmas in the DEC Ada compiler.
146
147    --------------------------------------------
148    -- Checking for Duplicated External Names --
149    --------------------------------------------
150
151    --  It is suspicious if two separate Export pragmas use the same external
152    --  name. The following table is used to diagnose this situation so that
153    --  an appropriate warning can be issued.
154
155    --  The Node_Id stored is for the N_String_Literal node created to hold
156    --  the value of the external name. The Sloc of this node is used to
157    --  cross-reference the location of the duplication.
158
159    package Externals is new Table.Table (
160      Table_Component_Type => Node_Id,
161      Table_Index_Type     => Int,
162      Table_Low_Bound      => 0,
163      Table_Initial        => 100,
164      Table_Increment      => 100,
165      Table_Name           => "Name_Externals");
166
167    -------------------------------------
168    -- Local Subprograms and Variables --
169    -------------------------------------
170
171    function Adjust_External_Name_Case (N : Node_Id) return Node_Id;
172    --  This routine is used for possible casing adjustment of an explicit
173    --  external name supplied as a string literal (the node N), according to
174    --  the casing requirement of Opt.External_Name_Casing. If this is set to
175    --  As_Is, then the string literal is returned unchanged, but if it is set
176    --  to Uppercase or Lowercase, then a new string literal with appropriate
177    --  casing is constructed.
178
179    function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id;
180    --  If Def_Id refers to a renamed subprogram, then the base subprogram (the
181    --  original one, following the renaming chain) is returned. Otherwise the
182    --  entity is returned unchanged. Should be in Einfo???
183
184    procedure Preanalyze_TC_Args (N, Arg_Req, Arg_Ens : Node_Id);
185    --  Preanalyze the boolean expressions in the Requires and Ensures arguments
186    --  of a Test_Case pragma if present (possibly Empty). We treat these as
187    --  spec expressions (i.e. similar to a default expression).
188
189    procedure rv;
190    --  This is a dummy function called by the processing for pragma Reviewable.
191    --  It is there for assisting front end debugging. By placing a Reviewable
192    --  pragma in the source program, a breakpoint on rv catches this place in
193    --  the source, allowing convenient stepping to the point of interest.
194
195    procedure Set_Unit_Name (N : Node_Id; With_Item : Node_Id);
196    --  Place semantic information on the argument of an Elaborate/Elaborate_All
197    --  pragma. Entity name for unit and its parents is taken from item in
198    --  previous with_clause that mentions the unit.
199
200    -------------------------------
201    -- Adjust_External_Name_Case --
202    -------------------------------
203
204    function Adjust_External_Name_Case (N : Node_Id) return Node_Id is
205       CC : Char_Code;
206
207    begin
208       --  Adjust case of literal if required
209
210       if Opt.External_Name_Exp_Casing = As_Is then
211          return N;
212
213       else
214          --  Copy existing string
215
216          Start_String;
217
218          --  Set proper casing
219
220          for J in 1 .. String_Length (Strval (N)) loop
221             CC := Get_String_Char (Strval (N), J);
222
223             if Opt.External_Name_Exp_Casing = Uppercase
224               and then CC >= Get_Char_Code ('a')
225               and then CC <= Get_Char_Code ('z')
226             then
227                Store_String_Char (CC - 32);
228
229             elsif Opt.External_Name_Exp_Casing = Lowercase
230               and then CC >= Get_Char_Code ('A')
231               and then CC <= Get_Char_Code ('Z')
232             then
233                Store_String_Char (CC + 32);
234
235             else
236                Store_String_Char (CC);
237             end if;
238          end loop;
239
240          return
241            Make_String_Literal (Sloc (N),
242              Strval => End_String);
243       end if;
244    end Adjust_External_Name_Case;
245
246    ------------------------------
247    -- Analyze_PPC_In_Decl_Part --
248    ------------------------------
249
250    procedure Analyze_PPC_In_Decl_Part (N : Node_Id; S : Entity_Id) is
251       Arg1 : constant Node_Id := First (Pragma_Argument_Associations (N));
252
253    begin
254       --  Install formals and push subprogram spec onto scope stack so that we
255       --  can see the formals from the pragma.
256
257       Install_Formals (S);
258       Push_Scope (S);
259
260       --  Preanalyze the boolean expression, we treat this as a spec expression
261       --  (i.e. similar to a default expression).
262
263       Preanalyze_Spec_Expression (Get_Pragma_Arg (Arg1), Standard_Boolean);
264
265       --  In ASIS mode, for a pragma generated from a source aspect, also
266       --  analyze the original aspect expression.
267
268       if ASIS_Mode
269         and then Present (Corresponding_Aspect (N))
270       then
271          Preanalyze_Spec_Expression
272            (Expression (Corresponding_Aspect (N)), Standard_Boolean);
273       end if;
274
275       --  For a class-wide condition, a reference to a controlling formal must
276       --  be interpreted as having the class-wide type (or an access to such)
277       --  so that the inherited condition can be properly applied to any
278       --  overriding operation (see ARM12 6.6.1 (7)).
279
280       if Class_Present (N) then
281          declare
282             T   : constant Entity_Id := Find_Dispatching_Type (S);
283
284             ACW : Entity_Id := Empty;
285             --  Access to T'class, created if there is a controlling formal
286             --  that is an access parameter.
287
288             function Get_ACW return Entity_Id;
289             --  If the expression has a reference to an controlling access
290             --  parameter, create an access to T'class for the necessary
291             --  conversions if one does not exist.
292
293             function Process (N : Node_Id) return Traverse_Result;
294             --  ARM 6.1.1: Within the expression for a Pre'Class or Post'Class
295             --  aspect for a primitive subprogram of a tagged type T, a name
296             --  that denotes a formal parameter of type T is interpreted as
297             --  having type T'Class. Similarly, a name that denotes a formal
298             --  accessparameter of type access-to-T is interpreted as having
299             --  type access-to-T'Class. This ensures the expression is well-
300             --  defined for a primitive subprogram of a type descended from T.
301
302             -------------
303             -- Get_ACW --
304             -------------
305
306             function Get_ACW return Entity_Id is
307                Loc  : constant Source_Ptr := Sloc (N);
308                Decl : Node_Id;
309
310             begin
311                if No (ACW) then
312                   Decl := Make_Full_Type_Declaration (Loc,
313                     Defining_Identifier => Make_Temporary (Loc, 'T'),
314                     Type_Definition =>
315                        Make_Access_To_Object_Definition (Loc,
316                        Subtype_Indication =>
317                          New_Occurrence_Of (Class_Wide_Type (T), Loc),
318                        All_Present => True));
319
320                   Insert_Before (Unit_Declaration_Node (S), Decl);
321                   Analyze (Decl);
322                   ACW := Defining_Identifier (Decl);
323                   Freeze_Before (Unit_Declaration_Node (S), ACW);
324                end if;
325
326                return ACW;
327             end Get_ACW;
328
329             -------------
330             -- Process --
331             -------------
332
333             function Process (N : Node_Id) return Traverse_Result is
334                Loc : constant Source_Ptr := Sloc (N);
335                Typ : Entity_Id;
336
337             begin
338                if Is_Entity_Name (N)
339                  and then Is_Formal (Entity (N))
340                  and then Nkind (Parent (N)) /= N_Type_Conversion
341                then
342                   if Etype (Entity (N)) = T then
343                      Typ := Class_Wide_Type (T);
344
345                   elsif Is_Access_Type (Etype (Entity (N)))
346                     and then Designated_Type (Etype (Entity (N))) = T
347                   then
348                      Typ := Get_ACW;
349                   else
350                      Typ := Empty;
351                   end if;
352
353                   if Present (Typ) then
354                      Rewrite (N,
355                        Make_Type_Conversion (Loc,
356                          Subtype_Mark =>
357                            New_Occurrence_Of (Typ, Loc),
358                          Expression  => New_Occurrence_Of (Entity (N), Loc)));
359                      Set_Etype (N, Typ);
360                   end if;
361                end if;
362
363                return OK;
364             end Process;
365
366             procedure Replace_Type is new Traverse_Proc (Process);
367
368          begin
369             Replace_Type (Get_Pragma_Arg (Arg1));
370          end;
371       end if;
372
373       --  Remove the subprogram from the scope stack now that the pre-analysis
374       --  of the precondition/postcondition is done.
375
376       End_Scope;
377    end Analyze_PPC_In_Decl_Part;
378
379    --------------------
380    -- Analyze_Pragma --
381    --------------------
382
383    procedure Analyze_Pragma (N : Node_Id) is
384       Loc     : constant Source_Ptr := Sloc (N);
385       Prag_Id : Pragma_Id;
386
387       Pname : Name_Id;
388       --  Name of the source pragma, or name of the corresponding aspect for
389       --  pragmas which originate in a source aspect. In the latter case, the
390       --  name may be different from the pragma name.
391
392       Pragma_Exit : exception;
393       --  This exception is used to exit pragma processing completely. It is
394       --  used when an error is detected, and no further processing is
395       --  required. It is also used if an earlier error has left the tree in
396       --  a state where the pragma should not be processed.
397
398       Arg_Count : Nat;
399       --  Number of pragma argument associations
400
401       Arg1 : Node_Id;
402       Arg2 : Node_Id;
403       Arg3 : Node_Id;
404       Arg4 : Node_Id;
405       --  First four pragma arguments (pragma argument association nodes, or
406       --  Empty if the corresponding argument does not exist).
407
408       type Name_List is array (Natural range <>) of Name_Id;
409       type Args_List is array (Natural range <>) of Node_Id;
410       --  Types used for arguments to Check_Arg_Order and Gather_Associations
411
412       procedure Ada_2005_Pragma;
413       --  Called for pragmas defined in Ada 2005, that are not in Ada 95. In
414       --  Ada 95 mode, these are implementation defined pragmas, so should be
415       --  caught by the No_Implementation_Pragmas restriction.
416
417       procedure Ada_2012_Pragma;
418       --  Called for pragmas defined in Ada 2012, that are not in Ada 95 or 05.
419       --  In Ada 95 or 05 mode, these are implementation defined pragmas, so
420       --  should be caught by the No_Implementation_Pragmas restriction.
421
422       procedure Check_Ada_83_Warning;
423       --  Issues a warning message for the current pragma if operating in Ada
424       --  83 mode (used for language pragmas that are not a standard part of
425       --  Ada 83). This procedure does not raise Error_Pragma. Also notes use
426       --  of 95 pragma.
427
428       procedure Check_Arg_Count (Required : Nat);
429       --  Check argument count for pragma is equal to given parameter. If not,
430       --  then issue an error message and raise Pragma_Exit.
431
432       --  Note: all routines whose name is Check_Arg_Is_xxx take an argument
433       --  Arg which can either be a pragma argument association, in which case
434       --  the check is applied to the expression of the association or an
435       --  expression directly.
436
437       procedure Check_Arg_Is_External_Name (Arg : Node_Id);
438       --  Check that an argument has the right form for an EXTERNAL_NAME
439       --  parameter of an extended import/export pragma. The rule is that the
440       --  name must be an identifier or string literal (in Ada 83 mode) or a
441       --  static string expression (in Ada 95 mode).
442
443       procedure Check_Arg_Is_Identifier (Arg : Node_Id);
444       --  Check the specified argument Arg to make sure that it is an
445       --  identifier. If not give error and raise Pragma_Exit.
446
447       procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id);
448       --  Check the specified argument Arg to make sure that it is an integer
449       --  literal. If not give error and raise Pragma_Exit.
450
451       procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id);
452       --  Check the specified argument Arg to make sure that it has the proper
453       --  syntactic form for a local name and meets the semantic requirements
454       --  for a local name. The local name is analyzed as part of the
455       --  processing for this call. In addition, the local name is required
456       --  to represent an entity at the library level.
457
458       procedure Check_Arg_Is_Local_Name (Arg : Node_Id);
459       --  Check the specified argument Arg to make sure that it has the proper
460       --  syntactic form for a local name and meets the semantic requirements
461       --  for a local name. The local name is analyzed as part of the
462       --  processing for this call.
463
464       procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id);
465       --  Check the specified argument Arg to make sure that it is a valid
466       --  locking policy name. If not give error and raise Pragma_Exit.
467
468       procedure Check_Arg_Is_One_Of
469         (Arg                : Node_Id;
470          N1, N2             : Name_Id);
471       procedure Check_Arg_Is_One_Of
472         (Arg                : Node_Id;
473          N1, N2, N3         : Name_Id);
474       procedure Check_Arg_Is_One_Of
475         (Arg                : Node_Id;
476          N1, N2, N3, N4     : Name_Id);
477       procedure Check_Arg_Is_One_Of
478         (Arg                : Node_Id;
479          N1, N2, N3, N4, N5 : Name_Id);
480       --  Check the specified argument Arg to make sure that it is an
481       --  identifier whose name matches either N1 or N2 (or N3, N4, N5 if
482       --  present). If not then give error and raise Pragma_Exit.
483
484       procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id);
485       --  Check the specified argument Arg to make sure that it is a valid
486       --  queuing policy name. If not give error and raise Pragma_Exit.
487
488       procedure Check_Arg_Is_Static_Expression
489         (Arg : Node_Id;
490          Typ : Entity_Id := Empty);
491       --  Check the specified argument Arg to make sure that it is a static
492       --  expression of the given type (i.e. it will be analyzed and resolved
493       --  using this type, which can be any valid argument to Resolve, e.g.
494       --  Any_Integer is OK). If not, given error and raise Pragma_Exit. If
495       --  Typ is left Empty, then any static expression is allowed.
496
497       procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id);
498       --  Check the specified argument Arg to make sure that it is a valid task
499       --  dispatching policy name. If not give error and raise Pragma_Exit.
500
501       procedure Check_Arg_Order (Names : Name_List);
502       --  Checks for an instance of two arguments with identifiers for the
503       --  current pragma which are not in the sequence indicated by Names,
504       --  and if so, generates a fatal message about bad order of arguments.
505
506       procedure Check_At_Least_N_Arguments (N : Nat);
507       --  Check there are at least N arguments present
508
509       procedure Check_At_Most_N_Arguments (N : Nat);
510       --  Check there are no more than N arguments present
511
512       procedure Check_Component
513         (Comp            : Node_Id;
514          UU_Typ          : Entity_Id;
515          In_Variant_Part : Boolean := False);
516       --  Examine an Unchecked_Union component for correct use of per-object
517       --  constrained subtypes, and for restrictions on finalizable components.
518       --  UU_Typ is the related Unchecked_Union type. Flag In_Variant_Part
519       --  should be set when Comp comes from a record variant.
520
521       procedure Check_Duplicate_Pragma (E : Entity_Id);
522       --  Check if a pragma of the same name as the current pragma is already
523       --  chained as a rep pragma to the given entity. If so give a message
524       --  about the duplicate, and then raise Pragma_Exit so does not return.
525       --  Also checks for delayed aspect specification node in the chain.
526
527       procedure Check_Duplicated_Export_Name (Nam : Node_Id);
528       --  Nam is an N_String_Literal node containing the external name set by
529       --  an Import or Export pragma (or extended Import or Export pragma).
530       --  This procedure checks for possible duplications if this is the export
531       --  case, and if found, issues an appropriate error message.
532
533       procedure Check_Expr_Is_Static_Expression
534         (Expr : Node_Id;
535          Typ  : Entity_Id := Empty);
536       --  Check the specified expression Expr to make sure that it is a static
537       --  expression of the given type (i.e. it will be analyzed and resolved
538       --  using this type, which can be any valid argument to Resolve, e.g.
539       --  Any_Integer is OK). If not, given error and raise Pragma_Exit. If
540       --  Typ is left Empty, then any static expression is allowed.
541
542       procedure Check_First_Subtype (Arg : Node_Id);
543       --  Checks that Arg, whose expression is an entity name, references a
544       --  first subtype.
545
546       procedure Check_Identifier (Arg : Node_Id; Id : Name_Id);
547       --  Checks that the given argument has an identifier, and if so, requires
548       --  it to match the given identifier name. If there is no identifier, or
549       --  a non-matching identifier, then an error message is given and
550       --  Pragma_Exit is raised.
551
552       procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id);
553       --  Checks that the given argument has an identifier, and if so, requires
554       --  it to match one of the given identifier names. If there is no
555       --  identifier, or a non-matching identifier, then an error message is
556       --  given and Pragma_Exit is raised.
557
558       procedure Check_In_Main_Program;
559       --  Common checks for pragmas that appear within a main program
560       --  (Priority, Main_Storage, Time_Slice, Relative_Deadline, CPU).
561
562       procedure Check_Interrupt_Or_Attach_Handler;
563       --  Common processing for first argument of pragma Interrupt_Handler or
564       --  pragma Attach_Handler.
565
566       procedure Check_Is_In_Decl_Part_Or_Package_Spec;
567       --  Check that pragma appears in a declarative part, or in a package
568       --  specification, i.e. that it does not occur in a statement sequence
569       --  in a body.
570
571       procedure Check_No_Identifier (Arg : Node_Id);
572       --  Checks that the given argument does not have an identifier. If
573       --  an identifier is present, then an error message is issued, and
574       --  Pragma_Exit is raised.
575
576       procedure Check_No_Identifiers;
577       --  Checks that none of the arguments to the pragma has an identifier.
578       --  If any argument has an identifier, then an error message is issued,
579       --  and Pragma_Exit is raised.
580
581       procedure Check_No_Link_Name;
582       --  Checks that no link name is specified
583
584       procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id);
585       --  Checks if the given argument has an identifier, and if so, requires
586       --  it to match the given identifier name. If there is a non-matching
587       --  identifier, then an error message is given and Pragma_Exit is raised.
588
589       procedure Check_Optional_Identifier (Arg : Node_Id; Id : String);
590       --  Checks if the given argument has an identifier, and if so, requires
591       --  it to match the given identifier name. If there is a non-matching
592       --  identifier, then an error message is given and Pragma_Exit is raised.
593       --  In this version of the procedure, the identifier name is given as
594       --  a string with lower case letters.
595
596       procedure Check_Precondition_Postcondition (In_Body : out Boolean);
597       --  Called to process a precondition or postcondition pragma. There are
598       --  three cases:
599       --
600       --    The pragma appears after a subprogram spec
601       --
602       --      If the corresponding check is not enabled, the pragma is analyzed
603       --      but otherwise ignored and control returns with In_Body set False.
604       --
605       --      If the check is enabled, then the first step is to analyze the
606       --      pragma, but this is skipped if the subprogram spec appears within
607       --      a package specification (because this is the case where we delay
608       --      analysis till the end of the spec). Then (whether or not it was
609       --      analyzed), the pragma is chained to the subprogram in question
610       --      (using Spec_PPC_List and Next_Pragma) and control returns to the
611       --      caller with In_Body set False.
612       --
613       --    The pragma appears at the start of subprogram body declarations
614       --
615       --      In this case an immediate return to the caller is made with
616       --      In_Body set True, and the pragma is NOT analyzed.
617       --
618       --    In all other cases, an error message for bad placement is given
619
620       procedure Check_Static_Constraint (Constr : Node_Id);
621       --  Constr is a constraint from an N_Subtype_Indication node from a
622       --  component constraint in an Unchecked_Union type. This routine checks
623       --  that the constraint is static as required by the restrictions for
624       --  Unchecked_Union.
625
626       procedure Check_Test_Case;
627       --  Called to process a test-case pragma. The treatment is similar to the
628       --  one for pre- and postcondition in Check_Precondition_Postcondition,
629       --  except the placement rules for the test-case pragma are stricter.
630       --  This pragma may only occur after a subprogram spec declared directly
631       --  in a package spec unit. In this case, the pragma is chained to the
632       --  subprogram in question (using Spec_TC_List and Next_Pragma) and
633       --  analysis of the pragma is delayed till the end of the spec. In
634       --  all other cases, an error message for bad placement is given.
635
636       procedure Check_Valid_Configuration_Pragma;
637       --  Legality checks for placement of a configuration pragma
638
639       procedure Check_Valid_Library_Unit_Pragma;
640       --  Legality checks for library unit pragmas. A special case arises for
641       --  pragmas in generic instances that come from copies of the original
642       --  library unit pragmas in the generic templates. In the case of other
643       --  than library level instantiations these can appear in contexts which
644       --  would normally be invalid (they only apply to the original template
645       --  and to library level instantiations), and they are simply ignored,
646       --  which is implemented by rewriting them as null statements.
647
648       procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id);
649       --  Check an Unchecked_Union variant for lack of nested variants and
650       --  presence of at least one component. UU_Typ is the related Unchecked_
651       --  Union type.
652
653       procedure Error_Pragma (Msg : String);
654       pragma No_Return (Error_Pragma);
655       --  Outputs error message for current pragma. The message contains a %
656       --  that will be replaced with the pragma name, and the flag is placed
657       --  on the pragma itself. Pragma_Exit is then raised.
658
659       procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id);
660       pragma No_Return (Error_Pragma_Arg);
661       --  Outputs error message for current pragma. The message may contain
662       --  a % that will be replaced with the pragma name. The parameter Arg
663       --  may either be a pragma argument association, in which case the flag
664       --  is placed on the expression of this association, or an expression,
665       --  in which case the flag is placed directly on the expression. The
666       --  message is placed using Error_Msg_N, so the message may also contain
667       --  an & insertion character which will reference the given Arg value.
668       --  After placing the message, Pragma_Exit is raised.
669
670       procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id);
671       pragma No_Return (Error_Pragma_Arg);
672       --  Similar to above form of Error_Pragma_Arg except that two messages
673       --  are provided, the second is a continuation comment starting with \.
674
675       procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id);
676       pragma No_Return (Error_Pragma_Arg_Ident);
677       --  Outputs error message for current pragma. The message may contain
678       --  a % that will be replaced with the pragma name. The parameter Arg
679       --  must be a pragma argument association with a non-empty identifier
680       --  (i.e. its Chars field must be set), and the error message is placed
681       --  on the identifier. The message is placed using Error_Msg_N so
682       --  the message may also contain an & insertion character which will
683       --  reference the identifier. After placing the message, Pragma_Exit
684       --  is raised.
685
686       procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id);
687       pragma No_Return (Error_Pragma_Ref);
688       --  Outputs error message for current pragma. The message may contain
689       --  a % that will be replaced with the pragma name. The parameter Ref
690       --  must be an entity whose name can be referenced by & and sloc by #.
691       --  After placing the message, Pragma_Exit is raised.
692
693       function Find_Lib_Unit_Name return Entity_Id;
694       --  Used for a library unit pragma to find the entity to which the
695       --  library unit pragma applies, returns the entity found.
696
697       procedure Find_Program_Unit_Name (Id : Node_Id);
698       --  If the pragma is a compilation unit pragma, the id must denote the
699       --  compilation unit in the same compilation, and the pragma must appear
700       --  in the list of preceding or trailing pragmas. If it is a program
701       --  unit pragma that is not a compilation unit pragma, then the
702       --  identifier must be visible.
703
704       function Find_Unique_Parameterless_Procedure
705         (Name : Entity_Id;
706          Arg  : Node_Id) return Entity_Id;
707       --  Used for a procedure pragma to find the unique parameterless
708       --  procedure identified by Name, returns it if it exists, otherwise
709       --  errors out and uses Arg as the pragma argument for the message.
710
711       procedure Fix_Error (Msg : in out String);
712       --  This is called prior to issuing an error message. Msg is a string
713       --  that typically contains the substring "pragma". If the current pragma
714       --  comes from an aspect, each such "pragma" substring is replaced with
715       --  the characters "aspect", and if Error_Msg_Name_1 is Name_Precondition
716       --  (resp Name_Postcondition) it is changed to Name_Pre (resp Name_Post).
717
718       procedure Gather_Associations
719         (Names : Name_List;
720          Args  : out Args_List);
721       --  This procedure is used to gather the arguments for a pragma that
722       --  permits arbitrary ordering of parameters using the normal rules
723       --  for named and positional parameters. The Names argument is a list
724       --  of Name_Id values that corresponds to the allowed pragma argument
725       --  association identifiers in order. The result returned in Args is
726       --  a list of corresponding expressions that are the pragma arguments.
727       --  Note that this is a list of expressions, not of pragma argument
728       --  associations (Gather_Associations has completely checked all the
729       --  optional identifiers when it returns). An entry in Args is Empty
730       --  on return if the corresponding argument is not present.
731
732       procedure GNAT_Pragma;
733       --  Called for all GNAT defined pragmas to check the relevant restriction
734       --  (No_Implementation_Pragmas).
735
736       function Is_Before_First_Decl
737         (Pragma_Node : Node_Id;
738          Decls       : List_Id) return Boolean;
739       --  Return True if Pragma_Node is before the first declarative item in
740       --  Decls where Decls is the list of declarative items.
741
742       function Is_Configuration_Pragma return Boolean;
743       --  Determines if the placement of the current pragma is appropriate
744       --  for a configuration pragma.
745
746       function Is_In_Context_Clause return Boolean;
747       --  Returns True if pragma appears within the context clause of a unit,
748       --  and False for any other placement (does not generate any messages).
749
750       function Is_Static_String_Expression (Arg : Node_Id) return Boolean;
751       --  Analyzes the argument, and determines if it is a static string
752       --  expression, returns True if so, False if non-static or not String.
753
754       procedure Pragma_Misplaced;
755       pragma No_Return (Pragma_Misplaced);
756       --  Issue fatal error message for misplaced pragma
757
758       procedure Process_Atomic_Shared_Volatile;
759       --  Common processing for pragmas Atomic, Shared, Volatile. Note that
760       --  Shared is an obsolete Ada 83 pragma, treated as being identical
761       --  in effect to pragma Atomic.
762
763       procedure Process_Compile_Time_Warning_Or_Error;
764       --  Common processing for Compile_Time_Error and Compile_Time_Warning
765
766       procedure Process_Convention
767         (C   : out Convention_Id;
768          Ent : out Entity_Id);
769       --  Common processing for Convention, Interface, Import and Export.
770       --  Checks first two arguments of pragma, and sets the appropriate
771       --  convention value in the specified entity or entities. On return
772       --  C is the convention, Ent is the referenced entity.
773
774       procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id);
775       --  Common processing for Disable/Enable_Atomic_Synchronization. Nam is
776       --  Name_Suppress for Disable and Name_Unsuppress for Enable.
777
778       procedure Process_Extended_Import_Export_Exception_Pragma
779         (Arg_Internal : Node_Id;
780          Arg_External : Node_Id;
781          Arg_Form     : Node_Id;
782          Arg_Code     : Node_Id);
783       --  Common processing for the pragmas Import/Export_Exception. The three
784       --  arguments correspond to the three named parameters of the pragma. An
785       --  argument is empty if the corresponding parameter is not present in
786       --  the pragma.
787
788       procedure Process_Extended_Import_Export_Object_Pragma
789         (Arg_Internal : Node_Id;
790          Arg_External : Node_Id;
791          Arg_Size     : Node_Id);
792       --  Common processing for the pragmas Import/Export_Object. The three
793       --  arguments correspond to the three named parameters of the pragmas. An
794       --  argument is empty if the corresponding parameter is not present in
795       --  the pragma.
796
797       procedure Process_Extended_Import_Export_Internal_Arg
798         (Arg_Internal : Node_Id := Empty);
799       --  Common processing for all extended Import and Export pragmas. The
800       --  argument is the pragma parameter for the Internal argument. If
801       --  Arg_Internal is empty or inappropriate, an error message is posted.
802       --  Otherwise, on normal return, the Entity_Field of Arg_Internal is
803       --  set to identify the referenced entity.
804
805       procedure Process_Extended_Import_Export_Subprogram_Pragma
806         (Arg_Internal                 : Node_Id;
807          Arg_External                 : Node_Id;
808          Arg_Parameter_Types          : Node_Id;
809          Arg_Result_Type              : Node_Id := Empty;
810          Arg_Mechanism                : Node_Id;
811          Arg_Result_Mechanism         : Node_Id := Empty;
812          Arg_First_Optional_Parameter : Node_Id := Empty);
813       --  Common processing for all extended Import and Export pragmas applying
814       --  to subprograms. The caller omits any arguments that do not apply to
815       --  the pragma in question (for example, Arg_Result_Type can be non-Empty
816       --  only in the Import_Function and Export_Function cases). The argument
817       --  names correspond to the allowed pragma association identifiers.
818
819       procedure Process_Generic_List;
820       --  Common processing for Share_Generic and Inline_Generic
821
822       procedure Process_Import_Or_Interface;
823       --  Common processing for Import of Interface
824
825       procedure Process_Import_Predefined_Type;
826       --  Processing for completing a type with pragma Import. This is used
827       --  to declare types that match predefined C types, especially for cases
828       --  without corresponding Ada predefined type.
829
830       procedure Process_Inline (Active : Boolean);
831       --  Common processing for Inline and Inline_Always. The parameter
832       --  indicates if the inline pragma is active, i.e. if it should actually
833       --  cause inlining to occur.
834
835       procedure Process_Interface_Name
836         (Subprogram_Def : Entity_Id;
837          Ext_Arg        : Node_Id;
838          Link_Arg       : Node_Id);
839       --  Given the last two arguments of pragma Import, pragma Export, or
840       --  pragma Interface_Name, performs validity checks and sets the
841       --  Interface_Name field of the given subprogram entity to the
842       --  appropriate external or link name, depending on the arguments given.
843       --  Ext_Arg is always present, but Link_Arg may be missing. Note that
844       --  Ext_Arg may represent the Link_Name if Link_Arg is missing, and
845       --  appropriate named notation is used for Ext_Arg. If neither Ext_Arg
846       --  nor Link_Arg is present, the interface name is set to the default
847       --  from the subprogram name.
848
849       procedure Process_Interrupt_Or_Attach_Handler;
850       --  Common processing for Interrupt and Attach_Handler pragmas
851
852       procedure Process_Restrictions_Or_Restriction_Warnings (Warn : Boolean);
853       --  Common processing for Restrictions and Restriction_Warnings pragmas.
854       --  Warn is True for Restriction_Warnings, or for Restrictions if the
855       --  flag Treat_Restrictions_As_Warnings is set, and False if this flag
856       --  is not set in the Restrictions case.
857
858       procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean);
859       --  Common processing for Suppress and Unsuppress. The boolean parameter
860       --  Suppress_Case is True for the Suppress case, and False for the
861       --  Unsuppress case.
862
863       procedure Set_Exported (E : Entity_Id; Arg : Node_Id);
864       --  This procedure sets the Is_Exported flag for the given entity,
865       --  checking that the entity was not previously imported. Arg is
866       --  the argument that specified the entity. A check is also made
867       --  for exporting inappropriate entities.
868
869       procedure Set_Extended_Import_Export_External_Name
870         (Internal_Ent : Entity_Id;
871          Arg_External : Node_Id);
872       --  Common processing for all extended import export pragmas. The first
873       --  argument, Internal_Ent, is the internal entity, which has already
874       --  been checked for validity by the caller. Arg_External is from the
875       --  Import or Export pragma, and may be null if no External parameter
876       --  was present. If Arg_External is present and is a non-null string
877       --  (a null string is treated as the default), then the Interface_Name
878       --  field of Internal_Ent is set appropriately.
879
880       procedure Set_Imported (E : Entity_Id);
881       --  This procedure sets the Is_Imported flag for the given entity,
882       --  checking that it is not previously exported or imported.
883
884       procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id);
885       --  Mech is a parameter passing mechanism (see Import_Function syntax
886       --  for MECHANISM_NAME). This routine checks that the mechanism argument
887       --  has the right form, and if not issues an error message. If the
888       --  argument has the right form then the Mechanism field of Ent is
889       --  set appropriately.
890
891       procedure Set_Ravenscar_Profile (N : Node_Id);
892       --  Activate the set of configuration pragmas and restrictions that make
893       --  up the Ravenscar Profile. N is the corresponding pragma node, which
894       --  is used for error messages on any constructs that violate the
895       --  profile.
896
897       ---------------------
898       -- Ada_2005_Pragma --
899       ---------------------
900
901       procedure Ada_2005_Pragma is
902       begin
903          if Ada_Version <= Ada_95 then
904             Check_Restriction (No_Implementation_Pragmas, N);
905          end if;
906       end Ada_2005_Pragma;
907
908       ---------------------
909       -- Ada_2012_Pragma --
910       ---------------------
911
912       procedure Ada_2012_Pragma is
913       begin
914          if Ada_Version <= Ada_2005 then
915             Check_Restriction (No_Implementation_Pragmas, N);
916          end if;
917       end Ada_2012_Pragma;
918
919       --------------------------
920       -- Check_Ada_83_Warning --
921       --------------------------
922
923       procedure Check_Ada_83_Warning is
924       begin
925          if Ada_Version = Ada_83 and then Comes_From_Source (N) then
926             Error_Msg_N ("(Ada 83) pragma& is non-standard?", N);
927          end if;
928       end Check_Ada_83_Warning;
929
930       ---------------------
931       -- Check_Arg_Count --
932       ---------------------
933
934       procedure Check_Arg_Count (Required : Nat) is
935       begin
936          if Arg_Count /= Required then
937             Error_Pragma ("wrong number of arguments for pragma%");
938          end if;
939       end Check_Arg_Count;
940
941       --------------------------------
942       -- Check_Arg_Is_External_Name --
943       --------------------------------
944
945       procedure Check_Arg_Is_External_Name (Arg : Node_Id) is
946          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
947
948       begin
949          if Nkind (Argx) = N_Identifier then
950             return;
951
952          else
953             Analyze_And_Resolve (Argx, Standard_String);
954
955             if Is_OK_Static_Expression (Argx) then
956                return;
957
958             elsif Etype (Argx) = Any_Type then
959                raise Pragma_Exit;
960
961             --  An interesting special case, if we have a string literal and
962             --  we are in Ada 83 mode, then we allow it even though it will
963             --  not be flagged as static. This allows expected Ada 83 mode
964             --  use of external names which are string literals, even though
965             --  technically these are not static in Ada 83.
966
967             elsif Ada_Version = Ada_83
968               and then Nkind (Argx) = N_String_Literal
969             then
970                return;
971
972             --  Static expression that raises Constraint_Error. This has
973             --  already been flagged, so just exit from pragma processing.
974
975             elsif Is_Static_Expression (Argx) then
976                raise Pragma_Exit;
977
978             --  Here we have a real error (non-static expression)
979
980             else
981                Error_Msg_Name_1 := Pname;
982
983                declare
984                   Msg : String :=
985                           "argument for pragma% must be a identifier or "
986                           & "static string expression!";
987                begin
988                   Fix_Error (Msg);
989                   Flag_Non_Static_Expr (Msg, Argx);
990                   raise Pragma_Exit;
991                end;
992             end if;
993          end if;
994       end Check_Arg_Is_External_Name;
995
996       -----------------------------
997       -- Check_Arg_Is_Identifier --
998       -----------------------------
999
1000       procedure Check_Arg_Is_Identifier (Arg : Node_Id) is
1001          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1002       begin
1003          if Nkind (Argx) /= N_Identifier then
1004             Error_Pragma_Arg
1005               ("argument for pragma% must be identifier", Argx);
1006          end if;
1007       end Check_Arg_Is_Identifier;
1008
1009       ----------------------------------
1010       -- Check_Arg_Is_Integer_Literal --
1011       ----------------------------------
1012
1013       procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id) is
1014          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1015       begin
1016          if Nkind (Argx) /= N_Integer_Literal then
1017             Error_Pragma_Arg
1018               ("argument for pragma% must be integer literal", Argx);
1019          end if;
1020       end Check_Arg_Is_Integer_Literal;
1021
1022       -------------------------------------------
1023       -- Check_Arg_Is_Library_Level_Local_Name --
1024       -------------------------------------------
1025
1026       --  LOCAL_NAME ::=
1027       --    DIRECT_NAME
1028       --  | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
1029       --  | library_unit_NAME
1030
1031       procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id) is
1032       begin
1033          Check_Arg_Is_Local_Name (Arg);
1034
1035          if not Is_Library_Level_Entity (Entity (Get_Pragma_Arg (Arg)))
1036            and then Comes_From_Source (N)
1037          then
1038             Error_Pragma_Arg
1039               ("argument for pragma% must be library level entity", Arg);
1040          end if;
1041       end Check_Arg_Is_Library_Level_Local_Name;
1042
1043       -----------------------------
1044       -- Check_Arg_Is_Local_Name --
1045       -----------------------------
1046
1047       --  LOCAL_NAME ::=
1048       --    DIRECT_NAME
1049       --  | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
1050       --  | library_unit_NAME
1051
1052       procedure Check_Arg_Is_Local_Name (Arg : Node_Id) is
1053          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1054
1055       begin
1056          Analyze (Argx);
1057
1058          if Nkind (Argx) not in N_Direct_Name
1059            and then (Nkind (Argx) /= N_Attribute_Reference
1060                       or else Present (Expressions (Argx))
1061                       or else Nkind (Prefix (Argx)) /= N_Identifier)
1062            and then (not Is_Entity_Name (Argx)
1063                       or else not Is_Compilation_Unit (Entity (Argx)))
1064          then
1065             Error_Pragma_Arg ("argument for pragma% must be local name", Argx);
1066          end if;
1067
1068          --  No further check required if not an entity name
1069
1070          if not Is_Entity_Name (Argx) then
1071             null;
1072
1073          else
1074             declare
1075                OK   : Boolean;
1076                Ent  : constant Entity_Id := Entity (Argx);
1077                Scop : constant Entity_Id := Scope (Ent);
1078             begin
1079                --  Case of a pragma applied to a compilation unit: pragma must
1080                --  occur immediately after the program unit in the compilation.
1081
1082                if Is_Compilation_Unit (Ent) then
1083                   declare
1084                      Decl : constant Node_Id := Unit_Declaration_Node (Ent);
1085
1086                   begin
1087                      --  Case of pragma placed immediately after spec
1088
1089                      if Parent (N) = Aux_Decls_Node (Parent (Decl)) then
1090                         OK := True;
1091
1092                      --  Case of pragma placed immediately after body
1093
1094                      elsif Nkind (Decl) = N_Subprogram_Declaration
1095                              and then Present (Corresponding_Body (Decl))
1096                      then
1097                         OK := Parent (N) =
1098                                 Aux_Decls_Node
1099                                   (Parent (Unit_Declaration_Node
1100                                              (Corresponding_Body (Decl))));
1101
1102                      --  All other cases are illegal
1103
1104                      else
1105                         OK := False;
1106                      end if;
1107                   end;
1108
1109                --  Special restricted placement rule from 10.2.1(11.8/2)
1110
1111                elsif Is_Generic_Formal (Ent)
1112                        and then Prag_Id = Pragma_Preelaborable_Initialization
1113                then
1114                   OK := List_Containing (N) =
1115                           Generic_Formal_Declarations
1116                             (Unit_Declaration_Node (Scop));
1117
1118                --  Default case, just check that the pragma occurs in the scope
1119                --  of the entity denoted by the name.
1120
1121                else
1122                   OK := Current_Scope = Scop;
1123                end if;
1124
1125                if not OK then
1126                   Error_Pragma_Arg
1127                     ("pragma% argument must be in same declarative part", Arg);
1128                end if;
1129             end;
1130          end if;
1131       end Check_Arg_Is_Local_Name;
1132
1133       ---------------------------------
1134       -- Check_Arg_Is_Locking_Policy --
1135       ---------------------------------
1136
1137       procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id) is
1138          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1139
1140       begin
1141          Check_Arg_Is_Identifier (Argx);
1142
1143          if not Is_Locking_Policy_Name (Chars (Argx)) then
1144             Error_Pragma_Arg ("& is not a valid locking policy name", Argx);
1145          end if;
1146       end Check_Arg_Is_Locking_Policy;
1147
1148       -------------------------
1149       -- Check_Arg_Is_One_Of --
1150       -------------------------
1151
1152       procedure Check_Arg_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
1153          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1154
1155       begin
1156          Check_Arg_Is_Identifier (Argx);
1157
1158          if Chars (Argx) /= N1 and then Chars (Argx) /= N2 then
1159             Error_Msg_Name_2 := N1;
1160             Error_Msg_Name_3 := N2;
1161             Error_Pragma_Arg ("argument for pragma% must be% or%", Argx);
1162          end if;
1163       end Check_Arg_Is_One_Of;
1164
1165       procedure Check_Arg_Is_One_Of
1166         (Arg        : Node_Id;
1167          N1, N2, N3 : Name_Id)
1168       is
1169          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1170
1171       begin
1172          Check_Arg_Is_Identifier (Argx);
1173
1174          if Chars (Argx) /= N1
1175            and then Chars (Argx) /= N2
1176            and then Chars (Argx) /= N3
1177          then
1178             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1179          end if;
1180       end Check_Arg_Is_One_Of;
1181
1182       procedure Check_Arg_Is_One_Of
1183         (Arg                : Node_Id;
1184          N1, N2, N3, N4     : Name_Id)
1185       is
1186          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1187
1188       begin
1189          Check_Arg_Is_Identifier (Argx);
1190
1191          if Chars (Argx) /= N1
1192            and then Chars (Argx) /= N2
1193            and then Chars (Argx) /= N3
1194            and then Chars (Argx) /= N4
1195          then
1196             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1197          end if;
1198       end Check_Arg_Is_One_Of;
1199
1200       procedure Check_Arg_Is_One_Of
1201         (Arg                : Node_Id;
1202          N1, N2, N3, N4, N5 : Name_Id)
1203       is
1204          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1205
1206       begin
1207          Check_Arg_Is_Identifier (Argx);
1208
1209          if Chars (Argx) /= N1
1210            and then Chars (Argx) /= N2
1211            and then Chars (Argx) /= N3
1212            and then Chars (Argx) /= N4
1213            and then Chars (Argx) /= N5
1214          then
1215             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1216          end if;
1217       end Check_Arg_Is_One_Of;
1218       ---------------------------------
1219       -- Check_Arg_Is_Queuing_Policy --
1220       ---------------------------------
1221
1222       procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id) is
1223          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1224
1225       begin
1226          Check_Arg_Is_Identifier (Argx);
1227
1228          if not Is_Queuing_Policy_Name (Chars (Argx)) then
1229             Error_Pragma_Arg ("& is not a valid queuing policy name", Argx);
1230          end if;
1231       end Check_Arg_Is_Queuing_Policy;
1232
1233       ------------------------------------
1234       -- Check_Arg_Is_Static_Expression --
1235       ------------------------------------
1236
1237       procedure Check_Arg_Is_Static_Expression
1238         (Arg : Node_Id;
1239          Typ : Entity_Id := Empty)
1240       is
1241       begin
1242          Check_Expr_Is_Static_Expression (Get_Pragma_Arg (Arg), Typ);
1243       end Check_Arg_Is_Static_Expression;
1244
1245       ------------------------------------------
1246       -- Check_Arg_Is_Task_Dispatching_Policy --
1247       ------------------------------------------
1248
1249       procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id) is
1250          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1251
1252       begin
1253          Check_Arg_Is_Identifier (Argx);
1254
1255          if not Is_Task_Dispatching_Policy_Name (Chars (Argx)) then
1256             Error_Pragma_Arg
1257               ("& is not a valid task dispatching policy name", Argx);
1258          end if;
1259       end Check_Arg_Is_Task_Dispatching_Policy;
1260
1261       ---------------------
1262       -- Check_Arg_Order --
1263       ---------------------
1264
1265       procedure Check_Arg_Order (Names : Name_List) is
1266          Arg : Node_Id;
1267
1268          Highest_So_Far : Natural := 0;
1269          --  Highest index in Names seen do far
1270
1271       begin
1272          Arg := Arg1;
1273          for J in 1 .. Arg_Count loop
1274             if Chars (Arg) /= No_Name then
1275                for K in Names'Range loop
1276                   if Chars (Arg) = Names (K) then
1277                      if K < Highest_So_Far then
1278                         Error_Msg_Name_1 := Pname;
1279                         Error_Msg_N
1280                           ("parameters out of order for pragma%", Arg);
1281                         Error_Msg_Name_1 := Names (K);
1282                         Error_Msg_Name_2 := Names (Highest_So_Far);
1283                         Error_Msg_N ("\% must appear before %", Arg);
1284                         raise Pragma_Exit;
1285
1286                      else
1287                         Highest_So_Far := K;
1288                      end if;
1289                   end if;
1290                end loop;
1291             end if;
1292
1293             Arg := Next (Arg);
1294          end loop;
1295       end Check_Arg_Order;
1296
1297       --------------------------------
1298       -- Check_At_Least_N_Arguments --
1299       --------------------------------
1300
1301       procedure Check_At_Least_N_Arguments (N : Nat) is
1302       begin
1303          if Arg_Count < N then
1304             Error_Pragma ("too few arguments for pragma%");
1305          end if;
1306       end Check_At_Least_N_Arguments;
1307
1308       -------------------------------
1309       -- Check_At_Most_N_Arguments --
1310       -------------------------------
1311
1312       procedure Check_At_Most_N_Arguments (N : Nat) is
1313          Arg : Node_Id;
1314       begin
1315          if Arg_Count > N then
1316             Arg := Arg1;
1317             for J in 1 .. N loop
1318                Next (Arg);
1319                Error_Pragma_Arg ("too many arguments for pragma%", Arg);
1320             end loop;
1321          end if;
1322       end Check_At_Most_N_Arguments;
1323
1324       ---------------------
1325       -- Check_Component --
1326       ---------------------
1327
1328       procedure Check_Component
1329         (Comp            : Node_Id;
1330          UU_Typ          : Entity_Id;
1331          In_Variant_Part : Boolean := False)
1332       is
1333          Comp_Id : constant Entity_Id := Defining_Identifier (Comp);
1334          Sindic  : constant Node_Id :=
1335                      Subtype_Indication (Component_Definition (Comp));
1336          Typ     : constant Entity_Id := Etype (Comp_Id);
1337
1338       begin
1339          --  Ada 2005 (AI-216): If a component subtype is subject to a per-
1340          --  object constraint, then the component type shall be an Unchecked_
1341          --  Union.
1342
1343          if Nkind (Sindic) = N_Subtype_Indication
1344            and then Has_Per_Object_Constraint (Comp_Id)
1345            and then not Is_Unchecked_Union (Etype (Subtype_Mark (Sindic)))
1346          then
1347             Error_Msg_N
1348               ("component subtype subject to per-object constraint " &
1349                "must be an Unchecked_Union", Comp);
1350
1351          --  Ada 2012 (AI05-0026): For an unchecked union type declared within
1352          --  the body of a generic unit, or within the body of any of its
1353          --  descendant library units, no part of the type of a component
1354          --  declared in a variant_part of the unchecked union type shall be of
1355          --  a formal private type or formal private extension declared within
1356          --  the formal part of the generic unit.
1357
1358          elsif Ada_Version >= Ada_2012
1359            and then In_Generic_Body (UU_Typ)
1360            and then In_Variant_Part
1361            and then Is_Private_Type (Typ)
1362            and then Is_Generic_Type (Typ)
1363          then
1364             Error_Msg_N
1365               ("component of Unchecked_Union cannot be of generic type", Comp);
1366
1367          elsif Needs_Finalization (Typ) then
1368             Error_Msg_N
1369               ("component of Unchecked_Union cannot be controlled", Comp);
1370
1371          elsif Has_Task (Typ) then
1372             Error_Msg_N
1373               ("component of Unchecked_Union cannot have tasks", Comp);
1374          end if;
1375       end Check_Component;
1376
1377       ----------------------------
1378       -- Check_Duplicate_Pragma --
1379       ----------------------------
1380
1381       procedure Check_Duplicate_Pragma (E : Entity_Id) is
1382          P : Node_Id;
1383
1384       begin
1385          --  Nothing to do if this pragma comes from an aspect specification,
1386          --  since we could not be duplicating a pragma, and we dealt with the
1387          --  case of duplicated aspects in Analyze_Aspect_Specifications.
1388
1389          if From_Aspect_Specification (N) then
1390             return;
1391          end if;
1392
1393          --  Otherwise current pragma may duplicate previous pragma or a
1394          --  previously given aspect specification for the same pragma.
1395
1396          P := Get_Rep_Item_For_Entity (E, Pragma_Name (N));
1397
1398          if Present (P) then
1399             Error_Msg_Name_1 := Pragma_Name (N);
1400             Error_Msg_Sloc := Sloc (P);
1401
1402             if Nkind (P) = N_Aspect_Specification
1403               or else From_Aspect_Specification (P)
1404             then
1405                Error_Msg_NE ("aspect% for & previously given#", N, E);
1406             else
1407                Error_Msg_NE ("pragma% for & duplicates pragma#", N, E);
1408             end if;
1409
1410             raise Pragma_Exit;
1411          end if;
1412       end Check_Duplicate_Pragma;
1413
1414       ----------------------------------
1415       -- Check_Duplicated_Export_Name --
1416       ----------------------------------
1417
1418       procedure Check_Duplicated_Export_Name (Nam : Node_Id) is
1419          String_Val : constant String_Id := Strval (Nam);
1420
1421       begin
1422          --  We are only interested in the export case, and in the case of
1423          --  generics, it is the instance, not the template, that is the
1424          --  problem (the template will generate a warning in any case).
1425
1426          if not Inside_A_Generic
1427            and then (Prag_Id = Pragma_Export
1428                        or else
1429                      Prag_Id = Pragma_Export_Procedure
1430                        or else
1431                      Prag_Id = Pragma_Export_Valued_Procedure
1432                        or else
1433                      Prag_Id = Pragma_Export_Function)
1434          then
1435             for J in Externals.First .. Externals.Last loop
1436                if String_Equal (String_Val, Strval (Externals.Table (J))) then
1437                   Error_Msg_Sloc := Sloc (Externals.Table (J));
1438                   Error_Msg_N ("external name duplicates name given#", Nam);
1439                   exit;
1440                end if;
1441             end loop;
1442
1443             Externals.Append (Nam);
1444          end if;
1445       end Check_Duplicated_Export_Name;
1446
1447       -------------------------------------
1448       -- Check_Expr_Is_Static_Expression --
1449       -------------------------------------
1450
1451       procedure Check_Expr_Is_Static_Expression
1452         (Expr : Node_Id;
1453          Typ  : Entity_Id := Empty)
1454       is
1455       begin
1456          if Present (Typ) then
1457             Analyze_And_Resolve (Expr, Typ);
1458          else
1459             Analyze_And_Resolve (Expr);
1460          end if;
1461
1462          if Is_OK_Static_Expression (Expr) then
1463             return;
1464
1465          elsif Etype (Expr) = Any_Type then
1466             raise Pragma_Exit;
1467
1468          --  An interesting special case, if we have a string literal and we
1469          --  are in Ada 83 mode, then we allow it even though it will not be
1470          --  flagged as static. This allows the use of Ada 95 pragmas like
1471          --  Import in Ada 83 mode. They will of course be flagged with
1472          --  warnings as usual, but will not cause errors.
1473
1474          elsif Ada_Version = Ada_83
1475            and then Nkind (Expr) = N_String_Literal
1476          then
1477             return;
1478
1479          --  Static expression that raises Constraint_Error. This has already
1480          --  been flagged, so just exit from pragma processing.
1481
1482          elsif Is_Static_Expression (Expr) then
1483             raise Pragma_Exit;
1484
1485          --  Finally, we have a real error
1486
1487          else
1488             Error_Msg_Name_1 := Pname;
1489
1490             declare
1491                Msg : String :=
1492                        "argument for pragma% must be a static expression!";
1493             begin
1494                Fix_Error (Msg);
1495                Flag_Non_Static_Expr (Msg, Expr);
1496             end;
1497
1498             raise Pragma_Exit;
1499          end if;
1500       end Check_Expr_Is_Static_Expression;
1501
1502       -------------------------
1503       -- Check_First_Subtype --
1504       -------------------------
1505
1506       procedure Check_First_Subtype (Arg : Node_Id) is
1507          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1508          Ent  : constant Entity_Id := Entity (Argx);
1509
1510       begin
1511          if Is_First_Subtype (Ent) then
1512             null;
1513
1514          elsif Is_Type (Ent) then
1515             Error_Pragma_Arg
1516               ("pragma% cannot apply to subtype", Argx);
1517
1518          elsif Is_Object (Ent) then
1519             Error_Pragma_Arg
1520               ("pragma% cannot apply to object, requires a type", Argx);
1521
1522          else
1523             Error_Pragma_Arg
1524               ("pragma% cannot apply to&, requires a type", Argx);
1525          end if;
1526       end Check_First_Subtype;
1527
1528       ----------------------
1529       -- Check_Identifier --
1530       ----------------------
1531
1532       procedure Check_Identifier (Arg : Node_Id; Id : Name_Id) is
1533       begin
1534          if Present (Arg)
1535            and then Nkind (Arg) = N_Pragma_Argument_Association
1536          then
1537             if Chars (Arg) = No_Name or else Chars (Arg) /= Id then
1538                Error_Msg_Name_1 := Pname;
1539                Error_Msg_Name_2 := Id;
1540                Error_Msg_N ("pragma% argument expects identifier%", Arg);
1541                raise Pragma_Exit;
1542             end if;
1543          end if;
1544       end Check_Identifier;
1545
1546       --------------------------------
1547       -- Check_Identifier_Is_One_Of --
1548       --------------------------------
1549
1550       procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
1551       begin
1552          if Present (Arg)
1553            and then Nkind (Arg) = N_Pragma_Argument_Association
1554          then
1555             if Chars (Arg) = No_Name then
1556                Error_Msg_Name_1 := Pname;
1557                Error_Msg_N ("pragma% argument expects an identifier", Arg);
1558                raise Pragma_Exit;
1559
1560             elsif Chars (Arg) /= N1
1561               and then Chars (Arg) /= N2
1562             then
1563                Error_Msg_Name_1 := Pname;
1564                Error_Msg_N ("invalid identifier for pragma% argument", Arg);
1565                raise Pragma_Exit;
1566             end if;
1567          end if;
1568       end Check_Identifier_Is_One_Of;
1569
1570       ---------------------------
1571       -- Check_In_Main_Program --
1572       ---------------------------
1573
1574       procedure Check_In_Main_Program is
1575          P : constant Node_Id := Parent (N);
1576
1577       begin
1578          --  Must be at in subprogram body
1579
1580          if Nkind (P) /= N_Subprogram_Body then
1581             Error_Pragma ("% pragma allowed only in subprogram");
1582
1583          --  Otherwise warn if obviously not main program
1584
1585          elsif Present (Parameter_Specifications (Specification (P)))
1586            or else not Is_Compilation_Unit (Defining_Entity (P))
1587          then
1588             Error_Msg_Name_1 := Pname;
1589             Error_Msg_N
1590               ("?pragma% is only effective in main program", N);
1591          end if;
1592       end Check_In_Main_Program;
1593
1594       ---------------------------------------
1595       -- Check_Interrupt_Or_Attach_Handler --
1596       ---------------------------------------
1597
1598       procedure Check_Interrupt_Or_Attach_Handler is
1599          Arg1_X : constant Node_Id := Get_Pragma_Arg (Arg1);
1600          Handler_Proc, Proc_Scope : Entity_Id;
1601
1602       begin
1603          Analyze (Arg1_X);
1604
1605          if Prag_Id = Pragma_Interrupt_Handler then
1606             Check_Restriction (No_Dynamic_Attachment, N);
1607          end if;
1608
1609          Handler_Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
1610          Proc_Scope := Scope (Handler_Proc);
1611
1612          --  On AAMP only, a pragma Interrupt_Handler is supported for
1613          --  nonprotected parameterless procedures.
1614
1615          if not AAMP_On_Target
1616            or else Prag_Id = Pragma_Attach_Handler
1617          then
1618             if Ekind (Proc_Scope) /= E_Protected_Type then
1619                Error_Pragma_Arg
1620                  ("argument of pragma% must be protected procedure", Arg1);
1621             end if;
1622
1623             if Parent (N) /= Protected_Definition (Parent (Proc_Scope)) then
1624                Error_Pragma ("pragma% must be in protected definition");
1625             end if;
1626          end if;
1627
1628          if not Is_Library_Level_Entity (Proc_Scope)
1629            or else (AAMP_On_Target
1630                      and then not Is_Library_Level_Entity (Handler_Proc))
1631          then
1632             Error_Pragma_Arg
1633               ("argument for pragma% must be library level entity", Arg1);
1634          end if;
1635
1636          --  AI05-0033: A pragma cannot appear within a generic body, because
1637          --  instance can be in a nested scope. The check that protected type
1638          --  is itself a library-level declaration is done elsewhere.
1639
1640          --  Note: we omit this check in Codepeer mode to properly handle code
1641          --  prior to AI-0033 (pragmas don't matter to codepeer in any case).
1642
1643          if Inside_A_Generic then
1644             if Ekind (Scope (Current_Scope)) = E_Generic_Package
1645               and then In_Package_Body (Scope (Current_Scope))
1646               and then not CodePeer_Mode
1647             then
1648                Error_Pragma ("pragma% cannot be used inside a generic");
1649             end if;
1650          end if;
1651       end Check_Interrupt_Or_Attach_Handler;
1652
1653       -------------------------------------------
1654       -- Check_Is_In_Decl_Part_Or_Package_Spec --
1655       -------------------------------------------
1656
1657       procedure Check_Is_In_Decl_Part_Or_Package_Spec is
1658          P : Node_Id;
1659
1660       begin
1661          P := Parent (N);
1662          loop
1663             if No (P) then
1664                exit;
1665
1666             elsif Nkind (P) = N_Handled_Sequence_Of_Statements then
1667                exit;
1668
1669             elsif Nkind_In (P, N_Package_Specification,
1670                                N_Block_Statement)
1671             then
1672                return;
1673
1674             --  Note: the following tests seem a little peculiar, because
1675             --  they test for bodies, but if we were in the statement part
1676             --  of the body, we would already have hit the handled statement
1677             --  sequence, so the only way we get here is by being in the
1678             --  declarative part of the body.
1679
1680             elsif Nkind_In (P, N_Subprogram_Body,
1681                                N_Package_Body,
1682                                N_Task_Body,
1683                                N_Entry_Body)
1684             then
1685                return;
1686             end if;
1687
1688             P := Parent (P);
1689          end loop;
1690
1691          Error_Pragma ("pragma% is not in declarative part or package spec");
1692       end Check_Is_In_Decl_Part_Or_Package_Spec;
1693
1694       -------------------------
1695       -- Check_No_Identifier --
1696       -------------------------
1697
1698       procedure Check_No_Identifier (Arg : Node_Id) is
1699       begin
1700          if Nkind (Arg) = N_Pragma_Argument_Association
1701            and then Chars (Arg) /= No_Name
1702          then
1703             Error_Pragma_Arg_Ident
1704               ("pragma% does not permit identifier& here", Arg);
1705          end if;
1706       end Check_No_Identifier;
1707
1708       --------------------------
1709       -- Check_No_Identifiers --
1710       --------------------------
1711
1712       procedure Check_No_Identifiers is
1713          Arg_Node : Node_Id;
1714       begin
1715          if Arg_Count > 0 then
1716             Arg_Node := Arg1;
1717             while Present (Arg_Node) loop
1718                Check_No_Identifier (Arg_Node);
1719                Next (Arg_Node);
1720             end loop;
1721          end if;
1722       end Check_No_Identifiers;
1723
1724       ------------------------
1725       -- Check_No_Link_Name --
1726       ------------------------
1727
1728       procedure Check_No_Link_Name is
1729       begin
1730          if Present (Arg3)
1731            and then Chars (Arg3) = Name_Link_Name
1732          then
1733             Arg4 := Arg3;
1734          end if;
1735
1736          if Present (Arg4) then
1737             Error_Pragma_Arg
1738               ("Link_Name argument not allowed for Import Intrinsic", Arg4);
1739          end if;
1740       end Check_No_Link_Name;
1741
1742       -------------------------------
1743       -- Check_Optional_Identifier --
1744       -------------------------------
1745
1746       procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id) is
1747       begin
1748          if Present (Arg)
1749            and then Nkind (Arg) = N_Pragma_Argument_Association
1750            and then Chars (Arg) /= No_Name
1751          then
1752             if Chars (Arg) /= Id then
1753                Error_Msg_Name_1 := Pname;
1754                Error_Msg_Name_2 := Id;
1755                Error_Msg_N ("pragma% argument expects identifier%", Arg);
1756                raise Pragma_Exit;
1757             end if;
1758          end if;
1759       end Check_Optional_Identifier;
1760
1761       procedure Check_Optional_Identifier (Arg : Node_Id; Id : String) is
1762       begin
1763          Name_Buffer (1 .. Id'Length) := Id;
1764          Name_Len := Id'Length;
1765          Check_Optional_Identifier (Arg, Name_Find);
1766       end Check_Optional_Identifier;
1767
1768       --------------------------------------
1769       -- Check_Precondition_Postcondition --
1770       --------------------------------------
1771
1772       procedure Check_Precondition_Postcondition (In_Body : out Boolean) is
1773          P  : Node_Id;
1774          PO : Node_Id;
1775
1776          procedure Chain_PPC (PO : Node_Id);
1777          --  If PO is an entry or a [generic] subprogram declaration node, then
1778          --  the precondition/postcondition applies to this subprogram and the
1779          --  processing for the pragma is completed. Otherwise the pragma is
1780          --  misplaced.
1781
1782          ---------------
1783          -- Chain_PPC --
1784          ---------------
1785
1786          procedure Chain_PPC (PO : Node_Id) is
1787             S   : Entity_Id;
1788             P   : Node_Id;
1789
1790          begin
1791             if Nkind (PO) = N_Abstract_Subprogram_Declaration then
1792                if not From_Aspect_Specification (N) then
1793                   Error_Pragma
1794                     ("pragma% cannot be applied to abstract subprogram");
1795
1796                elsif Class_Present (N) then
1797                   null;
1798
1799                else
1800                   Error_Pragma
1801                     ("aspect % requires ''Class for abstract subprogram");
1802                end if;
1803
1804             --  AI05-0230: The same restriction applies to null procedures. For
1805             --  compatibility with earlier uses of the Ada pragma, apply this
1806             --  rule only to aspect specifications.
1807
1808             --  The above discrpency needs documentation. Robert is dubious
1809             --  about whether it is a good idea ???
1810
1811             elsif Nkind (PO) = N_Subprogram_Declaration
1812               and then Nkind (Specification (PO)) = N_Procedure_Specification
1813               and then Null_Present (Specification (PO))
1814               and then From_Aspect_Specification (N)
1815               and then not Class_Present (N)
1816             then
1817                Error_Pragma
1818                  ("aspect % requires ''Class for null procedure");
1819
1820             elsif not Nkind_In (PO, N_Subprogram_Declaration,
1821                                     N_Expression_Function,
1822                                     N_Generic_Subprogram_Declaration,
1823                                     N_Entry_Declaration)
1824             then
1825                Pragma_Misplaced;
1826             end if;
1827
1828             --  Here if we have [generic] subprogram or entry declaration
1829
1830             if Nkind (PO) = N_Entry_Declaration then
1831                S := Defining_Entity (PO);
1832             else
1833                S := Defining_Unit_Name (Specification (PO));
1834             end if;
1835
1836             --  Make sure we do not have the case of a precondition pragma when
1837             --  the Pre'Class aspect is present.
1838
1839             --  We do this by looking at pragmas already chained to the entity
1840             --  since the aspect derived pragma will be put on this list first.
1841
1842             if Pragma_Name (N) = Name_Precondition then
1843                if not From_Aspect_Specification (N) then
1844                   P := Spec_PPC_List (Contract (S));
1845                   while Present (P) loop
1846                      if Pragma_Name (P) = Name_Precondition
1847                        and then From_Aspect_Specification (P)
1848                        and then Class_Present (P)
1849                      then
1850                         Error_Msg_Sloc := Sloc (P);
1851                         Error_Pragma
1852                           ("pragma% not allowed, `Pre''Class` aspect given#");
1853                      end if;
1854
1855                      P := Next_Pragma (P);
1856                   end loop;
1857                end if;
1858             end if;
1859
1860             --  Similarly check for Pre with inherited Pre'Class. Note that
1861             --  we cover the aspect case as well here.
1862
1863             if Pragma_Name (N) = Name_Precondition
1864               and then not Class_Present (N)
1865             then
1866                declare
1867                   Inherited : constant Subprogram_List :=
1868                                 Inherited_Subprograms (S);
1869                   P         : Node_Id;
1870
1871                begin
1872                   for J in Inherited'Range loop
1873                      P := Spec_PPC_List (Contract (Inherited (J)));
1874                      while Present (P) loop
1875                         if Pragma_Name (P) = Name_Precondition
1876                           and then Class_Present (P)
1877                         then
1878                            Error_Msg_Sloc := Sloc (P);
1879                            Error_Pragma
1880                              ("pragma% not allowed, `Pre''Class` "
1881                               & "aspect inherited from#");
1882                         end if;
1883
1884                         P := Next_Pragma (P);
1885                      end loop;
1886                   end loop;
1887                end;
1888             end if;
1889
1890             --  Note: we do not analyze the pragma at this point. Instead we
1891             --  delay this analysis until the end of the declarative part in
1892             --  which the pragma appears. This implements the required delay
1893             --  in this analysis, allowing forward references. The analysis
1894             --  happens at the end of Analyze_Declarations.
1895
1896             --  Chain spec PPC pragma to list for subprogram
1897
1898             Set_Next_Pragma (N, Spec_PPC_List (Contract (S)));
1899             Set_Spec_PPC_List (Contract (S), N);
1900
1901             --  Return indicating spec case
1902
1903             In_Body := False;
1904             return;
1905          end Chain_PPC;
1906
1907       --  Start of processing for Check_Precondition_Postcondition
1908
1909       begin
1910          if not Is_List_Member (N) then
1911             Pragma_Misplaced;
1912          end if;
1913
1914          --  Preanalyze message argument if present. Visibility in this
1915          --  argument is established at the point of pragma occurrence.
1916
1917          if Arg_Count = 2 then
1918             Check_Optional_Identifier (Arg2, Name_Message);
1919             Preanalyze_Spec_Expression
1920               (Get_Pragma_Arg (Arg2), Standard_String);
1921          end if;
1922
1923          --  Record if pragma is disabled
1924
1925          if Check_Enabled (Pname) then
1926             Set_SCO_Pragma_Enabled (Loc);
1927          end if;
1928
1929          --  If we are within an inlined body, the legality of the pragma
1930          --  has been checked already.
1931
1932          if In_Inlined_Body then
1933             In_Body := True;
1934             return;
1935          end if;
1936
1937          --  Search prior declarations
1938
1939          P := N;
1940          while Present (Prev (P)) loop
1941             P := Prev (P);
1942
1943             --  If the previous node is a generic subprogram, do not go to to
1944             --  the original node, which is the unanalyzed tree: we need to
1945             --  attach the pre/postconditions to the analyzed version at this
1946             --  point. They get propagated to the original tree when analyzing
1947             --  the corresponding body.
1948
1949             if Nkind (P) not in N_Generic_Declaration then
1950                PO := Original_Node (P);
1951             else
1952                PO := P;
1953             end if;
1954
1955             --  Skip past prior pragma
1956
1957             if Nkind (PO) = N_Pragma then
1958                null;
1959
1960             --  Skip stuff not coming from source
1961
1962             elsif not Comes_From_Source (PO) then
1963
1964                --  The condition may apply to a subprogram instantiation
1965
1966                if Nkind (PO) = N_Subprogram_Declaration
1967                  and then Present (Generic_Parent (Specification (PO)))
1968                then
1969                   Chain_PPC (PO);
1970                   return;
1971
1972                elsif Nkind (PO) = N_Subprogram_Declaration
1973                  and then In_Instance
1974                then
1975                   Chain_PPC (PO);
1976                   return;
1977
1978                --  For all other cases of non source code, do nothing
1979
1980                else
1981                   null;
1982                end if;
1983
1984             --  Only remaining possibility is subprogram declaration
1985
1986             else
1987                Chain_PPC (PO);
1988                return;
1989             end if;
1990          end loop;
1991
1992          --  If we fall through loop, pragma is at start of list, so see if it
1993          --  is at the start of declarations of a subprogram body.
1994
1995          if Nkind (Parent (N)) = N_Subprogram_Body
1996            and then List_Containing (N) = Declarations (Parent (N))
1997          then
1998             if Operating_Mode /= Generate_Code
1999               or else Inside_A_Generic
2000             then
2001                --  Analyze pragma expression for correctness and for ASIS use
2002
2003                Preanalyze_Spec_Expression
2004                  (Get_Pragma_Arg (Arg1), Standard_Boolean);
2005
2006                --  In ASIS mode, for a pragma generated from a source aspect,
2007                --  also analyze the original aspect expression.
2008
2009                if ASIS_Mode
2010                  and then Present (Corresponding_Aspect (N))
2011                then
2012                   Preanalyze_Spec_Expression
2013                     (Expression (Corresponding_Aspect (N)), Standard_Boolean);
2014                end if;
2015             end if;
2016
2017             In_Body := True;
2018             return;
2019
2020          --  See if it is in the pragmas after a library level subprogram
2021
2022          elsif Nkind (Parent (N)) = N_Compilation_Unit_Aux then
2023
2024             --  In formal verification mode, analyze pragma expression for
2025             --  correctness, as it is not expanded later.
2026
2027             if Alfa_Mode then
2028                Analyze_PPC_In_Decl_Part
2029                  (N, Defining_Entity (Unit (Parent (Parent (N)))));
2030             end if;
2031
2032             Chain_PPC (Unit (Parent (Parent (N))));
2033             return;
2034          end if;
2035
2036          --  If we fall through, pragma was misplaced
2037
2038          Pragma_Misplaced;
2039       end Check_Precondition_Postcondition;
2040
2041       -----------------------------
2042       -- Check_Static_Constraint --
2043       -----------------------------
2044
2045       --  Note: for convenience in writing this procedure, in addition to
2046       --  the officially (i.e. by spec) allowed argument which is always a
2047       --  constraint, it also allows ranges and discriminant associations.
2048       --  Above is not clear ???
2049
2050       procedure Check_Static_Constraint (Constr : Node_Id) is
2051
2052          procedure Require_Static (E : Node_Id);
2053          --  Require given expression to be static expression
2054
2055          --------------------
2056          -- Require_Static --
2057          --------------------
2058
2059          procedure Require_Static (E : Node_Id) is
2060          begin
2061             if not Is_OK_Static_Expression (E) then
2062                Flag_Non_Static_Expr
2063                  ("non-static constraint not allowed in Unchecked_Union!", E);
2064                raise Pragma_Exit;
2065             end if;
2066          end Require_Static;
2067
2068       --  Start of processing for Check_Static_Constraint
2069
2070       begin
2071          case Nkind (Constr) is
2072             when N_Discriminant_Association =>
2073                Require_Static (Expression (Constr));
2074
2075             when N_Range =>
2076                Require_Static (Low_Bound (Constr));
2077                Require_Static (High_Bound (Constr));
2078
2079             when N_Attribute_Reference =>
2080                Require_Static (Type_Low_Bound  (Etype (Prefix (Constr))));
2081                Require_Static (Type_High_Bound (Etype (Prefix (Constr))));
2082
2083             when N_Range_Constraint =>
2084                Check_Static_Constraint (Range_Expression (Constr));
2085
2086             when N_Index_Or_Discriminant_Constraint =>
2087                declare
2088                   IDC : Entity_Id;
2089                begin
2090                   IDC := First (Constraints (Constr));
2091                   while Present (IDC) loop
2092                      Check_Static_Constraint (IDC);
2093                      Next (IDC);
2094                   end loop;
2095                end;
2096
2097             when others =>
2098                null;
2099          end case;
2100       end Check_Static_Constraint;
2101
2102       ---------------------
2103       -- Check_Test_Case --
2104       ---------------------
2105
2106       procedure Check_Test_Case is
2107          P  : Node_Id;
2108          PO : Node_Id;
2109
2110          procedure Chain_TC (PO : Node_Id);
2111          --  If PO is a [generic] subprogram declaration node, then the
2112          --  test-case applies to this subprogram and the processing for the
2113          --  pragma is completed. Otherwise the pragma is misplaced.
2114
2115          --------------
2116          -- Chain_TC --
2117          --------------
2118
2119          procedure Chain_TC (PO : Node_Id) is
2120             S   : Entity_Id;
2121
2122          begin
2123             if Nkind (PO) = N_Abstract_Subprogram_Declaration then
2124                if From_Aspect_Specification (N) then
2125                   Error_Pragma
2126                     ("aspect% cannot be applied to abstract subprogram");
2127                else
2128                   Error_Pragma
2129                     ("pragma% cannot be applied to abstract subprogram");
2130                end if;
2131
2132             elsif Nkind (PO) = N_Entry_Declaration then
2133                if From_Aspect_Specification (N) then
2134                   Error_Pragma ("aspect% cannot be applied to entry");
2135                else
2136                   Error_Pragma ("pragma% cannot be applied to entry");
2137                end if;
2138
2139             elsif not Nkind_In (PO, N_Subprogram_Declaration,
2140                                     N_Generic_Subprogram_Declaration)
2141             then
2142                Pragma_Misplaced;
2143             end if;
2144
2145             --  Here if we have [generic] subprogram declaration
2146
2147             S := Defining_Unit_Name (Specification (PO));
2148
2149             --  Note: we do not analyze the pragma at this point. Instead we
2150             --  delay this analysis until the end of the declarative part in
2151             --  which the pragma appears. This implements the required delay
2152             --  in this analysis, allowing forward references. The analysis
2153             --  happens at the end of Analyze_Declarations.
2154
2155             --  There should not be another test case with the same name
2156             --  associated to this subprogram.
2157
2158             declare
2159                Name : constant String_Id := Get_Name_From_Test_Case_Pragma (N);
2160                TC   : Node_Id;
2161
2162             begin
2163                TC := Spec_TC_List (Contract (S));
2164                while Present (TC) loop
2165
2166                   if String_Equal
2167                     (Name, Get_Name_From_Test_Case_Pragma (TC))
2168                   then
2169                      Error_Msg_Sloc := Sloc (TC);
2170
2171                      if From_Aspect_Specification (N) then
2172                         Error_Pragma ("name for aspect% is already used#");
2173                      else
2174                         Error_Pragma ("name for pragma% is already used#");
2175                      end if;
2176                   end if;
2177
2178                   TC := Next_Pragma (TC);
2179                end loop;
2180             end;
2181
2182             --  Chain spec TC pragma to list for subprogram
2183
2184             Set_Next_Pragma (N, Spec_TC_List (Contract (S)));
2185             Set_Spec_TC_List (Contract (S), N);
2186          end Chain_TC;
2187
2188       --  Start of processing for Check_Test_Case
2189
2190       begin
2191          if not Is_List_Member (N) then
2192             Pragma_Misplaced;
2193          end if;
2194
2195          --  Test cases should only appear in package spec unit
2196
2197          if Get_Source_Unit (N) = No_Unit
2198            or else not Nkind_In (Sinfo.Unit (Cunit (Get_Source_Unit (N))),
2199                                  N_Package_Declaration,
2200                                  N_Generic_Package_Declaration)
2201          then
2202             Pragma_Misplaced;
2203          end if;
2204
2205          --  Search prior declarations
2206
2207          P := N;
2208          while Present (Prev (P)) loop
2209             P := Prev (P);
2210
2211             --  If the previous node is a generic subprogram, do not go to to
2212             --  the original node, which is the unanalyzed tree: we need to
2213             --  attach the test-case to the analyzed version at this point.
2214             --  They get propagated to the original tree when analyzing the
2215             --  corresponding body.
2216
2217             if Nkind (P) not in N_Generic_Declaration then
2218                PO := Original_Node (P);
2219             else
2220                PO := P;
2221             end if;
2222
2223             --  Skip past prior pragma
2224
2225             if Nkind (PO) = N_Pragma then
2226                null;
2227
2228             --  Skip stuff not coming from source
2229
2230             elsif not Comes_From_Source (PO) then
2231                null;
2232
2233             --  Only remaining possibility is subprogram declaration. First
2234             --  check that it is declared directly in a package declaration.
2235             --  This may be either the package declaration for the current unit
2236             --  being defined or a local package declaration.
2237
2238             elsif not Present (Parent (Parent (PO)))
2239               or else not Present (Parent (Parent (Parent (PO))))
2240               or else not Nkind_In (Parent (Parent (PO)),
2241                                     N_Package_Declaration,
2242                                     N_Generic_Package_Declaration)
2243             then
2244                Pragma_Misplaced;
2245
2246             else
2247                Chain_TC (PO);
2248                return;
2249             end if;
2250          end loop;
2251
2252          --  If we fall through, pragma was misplaced
2253
2254          Pragma_Misplaced;
2255       end Check_Test_Case;
2256
2257       --------------------------------------
2258       -- Check_Valid_Configuration_Pragma --
2259       --------------------------------------
2260
2261       --  A configuration pragma must appear in the context clause of a
2262       --  compilation unit, and only other pragmas may precede it. Note that
2263       --  the test also allows use in a configuration pragma file.
2264
2265       procedure Check_Valid_Configuration_Pragma is
2266       begin
2267          if not Is_Configuration_Pragma then
2268             Error_Pragma ("incorrect placement for configuration pragma%");
2269          end if;
2270       end Check_Valid_Configuration_Pragma;
2271
2272       -------------------------------------
2273       -- Check_Valid_Library_Unit_Pragma --
2274       -------------------------------------
2275
2276       procedure Check_Valid_Library_Unit_Pragma is
2277          Plist       : List_Id;
2278          Parent_Node : Node_Id;
2279          Unit_Name   : Entity_Id;
2280          Unit_Kind   : Node_Kind;
2281          Unit_Node   : Node_Id;
2282          Sindex      : Source_File_Index;
2283
2284       begin
2285          if not Is_List_Member (N) then
2286             Pragma_Misplaced;
2287
2288          else
2289             Plist := List_Containing (N);
2290             Parent_Node := Parent (Plist);
2291
2292             if Parent_Node = Empty then
2293                Pragma_Misplaced;
2294
2295             --  Case of pragma appearing after a compilation unit. In this case
2296             --  it must have an argument with the corresponding name and must
2297             --  be part of the following pragmas of its parent.
2298
2299             elsif Nkind (Parent_Node) = N_Compilation_Unit_Aux then
2300                if Plist /= Pragmas_After (Parent_Node) then
2301                   Pragma_Misplaced;
2302
2303                elsif Arg_Count = 0 then
2304                   Error_Pragma
2305                     ("argument required if outside compilation unit");
2306
2307                else
2308                   Check_No_Identifiers;
2309                   Check_Arg_Count (1);
2310                   Unit_Node := Unit (Parent (Parent_Node));
2311                   Unit_Kind := Nkind (Unit_Node);
2312
2313                   Analyze (Get_Pragma_Arg (Arg1));
2314
2315                   if Unit_Kind = N_Generic_Subprogram_Declaration
2316                     or else Unit_Kind = N_Subprogram_Declaration
2317                   then
2318                      Unit_Name := Defining_Entity (Unit_Node);
2319
2320                   elsif Unit_Kind in N_Generic_Instantiation then
2321                      Unit_Name := Defining_Entity (Unit_Node);
2322
2323                   else
2324                      Unit_Name := Cunit_Entity (Current_Sem_Unit);
2325                   end if;
2326
2327                   if Chars (Unit_Name) /=
2328                      Chars (Entity (Get_Pragma_Arg (Arg1)))
2329                   then
2330                      Error_Pragma_Arg
2331                        ("pragma% argument is not current unit name", Arg1);
2332                   end if;
2333
2334                   if Ekind (Unit_Name) = E_Package
2335                     and then Present (Renamed_Entity (Unit_Name))
2336                   then
2337                      Error_Pragma ("pragma% not allowed for renamed package");
2338                   end if;
2339                end if;
2340
2341             --  Pragma appears other than after a compilation unit
2342
2343             else
2344                --  Here we check for the generic instantiation case and also
2345                --  for the case of processing a generic formal package. We
2346                --  detect these cases by noting that the Sloc on the node
2347                --  does not belong to the current compilation unit.
2348
2349                Sindex := Source_Index (Current_Sem_Unit);
2350
2351                if Loc not in Source_First (Sindex) .. Source_Last (Sindex) then
2352                   Rewrite (N, Make_Null_Statement (Loc));
2353                   return;
2354
2355                --  If before first declaration, the pragma applies to the
2356                --  enclosing unit, and the name if present must be this name.
2357
2358                elsif Is_Before_First_Decl (N, Plist) then
2359                   Unit_Node := Unit_Declaration_Node (Current_Scope);
2360                   Unit_Kind := Nkind (Unit_Node);
2361
2362                   if Nkind (Parent (Unit_Node)) /= N_Compilation_Unit then
2363                      Pragma_Misplaced;
2364
2365                   elsif Unit_Kind = N_Subprogram_Body
2366                     and then not Acts_As_Spec (Unit_Node)
2367                   then
2368                      Pragma_Misplaced;
2369
2370                   elsif Nkind (Parent_Node) = N_Package_Body then
2371                      Pragma_Misplaced;
2372
2373                   elsif Nkind (Parent_Node) = N_Package_Specification
2374                     and then Plist = Private_Declarations (Parent_Node)
2375                   then
2376                      Pragma_Misplaced;
2377
2378                   elsif (Nkind (Parent_Node) = N_Generic_Package_Declaration
2379                            or else Nkind (Parent_Node) =
2380                                              N_Generic_Subprogram_Declaration)
2381                     and then Plist = Generic_Formal_Declarations (Parent_Node)
2382                   then
2383                      Pragma_Misplaced;
2384
2385                   elsif Arg_Count > 0 then
2386                      Analyze (Get_Pragma_Arg (Arg1));
2387
2388                      if Entity (Get_Pragma_Arg (Arg1)) /= Current_Scope then
2389                         Error_Pragma_Arg
2390                           ("name in pragma% must be enclosing unit", Arg1);
2391                      end if;
2392
2393                   --  It is legal to have no argument in this context
2394
2395                   else
2396                      return;
2397                   end if;
2398
2399                --  Error if not before first declaration. This is because a
2400                --  library unit pragma argument must be the name of a library
2401                --  unit (RM 10.1.5(7)), but the only names permitted in this
2402                --  context are (RM 10.1.5(6)) names of subprogram declarations,
2403                --  generic subprogram declarations or generic instantiations.
2404
2405                else
2406                   Error_Pragma
2407                     ("pragma% misplaced, must be before first declaration");
2408                end if;
2409             end if;
2410          end if;
2411       end Check_Valid_Library_Unit_Pragma;
2412
2413       -------------------
2414       -- Check_Variant --
2415       -------------------
2416
2417       procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id) is
2418          Clist : constant Node_Id := Component_List (Variant);
2419          Comp  : Node_Id;
2420
2421       begin
2422          if not Is_Non_Empty_List (Component_Items (Clist)) then
2423             Error_Msg_N
2424               ("Unchecked_Union may not have empty component list",
2425                Variant);
2426             return;
2427          end if;
2428
2429          Comp := First (Component_Items (Clist));
2430          while Present (Comp) loop
2431             Check_Component (Comp, UU_Typ, In_Variant_Part => True);
2432             Next (Comp);
2433          end loop;
2434       end Check_Variant;
2435
2436       ------------------
2437       -- Error_Pragma --
2438       ------------------
2439
2440       procedure Error_Pragma (Msg : String) is
2441          MsgF : String := Msg;
2442       begin
2443          Error_Msg_Name_1 := Pname;
2444          Fix_Error (MsgF);
2445          Error_Msg_N (MsgF, N);
2446          raise Pragma_Exit;
2447       end Error_Pragma;
2448
2449       ----------------------
2450       -- Error_Pragma_Arg --
2451       ----------------------
2452
2453       procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id) is
2454          MsgF : String := Msg;
2455       begin
2456          Error_Msg_Name_1 := Pname;
2457          Fix_Error (MsgF);
2458          Error_Msg_N (MsgF, Get_Pragma_Arg (Arg));
2459          raise Pragma_Exit;
2460       end Error_Pragma_Arg;
2461
2462       procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id) is
2463          MsgF : String := Msg1;
2464       begin
2465          Error_Msg_Name_1 := Pname;
2466          Fix_Error (MsgF);
2467          Error_Msg_N (MsgF, Get_Pragma_Arg (Arg));
2468          Error_Pragma_Arg (Msg2, Arg);
2469       end Error_Pragma_Arg;
2470
2471       ----------------------------
2472       -- Error_Pragma_Arg_Ident --
2473       ----------------------------
2474
2475       procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id) is
2476          MsgF : String := Msg;
2477       begin
2478          Error_Msg_Name_1 := Pname;
2479          Fix_Error (MsgF);
2480          Error_Msg_N (MsgF, Arg);
2481          raise Pragma_Exit;
2482       end Error_Pragma_Arg_Ident;
2483
2484       ----------------------
2485       -- Error_Pragma_Ref --
2486       ----------------------
2487
2488       procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id) is
2489          MsgF : String := Msg;
2490       begin
2491          Error_Msg_Name_1 := Pname;
2492          Fix_Error (MsgF);
2493          Error_Msg_Sloc   := Sloc (Ref);
2494          Error_Msg_NE (MsgF, N, Ref);
2495          raise Pragma_Exit;
2496       end Error_Pragma_Ref;
2497
2498       ------------------------
2499       -- Find_Lib_Unit_Name --
2500       ------------------------
2501
2502       function Find_Lib_Unit_Name return Entity_Id is
2503       begin
2504          --  Return inner compilation unit entity, for case of nested
2505          --  categorization pragmas. This happens in generic unit.
2506
2507          if Nkind (Parent (N)) = N_Package_Specification
2508            and then Defining_Entity (Parent (N)) /= Current_Scope
2509          then
2510             return Defining_Entity (Parent (N));
2511          else
2512             return Current_Scope;
2513          end if;
2514       end Find_Lib_Unit_Name;
2515
2516       ----------------------------
2517       -- Find_Program_Unit_Name --
2518       ----------------------------
2519
2520       procedure Find_Program_Unit_Name (Id : Node_Id) is
2521          Unit_Name : Entity_Id;
2522          Unit_Kind : Node_Kind;
2523          P         : constant Node_Id := Parent (N);
2524
2525       begin
2526          if Nkind (P) = N_Compilation_Unit then
2527             Unit_Kind := Nkind (Unit (P));
2528
2529             if Unit_Kind = N_Subprogram_Declaration
2530               or else Unit_Kind = N_Package_Declaration
2531               or else Unit_Kind in N_Generic_Declaration
2532             then
2533                Unit_Name := Defining_Entity (Unit (P));
2534
2535                if Chars (Id) = Chars (Unit_Name) then
2536                   Set_Entity (Id, Unit_Name);
2537                   Set_Etype (Id, Etype (Unit_Name));
2538                else
2539                   Set_Etype (Id, Any_Type);
2540                   Error_Pragma
2541                     ("cannot find program unit referenced by pragma%");
2542                end if;
2543
2544             else
2545                Set_Etype (Id, Any_Type);
2546                Error_Pragma ("pragma% inapplicable to this unit");
2547             end if;
2548
2549          else
2550             Analyze (Id);
2551          end if;
2552       end Find_Program_Unit_Name;
2553
2554       -----------------------------------------
2555       -- Find_Unique_Parameterless_Procedure --
2556       -----------------------------------------
2557
2558       function Find_Unique_Parameterless_Procedure
2559         (Name : Entity_Id;
2560          Arg  : Node_Id) return Entity_Id
2561       is
2562          Proc : Entity_Id := Empty;
2563
2564       begin
2565          --  The body of this procedure needs some comments ???
2566
2567          if not Is_Entity_Name (Name) then
2568             Error_Pragma_Arg
2569               ("argument of pragma% must be entity name", Arg);
2570
2571          elsif not Is_Overloaded (Name) then
2572             Proc := Entity (Name);
2573
2574             if Ekind (Proc) /= E_Procedure
2575               or else Present (First_Formal (Proc))
2576             then
2577                Error_Pragma_Arg
2578                  ("argument of pragma% must be parameterless procedure", Arg);
2579             end if;
2580
2581          else
2582             declare
2583                Found : Boolean := False;
2584                It    : Interp;
2585                Index : Interp_Index;
2586
2587             begin
2588                Get_First_Interp (Name, Index, It);
2589                while Present (It.Nam) loop
2590                   Proc := It.Nam;
2591
2592                   if Ekind (Proc) = E_Procedure
2593                     and then No (First_Formal (Proc))
2594                   then
2595                      if not Found then
2596                         Found := True;
2597                         Set_Entity (Name, Proc);
2598                         Set_Is_Overloaded (Name, False);
2599                      else
2600                         Error_Pragma_Arg
2601                           ("ambiguous handler name for pragma% ", Arg);
2602                      end if;
2603                   end if;
2604
2605                   Get_Next_Interp (Index, It);
2606                end loop;
2607
2608                if not Found then
2609                   Error_Pragma_Arg
2610                     ("argument of pragma% must be parameterless procedure",
2611                      Arg);
2612                else
2613                   Proc := Entity (Name);
2614                end if;
2615             end;
2616          end if;
2617
2618          return Proc;
2619       end Find_Unique_Parameterless_Procedure;
2620
2621       ---------------
2622       -- Fix_Error --
2623       ---------------
2624
2625       procedure Fix_Error (Msg : in out String) is
2626       begin
2627          if From_Aspect_Specification (N) then
2628             for J in Msg'First .. Msg'Last - 5 loop
2629                if Msg (J .. J + 5) = "pragma" then
2630                   Msg (J .. J + 5) := "aspect";
2631                end if;
2632             end loop;
2633
2634             if Error_Msg_Name_1 = Name_Precondition then
2635                Error_Msg_Name_1 := Name_Pre;
2636             elsif Error_Msg_Name_1 = Name_Postcondition then
2637                Error_Msg_Name_1 := Name_Post;
2638             end if;
2639          end if;
2640       end Fix_Error;
2641
2642       -------------------------
2643       -- Gather_Associations --
2644       -------------------------
2645
2646       procedure Gather_Associations
2647         (Names : Name_List;
2648          Args  : out Args_List)
2649       is
2650          Arg : Node_Id;
2651
2652       begin
2653          --  Initialize all parameters to Empty
2654
2655          for J in Args'Range loop
2656             Args (J) := Empty;
2657          end loop;
2658
2659          --  That's all we have to do if there are no argument associations
2660
2661          if No (Pragma_Argument_Associations (N)) then
2662             return;
2663          end if;
2664
2665          --  Otherwise first deal with any positional parameters present
2666
2667          Arg := First (Pragma_Argument_Associations (N));
2668          for Index in Args'Range loop
2669             exit when No (Arg) or else Chars (Arg) /= No_Name;
2670             Args (Index) := Get_Pragma_Arg (Arg);
2671             Next (Arg);
2672          end loop;
2673
2674          --  Positional parameters all processed, if any left, then we
2675          --  have too many positional parameters.
2676
2677          if Present (Arg) and then Chars (Arg) = No_Name then
2678             Error_Pragma_Arg
2679               ("too many positional associations for pragma%", Arg);
2680          end if;
2681
2682          --  Process named parameters if any are present
2683
2684          while Present (Arg) loop
2685             if Chars (Arg) = No_Name then
2686                Error_Pragma_Arg
2687                  ("positional association cannot follow named association",
2688                   Arg);
2689
2690             else
2691                for Index in Names'Range loop
2692                   if Names (Index) = Chars (Arg) then
2693                      if Present (Args (Index)) then
2694                         Error_Pragma_Arg
2695                           ("duplicate argument association for pragma%", Arg);
2696                      else
2697                         Args (Index) := Get_Pragma_Arg (Arg);
2698                         exit;
2699                      end if;
2700                   end if;
2701
2702                   if Index = Names'Last then
2703                      Error_Msg_Name_1 := Pname;
2704                      Error_Msg_N ("pragma% does not allow & argument", Arg);
2705
2706                      --  Check for possible misspelling
2707
2708                      for Index1 in Names'Range loop
2709                         if Is_Bad_Spelling_Of
2710                              (Chars (Arg), Names (Index1))
2711                         then
2712                            Error_Msg_Name_1 := Names (Index1);
2713                            Error_Msg_N -- CODEFIX
2714                              ("\possible misspelling of%", Arg);
2715                            exit;
2716                         end if;
2717                      end loop;
2718
2719                      raise Pragma_Exit;
2720                   end if;
2721                end loop;
2722             end if;
2723
2724             Next (Arg);
2725          end loop;
2726       end Gather_Associations;
2727
2728       -----------------
2729       -- GNAT_Pragma --
2730       -----------------
2731
2732       procedure GNAT_Pragma is
2733       begin
2734          --  We need to check the No_Implementation_Pragmas restriction for
2735          --  the case of a pragma from source. Note that the case of aspects
2736          --  generating corresponding pragmas marks these pragmas as not being
2737          --  from source, so this test also catches that case.
2738
2739          if Comes_From_Source (N) then
2740             Check_Restriction (No_Implementation_Pragmas, N);
2741          end if;
2742       end GNAT_Pragma;
2743
2744       --------------------------
2745       -- Is_Before_First_Decl --
2746       --------------------------
2747
2748       function Is_Before_First_Decl
2749         (Pragma_Node : Node_Id;
2750          Decls       : List_Id) return Boolean
2751       is
2752          Item : Node_Id := First (Decls);
2753
2754       begin
2755          --  Only other pragmas can come before this pragma
2756
2757          loop
2758             if No (Item) or else Nkind (Item) /= N_Pragma then
2759                return False;
2760
2761             elsif Item = Pragma_Node then
2762                return True;
2763             end if;
2764
2765             Next (Item);
2766          end loop;
2767       end Is_Before_First_Decl;
2768
2769       -----------------------------
2770       -- Is_Configuration_Pragma --
2771       -----------------------------
2772
2773       --  A configuration pragma must appear in the context clause of a
2774       --  compilation unit, and only other pragmas may precede it. Note that
2775       --  the test below also permits use in a configuration pragma file.
2776
2777       function Is_Configuration_Pragma return Boolean is
2778          Lis : constant List_Id := List_Containing (N);
2779          Par : constant Node_Id := Parent (N);
2780          Prg : Node_Id;
2781
2782       begin
2783          --  If no parent, then we are in the configuration pragma file,
2784          --  so the placement is definitely appropriate.
2785
2786          if No (Par) then
2787             return True;
2788
2789          --  Otherwise we must be in the context clause of a compilation unit
2790          --  and the only thing allowed before us in the context list is more
2791          --  configuration pragmas.
2792
2793          elsif Nkind (Par) = N_Compilation_Unit
2794            and then Context_Items (Par) = Lis
2795          then
2796             Prg := First (Lis);
2797
2798             loop
2799                if Prg = N then
2800                   return True;
2801                elsif Nkind (Prg) /= N_Pragma then
2802                   return False;
2803                end if;
2804
2805                Next (Prg);
2806             end loop;
2807
2808          else
2809             return False;
2810          end if;
2811       end Is_Configuration_Pragma;
2812
2813       --------------------------
2814       -- Is_In_Context_Clause --
2815       --------------------------
2816
2817       function Is_In_Context_Clause return Boolean is
2818          Plist       : List_Id;
2819          Parent_Node : Node_Id;
2820
2821       begin
2822          if not Is_List_Member (N) then
2823             return False;
2824
2825          else
2826             Plist := List_Containing (N);
2827             Parent_Node := Parent (Plist);
2828
2829             if Parent_Node = Empty
2830               or else Nkind (Parent_Node) /= N_Compilation_Unit
2831               or else Context_Items (Parent_Node) /= Plist
2832             then
2833                return False;
2834             end if;
2835          end if;
2836
2837          return True;
2838       end Is_In_Context_Clause;
2839
2840       ---------------------------------
2841       -- Is_Static_String_Expression --
2842       ---------------------------------
2843
2844       function Is_Static_String_Expression (Arg : Node_Id) return Boolean is
2845          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
2846
2847       begin
2848          Analyze_And_Resolve (Argx);
2849          return Is_OK_Static_Expression (Argx)
2850            and then Nkind (Argx) = N_String_Literal;
2851       end Is_Static_String_Expression;
2852
2853       ----------------------
2854       -- Pragma_Misplaced --
2855       ----------------------
2856
2857       procedure Pragma_Misplaced is
2858       begin
2859          Error_Pragma ("incorrect placement of pragma%");
2860       end Pragma_Misplaced;
2861
2862       ------------------------------------
2863       -- Process Atomic_Shared_Volatile --
2864       ------------------------------------
2865
2866       procedure Process_Atomic_Shared_Volatile is
2867          E_Id : Node_Id;
2868          E    : Entity_Id;
2869          D    : Node_Id;
2870          K    : Node_Kind;
2871          Utyp : Entity_Id;
2872
2873          procedure Set_Atomic (E : Entity_Id);
2874          --  Set given type as atomic, and if no explicit alignment was given,
2875          --  set alignment to unknown, since back end knows what the alignment
2876          --  requirements are for atomic arrays. Note: this step is necessary
2877          --  for derived types.
2878
2879          ----------------
2880          -- Set_Atomic --
2881          ----------------
2882
2883          procedure Set_Atomic (E : Entity_Id) is
2884          begin
2885             Set_Is_Atomic (E);
2886
2887             if not Has_Alignment_Clause (E) then
2888                Set_Alignment (E, Uint_0);
2889             end if;
2890          end Set_Atomic;
2891
2892       --  Start of processing for Process_Atomic_Shared_Volatile
2893
2894       begin
2895          Check_Ada_83_Warning;
2896          Check_No_Identifiers;
2897          Check_Arg_Count (1);
2898          Check_Arg_Is_Local_Name (Arg1);
2899          E_Id := Get_Pragma_Arg (Arg1);
2900
2901          if Etype (E_Id) = Any_Type then
2902             return;
2903          end if;
2904
2905          E := Entity (E_Id);
2906          D := Declaration_Node (E);
2907          K := Nkind (D);
2908
2909          --  Check duplicate before we chain ourselves!
2910
2911          Check_Duplicate_Pragma (E);
2912
2913          --  Now check appropriateness of the entity
2914
2915          if Is_Type (E) then
2916             if Rep_Item_Too_Early (E, N)
2917                  or else
2918                Rep_Item_Too_Late (E, N)
2919             then
2920                return;
2921             else
2922                Check_First_Subtype (Arg1);
2923             end if;
2924
2925             if Prag_Id /= Pragma_Volatile then
2926                Set_Atomic (E);
2927                Set_Atomic (Underlying_Type (E));
2928                Set_Atomic (Base_Type (E));
2929             end if;
2930
2931             --  Attribute belongs on the base type. If the view of the type is
2932             --  currently private, it also belongs on the underlying type.
2933
2934             Set_Is_Volatile (Base_Type (E));
2935             Set_Is_Volatile (Underlying_Type (E));
2936
2937             Set_Treat_As_Volatile (E);
2938             Set_Treat_As_Volatile (Underlying_Type (E));
2939
2940          elsif K = N_Object_Declaration
2941            or else (K = N_Component_Declaration
2942                      and then Original_Record_Component (E) = E)
2943          then
2944             if Rep_Item_Too_Late (E, N) then
2945                return;
2946             end if;
2947
2948             if Prag_Id /= Pragma_Volatile then
2949                Set_Is_Atomic (E);
2950
2951                --  If the object declaration has an explicit initialization, a
2952                --  temporary may have to be created to hold the expression, to
2953                --  ensure that access to the object remain atomic.
2954
2955                if Nkind (Parent (E)) = N_Object_Declaration
2956                  and then Present (Expression (Parent (E)))
2957                then
2958                   Set_Has_Delayed_Freeze (E);
2959                end if;
2960
2961                --  An interesting improvement here. If an object of type X is
2962                --  declared atomic, and the type X is not atomic, that's a
2963                --  pity, since it may not have appropriate alignment etc. We
2964                --  can rescue this in the special case where the object and
2965                --  type are in the same unit by just setting the type as
2966                --  atomic, so that the back end will process it as atomic.
2967
2968                Utyp := Underlying_Type (Etype (E));
2969
2970                if Present (Utyp)
2971                  and then Sloc (E) > No_Location
2972                  and then Sloc (Utyp) > No_Location
2973                  and then
2974                    Get_Source_File_Index (Sloc (E)) =
2975                    Get_Source_File_Index (Sloc (Underlying_Type (Etype (E))))
2976                then
2977                   Set_Is_Atomic (Underlying_Type (Etype (E)));
2978                end if;
2979             end if;
2980
2981             Set_Is_Volatile (E);
2982             Set_Treat_As_Volatile (E);
2983
2984          else
2985             Error_Pragma_Arg
2986               ("inappropriate entity for pragma%", Arg1);
2987          end if;
2988       end Process_Atomic_Shared_Volatile;
2989
2990       -------------------------------------------
2991       -- Process_Compile_Time_Warning_Or_Error --
2992       -------------------------------------------
2993
2994       procedure Process_Compile_Time_Warning_Or_Error is
2995          Arg1x : constant Node_Id := Get_Pragma_Arg (Arg1);
2996
2997       begin
2998          Check_Arg_Count (2);
2999          Check_No_Identifiers;
3000          Check_Arg_Is_Static_Expression (Arg2, Standard_String);
3001          Analyze_And_Resolve (Arg1x, Standard_Boolean);
3002
3003          if Compile_Time_Known_Value (Arg1x) then
3004             if Is_True (Expr_Value (Get_Pragma_Arg (Arg1))) then
3005                declare
3006                   Str   : constant String_Id :=
3007                             Strval (Get_Pragma_Arg (Arg2));
3008                   Len   : constant Int := String_Length (Str);
3009                   Cont  : Boolean;
3010                   Ptr   : Nat;
3011                   CC    : Char_Code;
3012                   C     : Character;
3013                   Cent  : constant Entity_Id :=
3014                             Cunit_Entity (Current_Sem_Unit);
3015
3016                   Force : constant Boolean :=
3017                             Prag_Id = Pragma_Compile_Time_Warning
3018                               and then
3019                                 Is_Spec_Name (Unit_Name (Current_Sem_Unit))
3020                               and then (Ekind (Cent) /= E_Package
3021                                           or else not In_Private_Part (Cent));
3022                   --  Set True if this is the warning case, and we are in the
3023                   --  visible part of a package spec, or in a subprogram spec,
3024                   --  in which case we want to force the client to see the
3025                   --  warning, even though it is not in the main unit.
3026
3027                begin
3028                   --  Loop through segments of message separated by line feeds.
3029                   --  We output these segments as separate messages with
3030                   --  continuation marks for all but the first.
3031
3032                   Cont := False;
3033                   Ptr := 1;
3034                   loop
3035                      Error_Msg_Strlen := 0;
3036
3037                      --  Loop to copy characters from argument to error message
3038                      --  string buffer.
3039
3040                      loop
3041                         exit when Ptr > Len;
3042                         CC := Get_String_Char (Str, Ptr);
3043                         Ptr := Ptr + 1;
3044
3045                         --  Ignore wide chars ??? else store character
3046
3047                         if In_Character_Range (CC) then
3048                            C := Get_Character (CC);
3049                            exit when C = ASCII.LF;
3050                            Error_Msg_Strlen := Error_Msg_Strlen + 1;
3051                            Error_Msg_String (Error_Msg_Strlen) := C;
3052                         end if;
3053                      end loop;
3054
3055                      --  Here with one line ready to go
3056
3057                      Error_Msg_Warn := Prag_Id = Pragma_Compile_Time_Warning;
3058
3059                      --  If this is a warning in a spec, then we want clients
3060                      --  to see the warning, so mark the message with the
3061                      --  special sequence !! to force the warning. In the case
3062                      --  of a package spec, we do not force this if we are in
3063                      --  the private part of the spec.
3064
3065                      if Force then
3066                         if Cont = False then
3067                            Error_Msg_N ("<~!!", Arg1);
3068                            Cont := True;
3069                         else
3070                            Error_Msg_N ("\<~!!", Arg1);
3071                         end if;
3072
3073                      --  Error, rather than warning, or in a body, so we do not
3074                      --  need to force visibility for client (error will be
3075                      --  output in any case, and this is the situation in which
3076                      --  we do not want a client to get a warning, since the
3077                      --  warning is in the body or the spec private part).
3078
3079                      else
3080                         if Cont = False then
3081                            Error_Msg_N ("<~", Arg1);
3082                            Cont := True;
3083                         else
3084                            Error_Msg_N ("\<~", Arg1);
3085                         end if;
3086                      end if;
3087
3088                      exit when Ptr > Len;
3089                   end loop;
3090                end;
3091             end if;
3092          end if;
3093       end Process_Compile_Time_Warning_Or_Error;
3094
3095       ------------------------
3096       -- Process_Convention --
3097       ------------------------
3098
3099       procedure Process_Convention
3100         (C   : out Convention_Id;
3101          Ent : out Entity_Id)
3102       is
3103          Id        : Node_Id;
3104          E         : Entity_Id;
3105          E1        : Entity_Id;
3106          Cname     : Name_Id;
3107          Comp_Unit : Unit_Number_Type;
3108
3109          procedure Diagnose_Multiple_Pragmas (S : Entity_Id);
3110          --  Called if we have more than one Export/Import/Convention pragma.
3111          --  This is generally illegal, but we have a special case of allowing
3112          --  Import and Interface to coexist if they specify the convention in
3113          --  a consistent manner. We are allowed to do this, since Interface is
3114          --  an implementation defined pragma, and we choose to do it since we
3115          --  know Rational allows this combination. S is the entity id of the
3116          --  subprogram in question. This procedure also sets the special flag
3117          --  Import_Interface_Present in both pragmas in the case where we do
3118          --  have matching Import and Interface pragmas.
3119
3120          procedure Set_Convention_From_Pragma (E : Entity_Id);
3121          --  Set convention in entity E, and also flag that the entity has a
3122          --  convention pragma. If entity is for a private or incomplete type,
3123          --  also set convention and flag on underlying type. This procedure
3124          --  also deals with the special case of C_Pass_By_Copy convention.
3125
3126          -------------------------------
3127          -- Diagnose_Multiple_Pragmas --
3128          -------------------------------
3129
3130          procedure Diagnose_Multiple_Pragmas (S : Entity_Id) is
3131             Pdec : constant Node_Id := Declaration_Node (S);
3132             Decl : Node_Id;
3133             Err  : Boolean;
3134
3135             function Same_Convention (Decl : Node_Id) return Boolean;
3136             --  Decl is a pragma node. This function returns True if this
3137             --  pragma has a first argument that is an identifier with a
3138             --  Chars field corresponding to the Convention_Id C.
3139
3140             function Same_Name (Decl : Node_Id) return Boolean;
3141             --  Decl is a pragma node. This function returns True if this
3142             --  pragma has a second argument that is an identifier with a
3143             --  Chars field that matches the Chars of the current subprogram.
3144
3145             ---------------------
3146             -- Same_Convention --
3147             ---------------------
3148
3149             function Same_Convention (Decl : Node_Id) return Boolean is
3150                Arg1 : constant Node_Id :=
3151                         First (Pragma_Argument_Associations (Decl));
3152
3153             begin
3154                if Present (Arg1) then
3155                   declare
3156                      Arg : constant Node_Id := Get_Pragma_Arg (Arg1);
3157                   begin
3158                      if Nkind (Arg) = N_Identifier
3159                        and then Is_Convention_Name (Chars (Arg))
3160                        and then Get_Convention_Id (Chars (Arg)) = C
3161                      then
3162                         return True;
3163                      end if;
3164                   end;
3165                end if;
3166
3167                return False;
3168             end Same_Convention;
3169
3170             ---------------
3171             -- Same_Name --
3172             ---------------
3173
3174             function Same_Name (Decl : Node_Id) return Boolean is
3175                Arg1 : constant Node_Id :=
3176                         First (Pragma_Argument_Associations (Decl));
3177                Arg2 : Node_Id;
3178
3179             begin
3180                if No (Arg1) then
3181                   return False;
3182                end if;
3183
3184                Arg2 := Next (Arg1);
3185
3186                if No (Arg2) then
3187                   return False;
3188                end if;
3189
3190                declare
3191                   Arg : constant Node_Id := Get_Pragma_Arg (Arg2);
3192                begin
3193                   if Nkind (Arg) = N_Identifier
3194                     and then Chars (Arg) = Chars (S)
3195                   then
3196                      return True;
3197                   end if;
3198                end;
3199
3200                return False;
3201             end Same_Name;
3202
3203          --  Start of processing for Diagnose_Multiple_Pragmas
3204
3205          begin
3206             Err := True;
3207
3208             --  Definitely give message if we have Convention/Export here
3209
3210             if Prag_Id = Pragma_Convention or else Prag_Id = Pragma_Export then
3211                null;
3212
3213                --  If we have an Import or Export, scan back from pragma to
3214                --  find any previous pragma applying to the same procedure.
3215                --  The scan will be terminated by the start of the list, or
3216                --  hitting the subprogram declaration. This won't allow one
3217                --  pragma to appear in the public part and one in the private
3218                --  part, but that seems very unlikely in practice.
3219
3220             else
3221                Decl := Prev (N);
3222                while Present (Decl) and then Decl /= Pdec loop
3223
3224                   --  Look for pragma with same name as us
3225
3226                   if Nkind (Decl) = N_Pragma
3227                     and then Same_Name (Decl)
3228                   then
3229                      --  Give error if same as our pragma or Export/Convention
3230
3231                      if Pragma_Name (Decl) = Name_Export
3232                           or else
3233                         Pragma_Name (Decl) = Name_Convention
3234                           or else
3235                         Pragma_Name (Decl) = Pragma_Name (N)
3236                      then
3237                         exit;
3238
3239                      --  Case of Import/Interface or the other way round
3240
3241                      elsif Pragma_Name (Decl) = Name_Interface
3242                              or else
3243                            Pragma_Name (Decl) = Name_Import
3244                      then
3245                         --  Here we know that we have Import and Interface. It
3246                         --  doesn't matter which way round they are. See if
3247                         --  they specify the same convention. If so, all OK,
3248                         --  and set special flags to stop other messages
3249
3250                         if Same_Convention (Decl) then
3251                            Set_Import_Interface_Present (N);
3252                            Set_Import_Interface_Present (Decl);
3253                            Err := False;
3254
3255                         --  If different conventions, special message
3256
3257                         else
3258                            Error_Msg_Sloc := Sloc (Decl);
3259                            Error_Pragma_Arg
3260                              ("convention differs from that given#", Arg1);
3261                            return;
3262                         end if;
3263                      end if;
3264                   end if;
3265
3266                   Next (Decl);
3267                end loop;
3268             end if;
3269
3270             --  Give message if needed if we fall through those tests
3271
3272             if Err then
3273                Error_Pragma_Arg
3274                  ("at most one Convention/Export/Import pragma is allowed",
3275                   Arg2);
3276             end if;
3277          end Diagnose_Multiple_Pragmas;
3278
3279          --------------------------------
3280          -- Set_Convention_From_Pragma --
3281          --------------------------------
3282
3283          procedure Set_Convention_From_Pragma (E : Entity_Id) is
3284          begin
3285             --  Ada 2005 (AI-430): Check invalid attempt to change convention
3286             --  for an overridden dispatching operation. Technically this is
3287             --  an amendment and should only be done in Ada 2005 mode. However,
3288             --  this is clearly a mistake, since the problem that is addressed
3289             --  by this AI is that there is a clear gap in the RM!
3290
3291             if Is_Dispatching_Operation (E)
3292               and then Present (Overridden_Operation (E))
3293               and then C /= Convention (Overridden_Operation (E))
3294             then
3295                Error_Pragma_Arg
3296                  ("cannot change convention for " &
3297                   "overridden dispatching operation",
3298                   Arg1);
3299             end if;
3300
3301             --  Set the convention
3302
3303             Set_Convention (E, C);
3304             Set_Has_Convention_Pragma (E);
3305
3306             if Is_Incomplete_Or_Private_Type (E)
3307               and then Present (Underlying_Type (E))
3308             then
3309                Set_Convention            (Underlying_Type (E), C);
3310                Set_Has_Convention_Pragma (Underlying_Type (E), True);
3311             end if;
3312
3313             --  A class-wide type should inherit the convention of the specific
3314             --  root type (although this isn't specified clearly by the RM).
3315
3316             if Is_Type (E) and then Present (Class_Wide_Type (E)) then
3317                Set_Convention (Class_Wide_Type (E), C);
3318             end if;
3319
3320             --  If the entity is a record type, then check for special case of
3321             --  C_Pass_By_Copy, which is treated the same as C except that the
3322             --  special record flag is set. This convention is only permitted
3323             --  on record types (see AI95-00131).
3324
3325             if Cname = Name_C_Pass_By_Copy then
3326                if Is_Record_Type (E) then
3327                   Set_C_Pass_By_Copy (Base_Type (E));
3328                elsif Is_Incomplete_Or_Private_Type (E)
3329                  and then Is_Record_Type (Underlying_Type (E))
3330                then
3331                   Set_C_Pass_By_Copy (Base_Type (Underlying_Type (E)));
3332                else
3333                   Error_Pragma_Arg
3334                     ("C_Pass_By_Copy convention allowed only for record type",
3335                      Arg2);
3336                end if;
3337             end if;
3338
3339             --  If the entity is a derived boolean type, check for the special
3340             --  case of convention C, C++, or Fortran, where we consider any
3341             --  nonzero value to represent true.
3342
3343             if Is_Discrete_Type (E)
3344               and then Root_Type (Etype (E)) = Standard_Boolean
3345               and then
3346                 (C = Convention_C
3347                    or else
3348                  C = Convention_CPP
3349                    or else
3350                  C = Convention_Fortran)
3351             then
3352                Set_Nonzero_Is_True (Base_Type (E));
3353             end if;
3354          end Set_Convention_From_Pragma;
3355
3356       --  Start of processing for Process_Convention
3357
3358       begin
3359          Check_At_Least_N_Arguments (2);
3360          Check_Optional_Identifier (Arg1, Name_Convention);
3361          Check_Arg_Is_Identifier (Arg1);
3362          Cname := Chars (Get_Pragma_Arg (Arg1));
3363
3364          --  C_Pass_By_Copy is treated as a synonym for convention C (this is
3365          --  tested again below to set the critical flag).
3366
3367          if Cname = Name_C_Pass_By_Copy then
3368             C := Convention_C;
3369
3370          --  Otherwise we must have something in the standard convention list
3371
3372          elsif Is_Convention_Name (Cname) then
3373             C := Get_Convention_Id (Chars (Get_Pragma_Arg (Arg1)));
3374
3375          --  In DEC VMS, it seems that there is an undocumented feature that
3376          --  any unrecognized convention is treated as the default, which for
3377          --  us is convention C. It does not seem so terrible to do this
3378          --  unconditionally, silently in the VMS case, and with a warning
3379          --  in the non-VMS case.
3380
3381          else
3382             if Warn_On_Export_Import and not OpenVMS_On_Target then
3383                Error_Msg_N
3384                  ("?unrecognized convention name, C assumed",
3385                   Get_Pragma_Arg (Arg1));
3386             end if;
3387
3388             C := Convention_C;
3389          end if;
3390
3391          Check_Optional_Identifier (Arg2, Name_Entity);
3392          Check_Arg_Is_Local_Name (Arg2);
3393
3394          Id := Get_Pragma_Arg (Arg2);
3395          Analyze (Id);
3396
3397          if not Is_Entity_Name (Id) then
3398             Error_Pragma_Arg ("entity name required", Arg2);
3399          end if;
3400
3401          E := Entity (Id);
3402
3403          --  Set entity to return
3404
3405          Ent := E;
3406
3407          --  Ada_Pass_By_Copy special checking
3408
3409          if C = Convention_Ada_Pass_By_Copy then
3410             if not Is_First_Subtype (E) then
3411                Error_Pragma_Arg
3412                  ("convention `Ada_Pass_By_Copy` only "
3413                   & "allowed for types", Arg2);
3414             end if;
3415
3416             if Is_By_Reference_Type (E) then
3417                Error_Pragma_Arg
3418                  ("convention `Ada_Pass_By_Copy` not allowed for "
3419                   & "by-reference type", Arg1);
3420             end if;
3421          end if;
3422
3423          --  Ada_Pass_By_Reference special checking
3424
3425          if C = Convention_Ada_Pass_By_Reference then
3426             if not Is_First_Subtype (E) then
3427                Error_Pragma_Arg
3428                  ("convention `Ada_Pass_By_Reference` only "
3429                   & "allowed for types", Arg2);
3430             end if;
3431
3432             if Is_By_Copy_Type (E) then
3433                Error_Pragma_Arg
3434                  ("convention `Ada_Pass_By_Reference` not allowed for "
3435                   & "by-copy type", Arg1);
3436             end if;
3437          end if;
3438
3439          --  Go to renamed subprogram if present, since convention applies to
3440          --  the actual renamed entity, not to the renaming entity. If the
3441          --  subprogram is inherited, go to parent subprogram.
3442
3443          if Is_Subprogram (E)
3444            and then Present (Alias (E))
3445          then
3446             if Nkind (Parent (Declaration_Node (E))) =
3447                                        N_Subprogram_Renaming_Declaration
3448             then
3449                if Scope (E) /= Scope (Alias (E)) then
3450                   Error_Pragma_Ref
3451                     ("cannot apply pragma% to non-local entity&#", E);
3452                end if;
3453
3454                E := Alias (E);
3455
3456             elsif Nkind_In (Parent (E), N_Full_Type_Declaration,
3457                                         N_Private_Extension_Declaration)
3458               and then Scope (E) = Scope (Alias (E))
3459             then
3460                E := Alias (E);
3461
3462                --  Return the parent subprogram the entity was inherited from
3463
3464                Ent := E;
3465             end if;
3466          end if;
3467
3468          --  Check that we are not applying this to a specless body
3469
3470          if Is_Subprogram (E)
3471            and then Nkind (Parent (Declaration_Node (E))) = N_Subprogram_Body
3472          then
3473             Error_Pragma
3474               ("pragma% requires separate spec and must come before body");
3475          end if;
3476
3477          --  Check that we are not applying this to a named constant
3478
3479          if Ekind_In (E, E_Named_Integer, E_Named_Real) then
3480             Error_Msg_Name_1 := Pname;
3481             Error_Msg_N
3482               ("cannot apply pragma% to named constant!",
3483                Get_Pragma_Arg (Arg2));
3484             Error_Pragma_Arg
3485               ("\supply appropriate type for&!", Arg2);
3486          end if;
3487
3488          if Ekind (E) = E_Enumeration_Literal then
3489             Error_Pragma ("enumeration literal not allowed for pragma%");
3490          end if;
3491
3492          --  Check for rep item appearing too early or too late
3493
3494          if Etype (E) = Any_Type
3495            or else Rep_Item_Too_Early (E, N)
3496          then
3497             raise Pragma_Exit;
3498
3499          elsif Present (Underlying_Type (E)) then
3500             E := Underlying_Type (E);
3501          end if;
3502
3503          if Rep_Item_Too_Late (E, N) then
3504             raise Pragma_Exit;
3505          end if;
3506
3507          if Has_Convention_Pragma (E) then
3508             Diagnose_Multiple_Pragmas (E);
3509
3510          elsif Convention (E) = Convention_Protected
3511            or else Ekind (Scope (E)) = E_Protected_Type
3512          then
3513             Error_Pragma_Arg
3514               ("a protected operation cannot be given a different convention",
3515                 Arg2);
3516          end if;
3517
3518          --  For Intrinsic, a subprogram is required
3519
3520          if C = Convention_Intrinsic
3521            and then not Is_Subprogram (E)
3522            and then not Is_Generic_Subprogram (E)
3523          then
3524             Error_Pragma_Arg
3525               ("second argument of pragma% must be a subprogram", Arg2);
3526          end if;
3527
3528          --  Stdcall case
3529
3530          if C = Convention_Stdcall then
3531
3532             --  A dispatching call is not allowed. A dispatching subprogram
3533             --  cannot be used to interface to the Win32 API, so in fact this
3534             --  check does not impose any effective restriction.
3535
3536             if Is_Dispatching_Operation (E) then
3537
3538                Error_Pragma
3539                  ("dispatching subprograms cannot use Stdcall convention");
3540
3541             --  Subprogram is allowed, but not a generic subprogram, and not a
3542             --  dispatching operation.
3543
3544             elsif not Is_Subprogram (E)
3545               and then not Is_Generic_Subprogram (E)
3546
3547               --  A variable is OK
3548
3549               and then Ekind (E) /= E_Variable
3550
3551               --  An access to subprogram is also allowed
3552
3553               and then not
3554                 (Is_Access_Type (E)
3555                   and then Ekind (Designated_Type (E)) = E_Subprogram_Type)
3556             then
3557                Error_Pragma_Arg
3558                  ("second argument of pragma% must be subprogram (type)",
3559                   Arg2);
3560             end if;
3561          end if;
3562
3563          if not Is_Subprogram (E)
3564            and then not Is_Generic_Subprogram (E)
3565          then
3566             Set_Convention_From_Pragma (E);
3567
3568             if Is_Type (E) then
3569                Check_First_Subtype (Arg2);
3570                Set_Convention_From_Pragma (Base_Type (E));
3571
3572                --  For subprograms, we must set the convention on the
3573                --  internally generated directly designated type as well.
3574
3575                if Ekind (E) = E_Access_Subprogram_Type then
3576                   Set_Convention_From_Pragma (Directly_Designated_Type (E));
3577                end if;
3578             end if;
3579
3580          --  For the subprogram case, set proper convention for all homonyms
3581          --  in same scope and the same declarative part, i.e. the same
3582          --  compilation unit.
3583
3584          else
3585             Comp_Unit := Get_Source_Unit (E);
3586             Set_Convention_From_Pragma (E);
3587
3588             --  Treat a pragma Import as an implicit body, for GPS use
3589
3590             if Prag_Id = Pragma_Import then
3591                Generate_Reference (E, Id, 'b');
3592             end if;
3593
3594             --  Loop through the homonyms of the pragma argument's entity
3595
3596             E1 := Ent;
3597             loop
3598                E1 := Homonym (E1);
3599                exit when No (E1) or else Scope (E1) /= Current_Scope;
3600
3601                --  Do not set the pragma on inherited operations or on formal
3602                --  subprograms.
3603
3604                if Comes_From_Source (E1)
3605                  and then Comp_Unit = Get_Source_Unit (E1)
3606                  and then not Is_Formal_Subprogram (E1)
3607                  and then Nkind (Original_Node (Parent (E1))) /=
3608                                                     N_Full_Type_Declaration
3609                then
3610                   if Present (Alias (E1))
3611                     and then Scope (E1) /= Scope (Alias (E1))
3612                   then
3613                      Error_Pragma_Ref
3614                        ("cannot apply pragma% to non-local entity& declared#",
3615                         E1);
3616                   end if;
3617
3618                   Set_Convention_From_Pragma (E1);
3619
3620                   if Prag_Id = Pragma_Import then
3621                      Generate_Reference (E1, Id, 'b');
3622                   end if;
3623                end if;
3624
3625                --  For aspect case, do NOT apply to homonyms
3626
3627                exit when From_Aspect_Specification (N);
3628             end loop;
3629          end if;
3630       end Process_Convention;
3631
3632       ----------------------------------------
3633       -- Process_Disable_Enable_Atomic_Sync --
3634       ----------------------------------------
3635
3636       procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id) is
3637       begin
3638          GNAT_Pragma;
3639          Check_No_Identifiers;
3640          Check_At_Most_N_Arguments (1);
3641
3642          --  Modeled internally as
3643          --    pragma Unsuppress (Atomic_Synchronization [,Entity])
3644
3645          Rewrite (N,
3646            Make_Pragma (Loc,
3647              Pragma_Identifier            =>
3648                Make_Identifier (Loc, Nam),
3649              Pragma_Argument_Associations => New_List (
3650                Make_Pragma_Argument_Association (Loc,
3651                  Expression =>
3652                    Make_Identifier (Loc, Name_Atomic_Synchronization)))));
3653
3654          if Present (Arg1) then
3655             Append_To (Pragma_Argument_Associations (N), New_Copy (Arg1));
3656          end if;
3657
3658          Analyze (N);
3659       end Process_Disable_Enable_Atomic_Sync;
3660
3661       -----------------------------------------------------
3662       -- Process_Extended_Import_Export_Exception_Pragma --
3663       -----------------------------------------------------
3664
3665       procedure Process_Extended_Import_Export_Exception_Pragma
3666         (Arg_Internal : Node_Id;
3667          Arg_External : Node_Id;
3668          Arg_Form     : Node_Id;
3669          Arg_Code     : Node_Id)
3670       is
3671          Def_Id   : Entity_Id;
3672          Code_Val : Uint;
3673
3674       begin
3675          if not OpenVMS_On_Target then
3676             Error_Pragma
3677               ("?pragma% ignored (applies only to Open'V'M'S)");
3678          end if;
3679
3680          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3681          Def_Id := Entity (Arg_Internal);
3682
3683          if Ekind (Def_Id) /= E_Exception then
3684             Error_Pragma_Arg
3685               ("pragma% must refer to declared exception", Arg_Internal);
3686          end if;
3687
3688          Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
3689
3690          if Present (Arg_Form) then
3691             Check_Arg_Is_One_Of (Arg_Form, Name_Ada, Name_VMS);
3692          end if;
3693
3694          if Present (Arg_Form)
3695            and then Chars (Arg_Form) = Name_Ada
3696          then
3697             null;
3698          else
3699             Set_Is_VMS_Exception (Def_Id);
3700             Set_Exception_Code (Def_Id, No_Uint);
3701          end if;
3702
3703          if Present (Arg_Code) then
3704             if not Is_VMS_Exception (Def_Id) then
3705                Error_Pragma_Arg
3706                  ("Code option for pragma% not allowed for Ada case",
3707                   Arg_Code);
3708             end if;
3709
3710             Check_Arg_Is_Static_Expression (Arg_Code, Any_Integer);
3711             Code_Val := Expr_Value (Arg_Code);
3712
3713             if not UI_Is_In_Int_Range (Code_Val) then
3714                Error_Pragma_Arg
3715                  ("Code option for pragma% must be in 32-bit range",
3716                   Arg_Code);
3717
3718             else
3719                Set_Exception_Code (Def_Id, Code_Val);
3720             end if;
3721          end if;
3722       end Process_Extended_Import_Export_Exception_Pragma;
3723
3724       -------------------------------------------------
3725       -- Process_Extended_Import_Export_Internal_Arg --
3726       -------------------------------------------------
3727
3728       procedure Process_Extended_Import_Export_Internal_Arg
3729         (Arg_Internal : Node_Id := Empty)
3730       is
3731       begin
3732          if No (Arg_Internal) then
3733             Error_Pragma ("Internal parameter required for pragma%");
3734          end if;
3735
3736          if Nkind (Arg_Internal) = N_Identifier then
3737             null;
3738
3739          elsif Nkind (Arg_Internal) = N_Operator_Symbol
3740            and then (Prag_Id = Pragma_Import_Function
3741                        or else
3742                      Prag_Id = Pragma_Export_Function)
3743          then
3744             null;
3745
3746          else
3747             Error_Pragma_Arg
3748               ("wrong form for Internal parameter for pragma%", Arg_Internal);
3749          end if;
3750
3751          Check_Arg_Is_Local_Name (Arg_Internal);
3752       end Process_Extended_Import_Export_Internal_Arg;
3753
3754       --------------------------------------------------
3755       -- Process_Extended_Import_Export_Object_Pragma --
3756       --------------------------------------------------
3757
3758       procedure Process_Extended_Import_Export_Object_Pragma
3759         (Arg_Internal : Node_Id;
3760          Arg_External : Node_Id;
3761          Arg_Size     : Node_Id)
3762       is
3763          Def_Id : Entity_Id;
3764
3765       begin
3766          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3767          Def_Id := Entity (Arg_Internal);
3768
3769          if not Ekind_In (Def_Id, E_Constant, E_Variable) then
3770             Error_Pragma_Arg
3771               ("pragma% must designate an object", Arg_Internal);
3772          end if;
3773
3774          if Has_Rep_Pragma (Def_Id, Name_Common_Object)
3775               or else
3776             Has_Rep_Pragma (Def_Id, Name_Psect_Object)
3777          then
3778             Error_Pragma_Arg
3779               ("previous Common/Psect_Object applies, pragma % not permitted",
3780                Arg_Internal);
3781          end if;
3782
3783          if Rep_Item_Too_Late (Def_Id, N) then
3784             raise Pragma_Exit;
3785          end if;
3786
3787          Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
3788
3789          if Present (Arg_Size) then
3790             Check_Arg_Is_External_Name (Arg_Size);
3791          end if;
3792
3793          --  Export_Object case
3794
3795          if Prag_Id = Pragma_Export_Object then
3796             if not Is_Library_Level_Entity (Def_Id) then
3797                Error_Pragma_Arg
3798                  ("argument for pragma% must be library level entity",
3799                   Arg_Internal);
3800             end if;
3801
3802             if Ekind (Current_Scope) = E_Generic_Package then
3803                Error_Pragma ("pragma& cannot appear in a generic unit");
3804             end if;
3805
3806             if not Size_Known_At_Compile_Time (Etype (Def_Id)) then
3807                Error_Pragma_Arg
3808                  ("exported object must have compile time known size",
3809                   Arg_Internal);
3810             end if;
3811
3812             if Warn_On_Export_Import and then Is_Exported (Def_Id) then
3813                Error_Msg_N ("?duplicate Export_Object pragma", N);
3814             else
3815                Set_Exported (Def_Id, Arg_Internal);
3816             end if;
3817
3818          --  Import_Object case
3819
3820          else
3821             if Is_Concurrent_Type (Etype (Def_Id)) then
3822                Error_Pragma_Arg
3823                  ("cannot use pragma% for task/protected object",
3824                   Arg_Internal);
3825             end if;
3826
3827             if Ekind (Def_Id) = E_Constant then
3828                Error_Pragma_Arg
3829                  ("cannot import a constant", Arg_Internal);
3830             end if;
3831
3832             if Warn_On_Export_Import
3833               and then Has_Discriminants (Etype (Def_Id))
3834             then
3835                Error_Msg_N
3836                  ("imported value must be initialized?", Arg_Internal);
3837             end if;
3838
3839             if Warn_On_Export_Import
3840               and then Is_Access_Type (Etype (Def_Id))
3841             then
3842                Error_Pragma_Arg
3843                  ("cannot import object of an access type?", Arg_Internal);
3844             end if;
3845
3846             if Warn_On_Export_Import
3847               and then Is_Imported (Def_Id)
3848             then
3849                Error_Msg_N
3850                  ("?duplicate Import_Object pragma", N);
3851
3852             --  Check for explicit initialization present. Note that an
3853             --  initialization generated by the code generator, e.g. for an
3854             --  access type, does not count here.
3855
3856             elsif Present (Expression (Parent (Def_Id)))
3857                and then
3858                  Comes_From_Source
3859                    (Original_Node (Expression (Parent (Def_Id))))
3860             then
3861                Error_Msg_Sloc := Sloc (Def_Id);
3862                Error_Pragma_Arg
3863                  ("imported entities cannot be initialized (RM B.1(24))",
3864                   "\no initialization allowed for & declared#", Arg1);
3865             else
3866                Set_Imported (Def_Id);
3867                Note_Possible_Modification (Arg_Internal, Sure => False);
3868             end if;
3869          end if;
3870       end Process_Extended_Import_Export_Object_Pragma;
3871
3872       ------------------------------------------------------
3873       -- Process_Extended_Import_Export_Subprogram_Pragma --
3874       ------------------------------------------------------
3875
3876       procedure Process_Extended_Import_Export_Subprogram_Pragma
3877         (Arg_Internal                 : Node_Id;
3878          Arg_External                 : Node_Id;
3879          Arg_Parameter_Types          : Node_Id;
3880          Arg_Result_Type              : Node_Id := Empty;
3881          Arg_Mechanism                : Node_Id;
3882          Arg_Result_Mechanism         : Node_Id := Empty;
3883          Arg_First_Optional_Parameter : Node_Id := Empty)
3884       is
3885          Ent       : Entity_Id;
3886          Def_Id    : Entity_Id;
3887          Hom_Id    : Entity_Id;
3888          Formal    : Entity_Id;
3889          Ambiguous : Boolean;
3890          Match     : Boolean;
3891          Dval      : Node_Id;
3892
3893          function Same_Base_Type
3894           (Ptype  : Node_Id;
3895            Formal : Entity_Id) return Boolean;
3896          --  Determines if Ptype references the type of Formal. Note that only
3897          --  the base types need to match according to the spec. Ptype here is
3898          --  the argument from the pragma, which is either a type name, or an
3899          --  access attribute.
3900
3901          --------------------
3902          -- Same_Base_Type --
3903          --------------------
3904
3905          function Same_Base_Type
3906            (Ptype  : Node_Id;
3907             Formal : Entity_Id) return Boolean
3908          is
3909             Ftyp : constant Entity_Id := Base_Type (Etype (Formal));
3910             Pref : Node_Id;
3911
3912          begin
3913             --  Case where pragma argument is typ'Access
3914
3915             if Nkind (Ptype) = N_Attribute_Reference
3916               and then Attribute_Name (Ptype) = Name_Access
3917             then
3918                Pref := Prefix (Ptype);
3919                Find_Type (Pref);
3920
3921                if not Is_Entity_Name (Pref)
3922                  or else Entity (Pref) = Any_Type
3923                then
3924                   raise Pragma_Exit;
3925                end if;
3926
3927                --  We have a match if the corresponding argument is of an
3928                --  anonymous access type, and its designated type matches the
3929                --  type of the prefix of the access attribute
3930
3931                return Ekind (Ftyp) = E_Anonymous_Access_Type
3932                  and then Base_Type (Entity (Pref)) =
3933                             Base_Type (Etype (Designated_Type (Ftyp)));
3934
3935             --  Case where pragma argument is a type name
3936
3937             else
3938                Find_Type (Ptype);
3939
3940                if not Is_Entity_Name (Ptype)
3941                  or else Entity (Ptype) = Any_Type
3942                then
3943                   raise Pragma_Exit;
3944                end if;
3945
3946                --  We have a match if the corresponding argument is of the type
3947                --  given in the pragma (comparing base types)
3948
3949                return Base_Type (Entity (Ptype)) = Ftyp;
3950             end if;
3951          end Same_Base_Type;
3952
3953       --  Start of processing for
3954       --  Process_Extended_Import_Export_Subprogram_Pragma
3955
3956       begin
3957          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3958          Ent := Empty;
3959          Ambiguous := False;
3960
3961          --  Loop through homonyms (overloadings) of the entity
3962
3963          Hom_Id := Entity (Arg_Internal);
3964          while Present (Hom_Id) loop
3965             Def_Id := Get_Base_Subprogram (Hom_Id);
3966
3967             --  We need a subprogram in the current scope
3968
3969             if not Is_Subprogram (Def_Id)
3970               or else Scope (Def_Id) /= Current_Scope
3971             then
3972                null;
3973
3974             else
3975                Match := True;
3976
3977                --  Pragma cannot apply to subprogram body
3978
3979                if Is_Subprogram (Def_Id)
3980                  and then Nkind (Parent (Declaration_Node (Def_Id))) =
3981                                                              N_Subprogram_Body
3982                then
3983                   Error_Pragma
3984                     ("pragma% requires separate spec"
3985                       & " and must come before body");
3986                end if;
3987
3988                --  Test result type if given, note that the result type
3989                --  parameter can only be present for the function cases.
3990
3991                if Present (Arg_Result_Type)
3992                  and then not Same_Base_Type (Arg_Result_Type, Def_Id)
3993                then
3994                   Match := False;
3995
3996                elsif Etype (Def_Id) /= Standard_Void_Type
3997                  and then
3998                    (Pname = Name_Export_Procedure
3999                       or else
4000                     Pname = Name_Import_Procedure)
4001                then
4002                   Match := False;
4003
4004                --  Test parameter types if given. Note that this parameter
4005                --  has not been analyzed (and must not be, since it is
4006                --  semantic nonsense), so we get it as the parser left it.
4007
4008                elsif Present (Arg_Parameter_Types) then
4009                   Check_Matching_Types : declare
4010                      Formal : Entity_Id;
4011                      Ptype  : Node_Id;
4012
4013                   begin
4014                      Formal := First_Formal (Def_Id);
4015
4016                      if Nkind (Arg_Parameter_Types) = N_Null then
4017                         if Present (Formal) then
4018                            Match := False;
4019                         end if;
4020
4021                      --  A list of one type, e.g. (List) is parsed as
4022                      --  a parenthesized expression.
4023
4024                      elsif Nkind (Arg_Parameter_Types) /= N_Aggregate
4025                        and then Paren_Count (Arg_Parameter_Types) = 1
4026                      then
4027                         if No (Formal)
4028                           or else Present (Next_Formal (Formal))
4029                         then
4030                            Match := False;
4031                         else
4032                            Match :=
4033                              Same_Base_Type (Arg_Parameter_Types, Formal);
4034                         end if;
4035
4036                      --  A list of more than one type is parsed as a aggregate
4037
4038                      elsif Nkind (Arg_Parameter_Types) = N_Aggregate
4039                        and then Paren_Count (Arg_Parameter_Types) = 0
4040                      then
4041                         Ptype := First (Expressions (Arg_Parameter_Types));
4042                         while Present (Ptype) or else Present (Formal) loop
4043                            if No (Ptype)
4044                              or else No (Formal)
4045                              or else not Same_Base_Type (Ptype, Formal)
4046                            then
4047                               Match := False;
4048                               exit;
4049                            else
4050                               Next_Formal (Formal);
4051                               Next (Ptype);
4052                            end if;
4053                         end loop;
4054
4055                      --  Anything else is of the wrong form
4056
4057                      else
4058                         Error_Pragma_Arg
4059                           ("wrong form for Parameter_Types parameter",
4060                            Arg_Parameter_Types);
4061                      end if;
4062                   end Check_Matching_Types;
4063                end if;
4064
4065                --  Match is now False if the entry we found did not match
4066                --  either a supplied Parameter_Types or Result_Types argument
4067
4068                if Match then
4069                   if No (Ent) then
4070                      Ent := Def_Id;
4071
4072                   --  Ambiguous case, the flag Ambiguous shows if we already
4073                   --  detected this and output the initial messages.
4074
4075                   else
4076                      if not Ambiguous then
4077                         Ambiguous := True;
4078                         Error_Msg_Name_1 := Pname;
4079                         Error_Msg_N
4080                           ("pragma% does not uniquely identify subprogram!",
4081                            N);
4082                         Error_Msg_Sloc := Sloc (Ent);
4083                         Error_Msg_N ("matching subprogram #!", N);
4084                         Ent := Empty;
4085                      end if;
4086
4087                      Error_Msg_Sloc := Sloc (Def_Id);
4088                      Error_Msg_N ("matching subprogram #!", N);
4089                   end if;
4090                end if;
4091             end if;
4092
4093             Hom_Id := Homonym (Hom_Id);
4094          end loop;
4095
4096          --  See if we found an entry
4097
4098          if No (Ent) then
4099             if not Ambiguous then
4100                if Is_Generic_Subprogram (Entity (Arg_Internal)) then
4101                   Error_Pragma
4102                     ("pragma% cannot be given for generic subprogram");
4103                else
4104                   Error_Pragma
4105                     ("pragma% does not identify local subprogram");
4106                end if;
4107             end if;
4108
4109             return;
4110          end if;
4111
4112          --  Import pragmas must be for imported entities
4113
4114          if Prag_Id = Pragma_Import_Function
4115               or else
4116             Prag_Id = Pragma_Import_Procedure
4117               or else
4118             Prag_Id = Pragma_Import_Valued_Procedure
4119          then
4120             if not Is_Imported (Ent) then
4121                Error_Pragma
4122                  ("pragma Import or Interface must precede pragma%");
4123             end if;
4124
4125          --  Here we have the Export case which can set the entity as exported
4126
4127          --  But does not do so if the specified external name is null, since
4128          --  that is taken as a signal in DEC Ada 83 (with which we want to be
4129          --  compatible) to request no external name.
4130
4131          elsif Nkind (Arg_External) = N_String_Literal
4132            and then String_Length (Strval (Arg_External)) = 0
4133          then
4134             null;
4135
4136          --  In all other cases, set entity as exported
4137
4138          else
4139             Set_Exported (Ent, Arg_Internal);
4140          end if;
4141
4142          --  Special processing for Valued_Procedure cases
4143
4144          if Prag_Id = Pragma_Import_Valued_Procedure
4145            or else
4146             Prag_Id = Pragma_Export_Valued_Procedure
4147          then
4148             Formal := First_Formal (Ent);
4149
4150             if No (Formal) then
4151                Error_Pragma ("at least one parameter required for pragma%");
4152
4153             elsif Ekind (Formal) /= E_Out_Parameter then
4154                Error_Pragma ("first parameter must have mode out for pragma%");
4155
4156             else
4157                Set_Is_Valued_Procedure (Ent);
4158             end if;
4159          end if;
4160
4161          Set_Extended_Import_Export_External_Name (Ent, Arg_External);
4162
4163          --  Process Result_Mechanism argument if present. We have already
4164          --  checked that this is only allowed for the function case.
4165
4166          if Present (Arg_Result_Mechanism) then
4167             Set_Mechanism_Value (Ent, Arg_Result_Mechanism);
4168          end if;
4169
4170          --  Process Mechanism parameter if present. Note that this parameter
4171          --  is not analyzed, and must not be analyzed since it is semantic
4172          --  nonsense, so we get it in exactly as the parser left it.
4173
4174          if Present (Arg_Mechanism) then
4175             declare
4176                Formal : Entity_Id;
4177                Massoc : Node_Id;
4178                Mname  : Node_Id;
4179                Choice : Node_Id;
4180
4181             begin
4182                --  A single mechanism association without a formal parameter
4183                --  name is parsed as a parenthesized expression. All other
4184                --  cases are parsed as aggregates, so we rewrite the single
4185                --  parameter case as an aggregate for consistency.
4186
4187                if Nkind (Arg_Mechanism) /= N_Aggregate
4188                  and then Paren_Count (Arg_Mechanism) = 1
4189                then
4190                   Rewrite (Arg_Mechanism,
4191                     Make_Aggregate (Sloc (Arg_Mechanism),
4192                       Expressions => New_List (
4193                         Relocate_Node (Arg_Mechanism))));
4194                end if;
4195
4196                --  Case of only mechanism name given, applies to all formals
4197
4198                if Nkind (Arg_Mechanism) /= N_Aggregate then
4199                   Formal := First_Formal (Ent);
4200                   while Present (Formal) loop
4201                      Set_Mechanism_Value (Formal, Arg_Mechanism);
4202                      Next_Formal (Formal);
4203                   end loop;
4204
4205                --  Case of list of mechanism associations given
4206
4207                else
4208                   if Null_Record_Present (Arg_Mechanism) then
4209                      Error_Pragma_Arg
4210                        ("inappropriate form for Mechanism parameter",
4211                         Arg_Mechanism);
4212                   end if;
4213
4214                   --  Deal with positional ones first
4215
4216                   Formal := First_Formal (Ent);
4217
4218                   if Present (Expressions (Arg_Mechanism)) then
4219                      Mname := First (Expressions (Arg_Mechanism));
4220                      while Present (Mname) loop
4221                         if No (Formal) then
4222                            Error_Pragma_Arg
4223                              ("too many mechanism associations", Mname);
4224                         end if;
4225
4226                         Set_Mechanism_Value (Formal, Mname);
4227                         Next_Formal (Formal);
4228                         Next (Mname);
4229                      end loop;
4230                   end if;
4231
4232                   --  Deal with named entries
4233
4234                   if Present (Component_Associations (Arg_Mechanism)) then
4235                      Massoc := First (Component_Associations (Arg_Mechanism));
4236                      while Present (Massoc) loop
4237                         Choice := First (Choices (Massoc));
4238
4239                         if Nkind (Choice) /= N_Identifier
4240                           or else Present (Next (Choice))
4241                         then
4242                            Error_Pragma_Arg
4243                              ("incorrect form for mechanism association",
4244                               Massoc);
4245                         end if;
4246
4247                         Formal := First_Formal (Ent);
4248                         loop
4249                            if No (Formal) then
4250                               Error_Pragma_Arg
4251                                 ("parameter name & not present", Choice);
4252                            end if;
4253
4254                            if Chars (Choice) = Chars (Formal) then
4255                               Set_Mechanism_Value
4256                                 (Formal, Expression (Massoc));
4257
4258                               --  Set entity on identifier (needed by ASIS)
4259
4260                               Set_Entity (Choice, Formal);
4261
4262                               exit;
4263                            end if;
4264
4265                            Next_Formal (Formal);
4266                         end loop;
4267
4268                         Next (Massoc);
4269                      end loop;
4270                   end if;
4271                end if;
4272             end;
4273          end if;
4274
4275          --  Process First_Optional_Parameter argument if present. We have
4276          --  already checked that this is only allowed for the Import case.
4277
4278          if Present (Arg_First_Optional_Parameter) then
4279             if Nkind (Arg_First_Optional_Parameter) /= N_Identifier then
4280                Error_Pragma_Arg
4281                  ("first optional parameter must be formal parameter name",
4282                   Arg_First_Optional_Parameter);
4283             end if;
4284
4285             Formal := First_Formal (Ent);
4286             loop
4287                if No (Formal) then
4288                   Error_Pragma_Arg
4289                     ("specified formal parameter& not found",
4290                      Arg_First_Optional_Parameter);
4291                end if;
4292
4293                exit when Chars (Formal) =
4294                          Chars (Arg_First_Optional_Parameter);
4295
4296                Next_Formal (Formal);
4297             end loop;
4298
4299             Set_First_Optional_Parameter (Ent, Formal);
4300
4301             --  Check specified and all remaining formals have right form
4302
4303             while Present (Formal) loop
4304                if Ekind (Formal) /= E_In_Parameter then
4305                   Error_Msg_NE
4306                     ("optional formal& is not of mode in!",
4307                      Arg_First_Optional_Parameter, Formal);
4308
4309                else
4310                   Dval := Default_Value (Formal);
4311
4312                   if No (Dval) then
4313                      Error_Msg_NE
4314                        ("optional formal& does not have default value!",
4315                         Arg_First_Optional_Parameter, Formal);
4316
4317                   elsif Compile_Time_Known_Value_Or_Aggr (Dval) then
4318                      null;
4319
4320                   else
4321                      Error_Msg_FE
4322                        ("default value for optional formal& is non-static!",
4323                         Arg_First_Optional_Parameter, Formal);
4324                   end if;
4325                end if;
4326
4327                Set_Is_Optional_Parameter (Formal);
4328                Next_Formal (Formal);
4329             end loop;
4330          end if;
4331       end Process_Extended_Import_Export_Subprogram_Pragma;
4332
4333       --------------------------
4334       -- Process_Generic_List --
4335       --------------------------
4336
4337       procedure Process_Generic_List is
4338          Arg : Node_Id;
4339          Exp : Node_Id;
4340
4341       begin
4342          Check_No_Identifiers;
4343          Check_At_Least_N_Arguments (1);
4344
4345          Arg := Arg1;
4346          while Present (Arg) loop
4347             Exp := Get_Pragma_Arg (Arg);
4348             Analyze (Exp);
4349
4350             if not Is_Entity_Name (Exp)
4351               or else
4352                 (not Is_Generic_Instance (Entity (Exp))
4353                   and then
4354                  not Is_Generic_Unit (Entity (Exp)))
4355             then
4356                Error_Pragma_Arg
4357                  ("pragma% argument must be name of generic unit/instance",
4358                   Arg);
4359             end if;
4360
4361             Next (Arg);
4362          end loop;
4363       end Process_Generic_List;
4364
4365       ------------------------------------
4366       -- Process_Import_Predefined_Type --
4367       ------------------------------------
4368
4369       procedure Process_Import_Predefined_Type is
4370          Loc  : constant Source_Ptr := Sloc (N);
4371          Elmt : Elmt_Id;
4372          Ftyp : Node_Id := Empty;
4373          Decl : Node_Id;
4374          Def  : Node_Id;
4375          Nam  : Name_Id;
4376
4377       begin
4378          String_To_Name_Buffer (Strval (Expression (Arg3)));
4379          Nam := Name_Find;
4380
4381          Elmt := First_Elmt (Predefined_Float_Types);
4382          while Present (Elmt) and then Chars (Node (Elmt)) /= Nam loop
4383             Next_Elmt (Elmt);
4384          end loop;
4385
4386          Ftyp := Node (Elmt);
4387
4388          if Present (Ftyp) then
4389
4390             --  Don't build a derived type declaration, because predefined C
4391             --  types have no declaration anywhere, so cannot really be named.
4392             --  Instead build a full type declaration, starting with an
4393             --  appropriate type definition is built
4394
4395             if Is_Floating_Point_Type (Ftyp) then
4396                Def := Make_Floating_Point_Definition (Loc,
4397                  Make_Integer_Literal (Loc, Digits_Value (Ftyp)),
4398                  Make_Real_Range_Specification (Loc,
4399                    Make_Real_Literal (Loc, Realval (Type_Low_Bound (Ftyp))),
4400                    Make_Real_Literal (Loc, Realval (Type_High_Bound (Ftyp)))));
4401
4402             --  Should never have a predefined type we cannot handle
4403
4404             else
4405                raise Program_Error;
4406             end if;
4407
4408             --  Build and insert a Full_Type_Declaration, which will be
4409             --  analyzed as soon as this list entry has been analyzed.
4410
4411             Decl := Make_Full_Type_Declaration (Loc,
4412               Make_Defining_Identifier (Loc, Chars (Expression (Arg2))),
4413               Type_Definition => Def);
4414
4415             Insert_After (N, Decl);
4416             Mark_Rewrite_Insertion (Decl);
4417
4418          else
4419             Error_Pragma_Arg ("no matching type found for pragma%",
4420             Arg2);
4421          end if;
4422       end Process_Import_Predefined_Type;
4423
4424       ---------------------------------
4425       -- Process_Import_Or_Interface --
4426       ---------------------------------
4427
4428       procedure Process_Import_Or_Interface is
4429          C      : Convention_Id;
4430          Def_Id : Entity_Id;
4431          Hom_Id : Entity_Id;
4432
4433       begin
4434          Process_Convention (C, Def_Id);
4435          Kill_Size_Check_Code (Def_Id);
4436          Note_Possible_Modification (Get_Pragma_Arg (Arg2), Sure => False);
4437
4438          if Ekind_In (Def_Id, E_Variable, E_Constant) then
4439
4440             --  We do not permit Import to apply to a renaming declaration
4441
4442             if Present (Renamed_Object (Def_Id)) then
4443                Error_Pragma_Arg
4444                  ("pragma% not allowed for object renaming", Arg2);
4445
4446             --  User initialization is not allowed for imported object, but
4447             --  the object declaration may contain a default initialization,
4448             --  that will be discarded. Note that an explicit initialization
4449             --  only counts if it comes from source, otherwise it is simply
4450             --  the code generator making an implicit initialization explicit.
4451
4452             elsif Present (Expression (Parent (Def_Id)))
4453               and then Comes_From_Source (Expression (Parent (Def_Id)))
4454             then
4455                Error_Msg_Sloc := Sloc (Def_Id);
4456                Error_Pragma_Arg
4457                  ("no initialization allowed for declaration of& #",
4458                   "\imported entities cannot be initialized (RM B.1(24))",
4459                   Arg2);
4460
4461             else
4462                Set_Imported (Def_Id);
4463                Process_Interface_Name (Def_Id, Arg3, Arg4);
4464
4465                --  Note that we do not set Is_Public here. That's because we
4466                --  only want to set it if there is no address clause, and we
4467                --  don't know that yet, so we delay that processing till
4468                --  freeze time.
4469
4470                --  pragma Import completes deferred constants
4471
4472                if Ekind (Def_Id) = E_Constant then
4473                   Set_Has_Completion (Def_Id);
4474                end if;
4475
4476                --  It is not possible to import a constant of an unconstrained
4477                --  array type (e.g. string) because there is no simple way to
4478                --  write a meaningful subtype for it.
4479
4480                if Is_Array_Type (Etype (Def_Id))
4481                  and then not Is_Constrained (Etype (Def_Id))
4482                then
4483                   Error_Msg_NE
4484                     ("imported constant& must have a constrained subtype",
4485                       N, Def_Id);
4486                end if;
4487             end if;
4488
4489          elsif Is_Subprogram (Def_Id)
4490            or else Is_Generic_Subprogram (Def_Id)
4491          then
4492             --  If the name is overloaded, pragma applies to all of the denoted
4493             --  entities in the same declarative part.
4494
4495             Hom_Id := Def_Id;
4496             while Present (Hom_Id) loop
4497                Def_Id := Get_Base_Subprogram (Hom_Id);
4498
4499                --  Ignore inherited subprograms because the pragma will apply
4500                --  to the parent operation, which is the one called.
4501
4502                if Is_Overloadable (Def_Id)
4503                  and then Present (Alias (Def_Id))
4504                then
4505                   null;
4506
4507                --  If it is not a subprogram, it must be in an outer scope and
4508                --  pragma does not apply.
4509
4510                elsif not Is_Subprogram (Def_Id)
4511                  and then not Is_Generic_Subprogram (Def_Id)
4512                then
4513                   null;
4514
4515                --  The pragma does not apply to primitives of interfaces
4516
4517                elsif Is_Dispatching_Operation (Def_Id)
4518                  and then Present (Find_Dispatching_Type (Def_Id))
4519                  and then Is_Interface (Find_Dispatching_Type (Def_Id))
4520                then
4521                   null;
4522
4523                --  Verify that the homonym is in the same declarative part (not
4524                --  just the same scope).
4525
4526                elsif Parent (Unit_Declaration_Node (Def_Id)) /= Parent (N)
4527                  and then Nkind (Parent (N)) /= N_Compilation_Unit_Aux
4528                then
4529                   exit;
4530
4531                else
4532                   Set_Imported (Def_Id);
4533
4534                   --  Reject an Import applied to an abstract subprogram
4535
4536                   if Is_Subprogram (Def_Id)
4537                     and then Is_Abstract_Subprogram (Def_Id)
4538                   then
4539                      Error_Msg_Sloc := Sloc (Def_Id);
4540                      Error_Msg_NE
4541                        ("cannot import abstract subprogram& declared#",
4542                         Arg2, Def_Id);
4543                   end if;
4544
4545                   --  Special processing for Convention_Intrinsic
4546
4547                   if C = Convention_Intrinsic then
4548
4549                      --  Link_Name argument not allowed for intrinsic
4550
4551                      Check_No_Link_Name;
4552
4553                      Set_Is_Intrinsic_Subprogram (Def_Id);
4554
4555                      --  If no external name is present, then check that this
4556                      --  is a valid intrinsic subprogram. If an external name
4557                      --  is present, then this is handled by the back end.
4558
4559                      if No (Arg3) then
4560                         Check_Intrinsic_Subprogram
4561                           (Def_Id, Get_Pragma_Arg (Arg2));
4562                      end if;
4563                   end if;
4564
4565                   --  All interfaced procedures need an external symbol created
4566                   --  for them since they are always referenced from another
4567                   --  object file.
4568
4569                   Set_Is_Public (Def_Id);
4570
4571                   --  Verify that the subprogram does not have a completion
4572                   --  through a renaming declaration. For other completions the
4573                   --  pragma appears as a too late representation.
4574
4575                   declare
4576                      Decl : constant Node_Id := Unit_Declaration_Node (Def_Id);
4577
4578                   begin
4579                      if Present (Decl)
4580                        and then Nkind (Decl) = N_Subprogram_Declaration
4581                        and then Present (Corresponding_Body (Decl))
4582                        and then Nkind (Unit_Declaration_Node
4583                                         (Corresponding_Body (Decl))) =
4584                                              N_Subprogram_Renaming_Declaration
4585                      then
4586                         Error_Msg_Sloc := Sloc (Def_Id);
4587                         Error_Msg_NE
4588                           ("cannot import&, renaming already provided for " &
4589                            "declaration #", N, Def_Id);
4590                      end if;
4591                   end;
4592
4593                   Set_Has_Completion (Def_Id);
4594                   Process_Interface_Name (Def_Id, Arg3, Arg4);
4595                end if;
4596
4597                if Is_Compilation_Unit (Hom_Id) then
4598
4599                   --  Its possible homonyms are not affected by the pragma.
4600                   --  Such homonyms might be present in the context of other
4601                   --  units being compiled.
4602
4603                   exit;
4604
4605                else
4606                   Hom_Id := Homonym (Hom_Id);
4607                end if;
4608             end loop;
4609
4610          --  When the convention is Java or CIL, we also allow Import to be
4611          --  given for packages, generic packages, exceptions, record
4612          --  components, and access to subprograms.
4613
4614          elsif (C = Convention_Java or else C = Convention_CIL)
4615            and then
4616              (Is_Package_Or_Generic_Package (Def_Id)
4617                or else Ekind (Def_Id) = E_Exception
4618                or else Ekind (Def_Id) = E_Access_Subprogram_Type
4619                or else Nkind (Parent (Def_Id)) = N_Component_Declaration)
4620          then
4621             Set_Imported (Def_Id);
4622             Set_Is_Public (Def_Id);
4623             Process_Interface_Name (Def_Id, Arg3, Arg4);
4624
4625          --  Import a CPP class
4626
4627          elsif C = Convention_CPP
4628            and then (Is_Record_Type (Def_Id)
4629                       or else Ekind (Def_Id) = E_Incomplete_Type)
4630          then
4631             if Ekind (Def_Id) = E_Incomplete_Type then
4632                if Present (Full_View (Def_Id)) then
4633                   Def_Id := Full_View (Def_Id);
4634
4635                else
4636                   Error_Msg_N
4637                     ("cannot import 'C'P'P type before full declaration seen",
4638                      Get_Pragma_Arg (Arg2));
4639
4640                   --  Although we have reported the error we decorate it as
4641                   --  CPP_Class to avoid reporting spurious errors
4642
4643                   Set_Is_CPP_Class (Def_Id);
4644                   return;
4645                end if;
4646             end if;
4647
4648             --  Types treated as CPP classes must be declared limited (note:
4649             --  this used to be a warning but there is no real benefit to it
4650             --  since we did effectively intend to treat the type as limited
4651             --  anyway).
4652
4653             if not Is_Limited_Type (Def_Id) then
4654                Error_Msg_N
4655                  ("imported 'C'P'P type must be limited",
4656                   Get_Pragma_Arg (Arg2));
4657             end if;
4658
4659             Set_Is_CPP_Class (Def_Id);
4660
4661             --  Imported CPP types must not have discriminants (because C++
4662             --  classes do not have discriminants).
4663
4664             if Has_Discriminants (Def_Id) then
4665                Error_Msg_N
4666                  ("imported 'C'P'P type cannot have discriminants",
4667                   First (Discriminant_Specifications
4668                           (Declaration_Node (Def_Id))));
4669             end if;
4670
4671             --  Check that components of imported CPP types do not have default
4672             --  expressions. For private types this check is performed when the
4673             --  full view is analyzed (see Process_Full_View).
4674
4675             if not Is_Private_Type (Def_Id) then
4676                Check_CPP_Type_Has_No_Defaults (Def_Id);
4677             end if;
4678
4679          elsif Nkind (Parent (Def_Id)) = N_Incomplete_Type_Declaration then
4680             Check_No_Link_Name;
4681             Check_Arg_Count (3);
4682             Check_Arg_Is_Static_Expression (Arg3, Standard_String);
4683
4684             Process_Import_Predefined_Type;
4685
4686          else
4687             Error_Pragma_Arg
4688               ("second argument of pragma% must be object, subprogram "
4689                & "or incomplete type",
4690                Arg2);
4691          end if;
4692
4693          --  If this pragma applies to a compilation unit, then the unit, which
4694          --  is a subprogram, does not require (or allow) a body. We also do
4695          --  not need to elaborate imported procedures.
4696
4697          if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
4698             declare
4699                Cunit : constant Node_Id := Parent (Parent (N));
4700             begin
4701                Set_Body_Required (Cunit, False);
4702             end;
4703          end if;
4704       end Process_Import_Or_Interface;
4705
4706       --------------------
4707       -- Process_Inline --
4708       --------------------
4709
4710       procedure Process_Inline (Active : Boolean) is
4711          Assoc     : Node_Id;
4712          Decl      : Node_Id;
4713          Subp_Id   : Node_Id;
4714          Subp      : Entity_Id;
4715          Applies   : Boolean;
4716
4717          Effective : Boolean := False;
4718          --  Set True if inline has some effect, i.e. if there is at least one
4719          --  subprogram set as inlined as a result of the use of the pragma.
4720
4721          procedure Make_Inline (Subp : Entity_Id);
4722          --  Subp is the defining unit name of the subprogram declaration. Set
4723          --  the flag, as well as the flag in the corresponding body, if there
4724          --  is one present.
4725
4726          procedure Set_Inline_Flags (Subp : Entity_Id);
4727          --  Sets Is_Inlined and Has_Pragma_Inline flags for Subp and also
4728          --  Has_Pragma_Inline_Always for the Inline_Always case.
4729
4730          function Inlining_Not_Possible (Subp : Entity_Id) return Boolean;
4731          --  Returns True if it can be determined at this stage that inlining
4732          --  is not possible, for example if the body is available and contains
4733          --  exception handlers, we prevent inlining, since otherwise we can
4734          --  get undefined symbols at link time. This function also emits a
4735          --  warning if front-end inlining is enabled and the pragma appears
4736          --  too late.
4737          --
4738          --  ??? is business with link symbols still valid, or does it relate
4739          --  to front end ZCX which is being phased out ???
4740
4741          ---------------------------
4742          -- Inlining_Not_Possible --
4743          ---------------------------
4744
4745          function Inlining_Not_Possible (Subp : Entity_Id) return Boolean is
4746             Decl  : constant Node_Id := Unit_Declaration_Node (Subp);
4747             Stats : Node_Id;
4748
4749          begin
4750             if Nkind (Decl) = N_Subprogram_Body then
4751                Stats := Handled_Statement_Sequence (Decl);
4752                return Present (Exception_Handlers (Stats))
4753                  or else Present (At_End_Proc (Stats));
4754
4755             elsif Nkind (Decl) = N_Subprogram_Declaration
4756               and then Present (Corresponding_Body (Decl))
4757             then
4758                if Front_End_Inlining
4759                  and then Analyzed (Corresponding_Body (Decl))
4760                then
4761                   Error_Msg_N ("pragma appears too late, ignored?", N);
4762                   return True;
4763
4764                --  If the subprogram is a renaming as body, the body is just a
4765                --  call to the renamed subprogram, and inlining is trivially
4766                --  possible.
4767
4768                elsif
4769                  Nkind (Unit_Declaration_Node (Corresponding_Body (Decl))) =
4770                                              N_Subprogram_Renaming_Declaration
4771                then
4772                   return False;
4773
4774                else
4775                   Stats :=
4776                     Handled_Statement_Sequence
4777                         (Unit_Declaration_Node (Corresponding_Body (Decl)));
4778
4779                   return
4780                     Present (Exception_Handlers (Stats))
4781                       or else Present (At_End_Proc (Stats));
4782                end if;
4783
4784             else
4785                --  If body is not available, assume the best, the check is
4786                --  performed again when compiling enclosing package bodies.
4787
4788                return False;
4789             end if;
4790          end Inlining_Not_Possible;
4791
4792          -----------------
4793          -- Make_Inline --
4794          -----------------
4795
4796          procedure Make_Inline (Subp : Entity_Id) is
4797             Kind       : constant Entity_Kind := Ekind (Subp);
4798             Inner_Subp : Entity_Id   := Subp;
4799
4800          begin
4801             --  Ignore if bad type, avoid cascaded error
4802
4803             if Etype (Subp) = Any_Type then
4804                Applies := True;
4805                return;
4806
4807             --  Ignore if all inlining is suppressed
4808
4809             elsif Suppress_All_Inlining then
4810                Applies := True;
4811                return;
4812
4813             --  If inlining is not possible, for now do not treat as an error
4814
4815             elsif Inlining_Not_Possible (Subp) then
4816                Applies := True;
4817                return;
4818
4819             --  Here we have a candidate for inlining, but we must exclude
4820             --  derived operations. Otherwise we would end up trying to inline
4821             --  a phantom declaration, and the result would be to drag in a
4822             --  body which has no direct inlining associated with it. That
4823             --  would not only be inefficient but would also result in the
4824             --  backend doing cross-unit inlining in cases where it was
4825             --  definitely inappropriate to do so.
4826
4827             --  However, a simple Comes_From_Source test is insufficient, since
4828             --  we do want to allow inlining of generic instances which also do
4829             --  not come from source. We also need to recognize specs generated
4830             --  by the front-end for bodies that carry the pragma. Finally,
4831             --  predefined operators do not come from source but are not
4832             --  inlineable either.
4833
4834             elsif Is_Generic_Instance (Subp)
4835               or else Nkind (Parent (Parent (Subp))) = N_Subprogram_Declaration
4836             then
4837                null;
4838
4839             elsif not Comes_From_Source (Subp)
4840               and then Scope (Subp) /= Standard_Standard
4841             then
4842                Applies := True;
4843                return;
4844             end if;
4845
4846             --  The referenced entity must either be the enclosing entity, or
4847             --  an entity declared within the current open scope.
4848
4849             if Present (Scope (Subp))
4850               and then Scope (Subp) /= Current_Scope
4851               and then Subp /= Current_Scope
4852             then
4853                Error_Pragma_Arg
4854                  ("argument of% must be entity in current scope", Assoc);
4855                return;
4856             end if;
4857
4858             --  Processing for procedure, operator or function. If subprogram
4859             --  is aliased (as for an instance) indicate that the renamed
4860             --  entity (if declared in the same unit) is inlined.
4861
4862             if Is_Subprogram (Subp) then
4863                Inner_Subp := Ultimate_Alias (Inner_Subp);
4864
4865                if In_Same_Source_Unit (Subp, Inner_Subp) then
4866                   Set_Inline_Flags (Inner_Subp);
4867
4868                   Decl := Parent (Parent (Inner_Subp));
4869
4870                   if Nkind (Decl) = N_Subprogram_Declaration
4871                     and then Present (Corresponding_Body (Decl))
4872                   then
4873                      Set_Inline_Flags (Corresponding_Body (Decl));
4874
4875                   elsif Is_Generic_Instance (Subp) then
4876
4877                      --  Indicate that the body needs to be created for
4878                      --  inlining subsequent calls. The instantiation node
4879                      --  follows the declaration of the wrapper package
4880                      --  created for it.
4881
4882                      if Scope (Subp) /= Standard_Standard
4883                        and then
4884                          Need_Subprogram_Instance_Body
4885                           (Next (Unit_Declaration_Node (Scope (Alias (Subp)))),
4886                               Subp)
4887                      then
4888                         null;
4889                      end if;
4890
4891                   --  Inline is a program unit pragma (RM 10.1.5) and cannot
4892                   --  appear in a formal part to apply to a formal subprogram.
4893                   --  Do not apply check within an instance or a formal package
4894                   --  the test will have been applied to the original generic.
4895
4896                   elsif Nkind (Decl) in N_Formal_Subprogram_Declaration
4897                     and then List_Containing (Decl) = List_Containing (N)
4898                     and then not In_Instance
4899                   then
4900                      Error_Msg_N
4901                        ("Inline cannot apply to a formal subprogram", N);
4902                   end if;
4903                end if;
4904
4905                Applies := True;
4906
4907             --  For a generic subprogram set flag as well, for use at the point
4908             --  of instantiation, to determine whether the body should be
4909             --  generated.
4910
4911             elsif Is_Generic_Subprogram (Subp) then
4912                Set_Inline_Flags (Subp);
4913                Applies := True;
4914
4915             --  Literals are by definition inlined
4916
4917             elsif Kind = E_Enumeration_Literal then
4918                null;
4919
4920             --  Anything else is an error
4921
4922             else
4923                Error_Pragma_Arg
4924                  ("expect subprogram name for pragma%", Assoc);
4925             end if;
4926          end Make_Inline;
4927
4928          ----------------------
4929          -- Set_Inline_Flags --
4930          ----------------------
4931
4932          procedure Set_Inline_Flags (Subp : Entity_Id) is
4933          begin
4934             if Active then
4935                Set_Is_Inlined (Subp);
4936             end if;
4937
4938             if not Has_Pragma_Inline (Subp) then
4939                Set_Has_Pragma_Inline (Subp);
4940                Effective := True;
4941             end if;
4942
4943             if Prag_Id = Pragma_Inline_Always then
4944                Set_Has_Pragma_Inline_Always (Subp);
4945             end if;
4946          end Set_Inline_Flags;
4947
4948       --  Start of processing for Process_Inline
4949
4950       begin
4951          Check_No_Identifiers;
4952          Check_At_Least_N_Arguments (1);
4953
4954          if Active then
4955             Inline_Processing_Required := True;
4956          end if;
4957
4958          Assoc := Arg1;
4959          while Present (Assoc) loop
4960             Subp_Id := Get_Pragma_Arg (Assoc);
4961             Analyze (Subp_Id);
4962             Applies := False;
4963
4964             if Is_Entity_Name (Subp_Id) then
4965                Subp := Entity (Subp_Id);
4966
4967                if Subp = Any_Id then
4968
4969                   --  If previous error, avoid cascaded errors
4970
4971                   Applies := True;
4972                   Effective := True;
4973
4974                else
4975                   Make_Inline (Subp);
4976
4977                   --  For the pragma case, climb homonym chain. This is
4978                   --  what implements allowing the pragma in the renaming
4979                   --  case, with the result applying to the ancestors, and
4980                   --  also allows Inline to apply to all previous homonyms.
4981
4982                   if not From_Aspect_Specification (N) then
4983                      while Present (Homonym (Subp))
4984                        and then Scope (Homonym (Subp)) = Current_Scope
4985                      loop
4986                         Make_Inline (Homonym (Subp));
4987                         Subp := Homonym (Subp);
4988                      end loop;
4989                   end if;
4990                end if;
4991             end if;
4992
4993             if not Applies then
4994                Error_Pragma_Arg
4995                  ("inappropriate argument for pragma%", Assoc);
4996
4997             elsif not Effective
4998               and then Warn_On_Redundant_Constructs
4999               and then not Suppress_All_Inlining
5000             then
5001                if Inlining_Not_Possible (Subp) then
5002                   Error_Msg_NE
5003                     ("pragma Inline for& is ignored?", N, Entity (Subp_Id));
5004                else
5005                   Error_Msg_NE
5006                     ("pragma Inline for& is redundant?", N, Entity (Subp_Id));
5007                end if;
5008             end if;
5009
5010             Next (Assoc);
5011          end loop;
5012       end Process_Inline;
5013
5014       ----------------------------
5015       -- Process_Interface_Name --
5016       ----------------------------
5017
5018       procedure Process_Interface_Name
5019         (Subprogram_Def : Entity_Id;
5020          Ext_Arg        : Node_Id;
5021          Link_Arg       : Node_Id)
5022       is
5023          Ext_Nam    : Node_Id;
5024          Link_Nam   : Node_Id;
5025          String_Val : String_Id;
5026
5027          procedure Check_Form_Of_Interface_Name
5028            (SN            : Node_Id;
5029             Ext_Name_Case : Boolean);
5030          --  SN is a string literal node for an interface name. This routine
5031          --  performs some minimal checks that the name is reasonable. In
5032          --  particular that no spaces or other obviously incorrect characters
5033          --  appear. This is only a warning, since any characters are allowed.
5034          --  Ext_Name_Case is True for an External_Name, False for a Link_Name.
5035
5036          ----------------------------------
5037          -- Check_Form_Of_Interface_Name --
5038          ----------------------------------
5039
5040          procedure Check_Form_Of_Interface_Name
5041            (SN            : Node_Id;
5042             Ext_Name_Case : Boolean)
5043          is
5044             S  : constant String_Id := Strval (Expr_Value_S (SN));
5045             SL : constant Nat       := String_Length (S);
5046             C  : Char_Code;
5047
5048          begin
5049             if SL = 0 then
5050                Error_Msg_N ("interface name cannot be null string", SN);
5051             end if;
5052
5053             for J in 1 .. SL loop
5054                C := Get_String_Char (S, J);
5055
5056                --  Look for dubious character and issue unconditional warning.
5057                --  Definitely dubious if not in character range.
5058
5059                if not In_Character_Range (C)
5060
5061                   --  For all cases except CLI target,
5062                   --  commas, spaces and slashes are dubious (in CLI, we use
5063                   --  commas and backslashes in external names to specify
5064                   --  assembly version and public key, while slashes and spaces
5065                   --  can be used in names to mark nested classes and
5066                   --  valuetypes).
5067
5068                   or else ((not Ext_Name_Case or else VM_Target /= CLI_Target)
5069                              and then (Get_Character (C) = ','
5070                                          or else
5071                                        Get_Character (C) = '\'))
5072                  or else (VM_Target /= CLI_Target
5073                             and then (Get_Character (C) = ' '
5074                                         or else
5075                                       Get_Character (C) = '/'))
5076                then
5077                   Error_Msg
5078                     ("?interface name contains illegal character",
5079                      Sloc (SN) + Source_Ptr (J));
5080                end if;
5081             end loop;
5082          end Check_Form_Of_Interface_Name;
5083
5084       --  Start of processing for Process_Interface_Name
5085
5086       begin
5087          if No (Link_Arg) then
5088             if No (Ext_Arg) then
5089                if VM_Target = CLI_Target
5090                  and then Ekind (Subprogram_Def) = E_Package
5091                  and then Nkind (Parent (Subprogram_Def)) =
5092                                                  N_Package_Specification
5093                  and then Present (Generic_Parent (Parent (Subprogram_Def)))
5094                then
5095                   Set_Interface_Name
5096                      (Subprogram_Def,
5097                       Interface_Name
5098                         (Generic_Parent (Parent (Subprogram_Def))));
5099                end if;
5100
5101                return;
5102
5103             elsif Chars (Ext_Arg) = Name_Link_Name then
5104                Ext_Nam  := Empty;
5105                Link_Nam := Expression (Ext_Arg);
5106
5107             else
5108                Check_Optional_Identifier (Ext_Arg, Name_External_Name);
5109                Ext_Nam  := Expression (Ext_Arg);
5110                Link_Nam := Empty;
5111             end if;
5112
5113          else
5114             Check_Optional_Identifier (Ext_Arg,  Name_External_Name);
5115             Check_Optional_Identifier (Link_Arg, Name_Link_Name);
5116             Ext_Nam  := Expression (Ext_Arg);
5117             Link_Nam := Expression (Link_Arg);
5118          end if;
5119
5120          --  Check expressions for external name and link name are static
5121
5122          if Present (Ext_Nam) then
5123             Check_Arg_Is_Static_Expression (Ext_Nam, Standard_String);
5124             Check_Form_Of_Interface_Name (Ext_Nam, Ext_Name_Case => True);
5125
5126             --  Verify that external name is not the name of a local entity,
5127             --  which would hide the imported one and could lead to run-time
5128             --  surprises. The problem can only arise for entities declared in
5129             --  a package body (otherwise the external name is fully qualified
5130             --  and will not conflict).
5131
5132             declare
5133                Nam : Name_Id;
5134                E   : Entity_Id;
5135                Par : Node_Id;
5136
5137             begin
5138                if Prag_Id = Pragma_Import then
5139                   String_To_Name_Buffer (Strval (Expr_Value_S (Ext_Nam)));
5140                   Nam := Name_Find;
5141                   E   := Entity_Id (Get_Name_Table_Info (Nam));
5142
5143                   if Nam /= Chars (Subprogram_Def)
5144                     and then Present (E)
5145                     and then not Is_Overloadable (E)
5146                     and then Is_Immediately_Visible (E)
5147                     and then not Is_Imported (E)
5148                     and then Ekind (Scope (E)) = E_Package
5149                   then
5150                      Par := Parent (E);
5151                      while Present (Par) loop
5152                         if Nkind (Par) = N_Package_Body then
5153                            Error_Msg_Sloc := Sloc (E);
5154                            Error_Msg_NE
5155                              ("imported entity is hidden by & declared#",
5156                               Ext_Arg, E);
5157                            exit;
5158                         end if;
5159
5160                         Par := Parent (Par);
5161                      end loop;
5162                   end if;
5163                end if;
5164             end;
5165          end if;
5166
5167          if Present (Link_Nam) then
5168             Check_Arg_Is_Static_Expression (Link_Nam, Standard_String);
5169             Check_Form_Of_Interface_Name (Link_Nam, Ext_Name_Case => False);
5170          end if;
5171
5172          --  If there is no link name, just set the external name
5173
5174          if No (Link_Nam) then
5175             Link_Nam := Adjust_External_Name_Case (Expr_Value_S (Ext_Nam));
5176
5177          --  For the Link_Name case, the given literal is preceded by an
5178          --  asterisk, which indicates to GCC that the given name should be
5179          --  taken literally, and in particular that no prepending of
5180          --  underlines should occur, even in systems where this is the
5181          --  normal default.
5182
5183          else
5184             Start_String;
5185
5186             if VM_Target = No_VM then
5187                Store_String_Char (Get_Char_Code ('*'));
5188             end if;
5189
5190             String_Val := Strval (Expr_Value_S (Link_Nam));
5191             Store_String_Chars (String_Val);
5192             Link_Nam :=
5193               Make_String_Literal (Sloc (Link_Nam),
5194                 Strval => End_String);
5195          end if;
5196
5197          --  Set the interface name. If the entity is a generic instance, use
5198          --  its alias, which is the callable entity.
5199
5200          if Is_Generic_Instance (Subprogram_Def) then
5201             Set_Encoded_Interface_Name
5202               (Alias (Get_Base_Subprogram (Subprogram_Def)), Link_Nam);
5203          else
5204             Set_Encoded_Interface_Name
5205               (Get_Base_Subprogram (Subprogram_Def), Link_Nam);
5206          end if;
5207
5208          --  We allow duplicated export names in CIL/Java, as they are always
5209          --  enclosed in a namespace that differentiates them, and overloaded
5210          --  entities are supported by the VM.
5211
5212          if Convention (Subprogram_Def) /= Convention_CIL
5213               and then
5214             Convention (Subprogram_Def) /= Convention_Java
5215          then
5216             Check_Duplicated_Export_Name (Link_Nam);
5217          end if;
5218       end Process_Interface_Name;
5219
5220       -----------------------------------------
5221       -- Process_Interrupt_Or_Attach_Handler --
5222       -----------------------------------------
5223
5224       procedure Process_Interrupt_Or_Attach_Handler is
5225          Arg1_X       : constant Node_Id   := Get_Pragma_Arg (Arg1);
5226          Handler_Proc : constant Entity_Id := Entity (Arg1_X);
5227          Proc_Scope   : constant Entity_Id := Scope (Handler_Proc);
5228
5229       begin
5230          Set_Is_Interrupt_Handler (Handler_Proc);
5231
5232          --  If the pragma is not associated with a handler procedure within a
5233          --  protected type, then it must be for a nonprotected procedure for
5234          --  the AAMP target, in which case we don't associate a representation
5235          --  item with the procedure's scope.
5236
5237          if Ekind (Proc_Scope) = E_Protected_Type then
5238             if Prag_Id = Pragma_Interrupt_Handler
5239                  or else
5240                Prag_Id = Pragma_Attach_Handler
5241             then
5242                Record_Rep_Item (Proc_Scope, N);
5243             end if;
5244          end if;
5245       end Process_Interrupt_Or_Attach_Handler;
5246
5247       --------------------------------------------------
5248       -- Process_Restrictions_Or_Restriction_Warnings --
5249       --------------------------------------------------
5250
5251       --  Note: some of the simple identifier cases were handled in par-prag,
5252       --  but it is harmless (and more straightforward) to simply handle all
5253       --  cases here, even if it means we repeat a bit of work in some cases.
5254
5255       procedure Process_Restrictions_Or_Restriction_Warnings
5256         (Warn : Boolean)
5257       is
5258          Arg   : Node_Id;
5259          R_Id  : Restriction_Id;
5260          Id    : Name_Id;
5261          Expr  : Node_Id;
5262          Val   : Uint;
5263
5264          procedure Check_Unit_Name (N : Node_Id);
5265          --  Checks unit name parameter for No_Dependence. Returns if it has
5266          --  an appropriate form, otherwise raises pragma argument error.
5267
5268          ---------------------
5269          -- Check_Unit_Name --
5270          ---------------------
5271
5272          procedure Check_Unit_Name (N : Node_Id) is
5273          begin
5274             if Nkind (N) = N_Selected_Component then
5275                Check_Unit_Name (Prefix (N));
5276                Check_Unit_Name (Selector_Name (N));
5277
5278             elsif Nkind (N) = N_Identifier then
5279                return;
5280
5281             else
5282                Error_Pragma_Arg
5283                  ("wrong form for unit name for No_Dependence", N);
5284             end if;
5285          end Check_Unit_Name;
5286
5287       --  Start of processing for Process_Restrictions_Or_Restriction_Warnings
5288
5289       begin
5290          --  Ignore all Restrictions pragma in CodePeer mode
5291
5292          if CodePeer_Mode then
5293             return;
5294          end if;
5295
5296          Check_Ada_83_Warning;
5297          Check_At_Least_N_Arguments (1);
5298          Check_Valid_Configuration_Pragma;
5299
5300          Arg := Arg1;
5301          while Present (Arg) loop
5302             Id := Chars (Arg);
5303             Expr := Get_Pragma_Arg (Arg);
5304
5305             --  Case of no restriction identifier present
5306
5307             if Id = No_Name then
5308                if Nkind (Expr) /= N_Identifier then
5309                   Error_Pragma_Arg
5310                     ("invalid form for restriction", Arg);
5311                end if;
5312
5313                R_Id :=
5314                  Get_Restriction_Id
5315                    (Process_Restriction_Synonyms (Expr));
5316
5317                if R_Id not in All_Boolean_Restrictions then
5318                   Error_Msg_Name_1 := Pname;
5319                   Error_Msg_N
5320                     ("invalid restriction identifier&", Get_Pragma_Arg (Arg));
5321
5322                   --  Check for possible misspelling
5323
5324                   for J in Restriction_Id loop
5325                      declare
5326                         Rnm : constant String := Restriction_Id'Image (J);
5327
5328                      begin
5329                         Name_Buffer (1 .. Rnm'Length) := Rnm;
5330                         Name_Len := Rnm'Length;
5331                         Set_Casing (All_Lower_Case);
5332
5333                         if Is_Bad_Spelling_Of (Chars (Expr), Name_Enter) then
5334                            Set_Casing
5335                              (Identifier_Casing (Current_Source_File));
5336                            Error_Msg_String (1 .. Rnm'Length) :=
5337                              Name_Buffer (1 .. Name_Len);
5338                            Error_Msg_Strlen := Rnm'Length;
5339                            Error_Msg_N -- CODEFIX
5340                              ("\possible misspelling of ""~""",
5341                               Get_Pragma_Arg (Arg));
5342                            exit;
5343                         end if;
5344                      end;
5345                   end loop;
5346
5347                   raise Pragma_Exit;
5348                end if;
5349
5350                if Implementation_Restriction (R_Id) then
5351                   Check_Restriction (No_Implementation_Restrictions, Arg);
5352                end if;
5353
5354                --  Special processing for No_Elaboration_Code restriction
5355
5356                if R_Id = No_Elaboration_Code then
5357
5358                   --  Restriction is only recognized within a configuration
5359                   --  pragma file, or within a unit of the main extended
5360                   --  program. Note: the test for Main_Unit is needed to
5361                   --  properly include the case of configuration pragma files.
5362
5363                   if not (Current_Sem_Unit = Main_Unit
5364                            or else In_Extended_Main_Source_Unit (N))
5365                   then
5366                      return;
5367
5368                   --  Don't allow in a subunit unless already specified in
5369                   --  body or spec.
5370
5371                   elsif Nkind (Parent (N)) = N_Compilation_Unit
5372                     and then Nkind (Unit (Parent (N))) = N_Subunit
5373                     and then not Restriction_Active (No_Elaboration_Code)
5374                   then
5375                      Error_Msg_N
5376                        ("invalid specification of ""No_Elaboration_Code""",
5377                         N);
5378                      Error_Msg_N
5379                        ("\restriction cannot be specified in a subunit", N);
5380                      Error_Msg_N
5381                        ("\unless also specified in body or spec", N);
5382                      return;
5383
5384                   --  If we have a No_Elaboration_Code pragma that we
5385                   --  accept, then it needs to be added to the configuration
5386                   --  restrcition set so that we get proper application to
5387                   --  other units in the main extended source as required.
5388
5389                   else
5390                      Add_To_Config_Boolean_Restrictions (No_Elaboration_Code);
5391                   end if;
5392                end if;
5393
5394                --  If this is a warning, then set the warning unless we already
5395                --  have a real restriction active (we never want a warning to
5396                --  override a real restriction).
5397
5398                if Warn then
5399                   if not Restriction_Active (R_Id) then
5400                      Set_Restriction (R_Id, N);
5401                      Restriction_Warnings (R_Id) := True;
5402                   end if;
5403
5404                --  If real restriction case, then set it and make sure that the
5405                --  restriction warning flag is off, since a real restriction
5406                --  always overrides a warning.
5407
5408                else
5409                   Set_Restriction (R_Id, N);
5410                   Restriction_Warnings (R_Id) := False;
5411                end if;
5412
5413                --  Check for obsolescent restrictions in Ada 2005 mode
5414
5415                if not Warn
5416                  and then Ada_Version >= Ada_2005
5417                  and then (R_Id = No_Asynchronous_Control
5418                             or else
5419                            R_Id = No_Unchecked_Deallocation
5420                             or else
5421                            R_Id = No_Unchecked_Conversion)
5422                then
5423                   Check_Restriction (No_Obsolescent_Features, N);
5424                end if;
5425
5426                --  A very special case that must be processed here: pragma
5427                --  Restrictions (No_Exceptions) turns off all run-time
5428                --  checking. This is a bit dubious in terms of the formal
5429                --  language definition, but it is what is intended by RM
5430                --  H.4(12). Restriction_Warnings never affects generated code
5431                --  so this is done only in the real restriction case.
5432
5433                --  Atomic_Synchronization is not a real check, so it is not
5434                --  affected by this processing).
5435
5436                if R_Id = No_Exceptions and then not Warn then
5437                   for J in Scope_Suppress'Range loop
5438                      if J /= Atomic_Synchronization then
5439                         Scope_Suppress (J) := True;
5440                      end if;
5441                   end loop;
5442                end if;
5443
5444             --  Case of No_Dependence => unit-name. Note that the parser
5445             --  already made the necessary entry in the No_Dependence table.
5446
5447             elsif Id = Name_No_Dependence then
5448                Check_Unit_Name (Expr);
5449
5450             --  Case of No_Specification_Of_Aspect => Identifier.
5451
5452             elsif Id = Name_No_Specification_Of_Aspect then
5453                declare
5454                   A_Id : Aspect_Id;
5455
5456                begin
5457                   if Nkind (Expr) /= N_Identifier then
5458                      A_Id := No_Aspect;
5459                   else
5460                      A_Id := Get_Aspect_Id (Chars (Expr));
5461                   end if;
5462
5463                   if A_Id = No_Aspect then
5464                      Error_Pragma_Arg ("invalid restriction name", Arg);
5465                   else
5466                      Set_Restriction_No_Specification_Of_Aspect (Expr, Warn);
5467                   end if;
5468                end;
5469
5470             --  All other cases of restriction identifier present
5471
5472             else
5473                R_Id := Get_Restriction_Id (Process_Restriction_Synonyms (Arg));
5474                Analyze_And_Resolve (Expr, Any_Integer);
5475
5476                if R_Id not in All_Parameter_Restrictions then
5477                   Error_Pragma_Arg
5478                     ("invalid restriction parameter identifier", Arg);
5479
5480                elsif not Is_OK_Static_Expression (Expr) then
5481                   Flag_Non_Static_Expr
5482                     ("value must be static expression!", Expr);
5483                   raise Pragma_Exit;
5484
5485                elsif not Is_Integer_Type (Etype (Expr))
5486                  or else Expr_Value (Expr) < 0
5487                then
5488                   Error_Pragma_Arg
5489                     ("value must be non-negative integer", Arg);
5490                end if;
5491
5492                --  Restriction pragma is active
5493
5494                Val := Expr_Value (Expr);
5495
5496                if not UI_Is_In_Int_Range (Val) then
5497                   Error_Pragma_Arg
5498                     ("pragma ignored, value too large?", Arg);
5499                end if;
5500
5501                --  Warning case. If the real restriction is active, then we
5502                --  ignore the request, since warning never overrides a real
5503                --  restriction. Otherwise we set the proper warning. Note that
5504                --  this circuit sets the warning again if it is already set,
5505                --  which is what we want, since the constant may have changed.
5506
5507                if Warn then
5508                   if not Restriction_Active (R_Id) then
5509                      Set_Restriction
5510                        (R_Id, N, Integer (UI_To_Int (Val)));
5511                      Restriction_Warnings (R_Id) := True;
5512                   end if;
5513
5514                --  Real restriction case, set restriction and make sure warning
5515                --  flag is off since real restriction always overrides warning.
5516
5517                else
5518                   Set_Restriction (R_Id, N, Integer (UI_To_Int (Val)));
5519                   Restriction_Warnings (R_Id) := False;
5520                end if;
5521             end if;
5522
5523             Next (Arg);
5524          end loop;
5525       end Process_Restrictions_Or_Restriction_Warnings;
5526
5527       ---------------------------------
5528       -- Process_Suppress_Unsuppress --
5529       ---------------------------------
5530
5531       --  Note: this procedure makes entries in the check suppress data
5532       --  structures managed by Sem. See spec of package Sem for full
5533       --  details on how we handle recording of check suppression.
5534
5535       procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean) is
5536          C    : Check_Id;
5537          E_Id : Node_Id;
5538          E    : Entity_Id;
5539
5540          In_Package_Spec : constant Boolean :=
5541                              Is_Package_Or_Generic_Package (Current_Scope)
5542                                and then not In_Package_Body (Current_Scope);
5543
5544          procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id);
5545          --  Used to suppress a single check on the given entity
5546
5547          --------------------------------
5548          -- Suppress_Unsuppress_Echeck --
5549          --------------------------------
5550
5551          procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id) is
5552          begin
5553             --  Check for error of trying to set atomic synchronization for
5554             --  a non-atomic variable.
5555
5556             if C = Atomic_Synchronization
5557               and then not (Is_Atomic (E) or else Has_Atomic_Components (E))
5558             then
5559                Error_Msg_N
5560                  ("pragma & requires atomic type or variable",
5561                   Pragma_Identifier (Original_Node (N)));
5562             end if;
5563
5564             Set_Checks_May_Be_Suppressed (E);
5565
5566             if In_Package_Spec then
5567                Push_Global_Suppress_Stack_Entry
5568                  (Entity   => E,
5569                   Check    => C,
5570                   Suppress => Suppress_Case);
5571             else
5572                Push_Local_Suppress_Stack_Entry
5573                  (Entity   => E,
5574                   Check    => C,
5575                   Suppress => Suppress_Case);
5576             end if;
5577
5578             --  If this is a first subtype, and the base type is distinct,
5579             --  then also set the suppress flags on the base type.
5580
5581             if Is_First_Subtype (E)
5582               and then Etype (E) /= E
5583             then
5584                Suppress_Unsuppress_Echeck (Etype (E), C);
5585             end if;
5586          end Suppress_Unsuppress_Echeck;
5587
5588       --  Start of processing for Process_Suppress_Unsuppress
5589
5590       begin
5591          --  Ignore pragma Suppress/Unsuppress in CodePeer and Alfa modes on
5592          --  user code: we want to generate checks for analysis purposes, as
5593          --  set respectively by -gnatC and -gnatd.F
5594
5595          if (CodePeer_Mode or Alfa_Mode)
5596            and then Comes_From_Source (N)
5597          then
5598             return;
5599          end if;
5600
5601          --  Suppress/Unsuppress can appear as a configuration pragma, or in a
5602          --  declarative part or a package spec (RM 11.5(5)).
5603
5604          if not Is_Configuration_Pragma then
5605             Check_Is_In_Decl_Part_Or_Package_Spec;
5606          end if;
5607
5608          Check_At_Least_N_Arguments (1);
5609          Check_At_Most_N_Arguments (2);
5610          Check_No_Identifier (Arg1);
5611          Check_Arg_Is_Identifier (Arg1);
5612
5613          C := Get_Check_Id (Chars (Get_Pragma_Arg (Arg1)));
5614
5615          if C = No_Check_Id then
5616             Error_Pragma_Arg
5617               ("argument of pragma% is not valid check name", Arg1);
5618          end if;
5619
5620          if not Suppress_Case
5621            and then (C = All_Checks or else C = Overflow_Check)
5622          then
5623             Opt.Overflow_Checks_Unsuppressed := True;
5624          end if;
5625
5626          if Arg_Count = 1 then
5627
5628             --  Make an entry in the local scope suppress table. This is the
5629             --  table that directly shows the current value of the scope
5630             --  suppress check for any check id value.
5631
5632             if C = All_Checks then
5633
5634                --  For All_Checks, we set all specific predefined checks with
5635                --  the exception of Elaboration_Check, which is handled
5636                --  specially because of not wanting All_Checks to have the
5637                --  effect of deactivating static elaboration order processing.
5638                --  Atomic_Synchronization is also not affected, since this is
5639                --  not a real check.
5640
5641                for J in Scope_Suppress'Range loop
5642                   if J /= Elaboration_Check
5643                     and then J /= Atomic_Synchronization
5644                   then
5645                      Scope_Suppress (J) := Suppress_Case;
5646                   end if;
5647                end loop;
5648
5649             --  If not All_Checks, and predefined check, then set appropriate
5650             --  scope entry. Note that we will set Elaboration_Check if this
5651             --  is explicitly specified. Atomic_Synchronization is allowed
5652             --  only if internally generated and entity is atomic.
5653
5654             elsif C in Predefined_Check_Id
5655               and then (not Comes_From_Source (N)
5656                          or else C /= Atomic_Synchronization)
5657             then
5658                Scope_Suppress (C) := Suppress_Case;
5659             end if;
5660
5661             --  Also make an entry in the Local_Entity_Suppress table
5662
5663             Push_Local_Suppress_Stack_Entry
5664               (Entity   => Empty,
5665                Check    => C,
5666                Suppress => Suppress_Case);
5667
5668          --  Case of two arguments present, where the check is suppressed for
5669          --  a specified entity (given as the second argument of the pragma)
5670
5671          else
5672             --  This is obsolescent in Ada 2005 mode
5673
5674             if Ada_Version >= Ada_2005 then
5675                Check_Restriction (No_Obsolescent_Features, Arg2);
5676             end if;
5677
5678             Check_Optional_Identifier (Arg2, Name_On);
5679             E_Id := Get_Pragma_Arg (Arg2);
5680             Analyze (E_Id);
5681
5682             if not Is_Entity_Name (E_Id) then
5683                Error_Pragma_Arg
5684                  ("second argument of pragma% must be entity name", Arg2);
5685             end if;
5686
5687             E := Entity (E_Id);
5688
5689             if E = Any_Id then
5690                return;
5691             end if;
5692
5693             --  Enforce RM 11.5(7) which requires that for a pragma that
5694             --  appears within a package spec, the named entity must be
5695             --  within the package spec. We allow the package name itself
5696             --  to be mentioned since that makes sense, although it is not
5697             --  strictly allowed by 11.5(7).
5698
5699             if In_Package_Spec
5700               and then E /= Current_Scope
5701               and then Scope (E) /= Current_Scope
5702             then
5703                Error_Pragma_Arg
5704                  ("entity in pragma% is not in package spec (RM 11.5(7))",
5705                   Arg2);
5706             end if;
5707
5708             --  Loop through homonyms. As noted below, in the case of a package
5709             --  spec, only homonyms within the package spec are considered.
5710
5711             loop
5712                Suppress_Unsuppress_Echeck (E, C);
5713
5714                if Is_Generic_Instance (E)
5715                  and then Is_Subprogram (E)
5716                  and then Present (Alias (E))
5717                then
5718                   Suppress_Unsuppress_Echeck (Alias (E), C);
5719                end if;
5720
5721                --  Move to next homonym if not aspect spec case
5722
5723                exit when From_Aspect_Specification (N);
5724                E := Homonym (E);
5725                exit when No (E);
5726
5727                --  If we are within a package specification, the pragma only
5728                --  applies to homonyms in the same scope.
5729
5730                exit when In_Package_Spec
5731                  and then Scope (E) /= Current_Scope;
5732             end loop;
5733          end if;
5734       end Process_Suppress_Unsuppress;
5735
5736       ------------------
5737       -- Set_Exported --
5738       ------------------
5739
5740       procedure Set_Exported (E : Entity_Id; Arg : Node_Id) is
5741       begin
5742          if Is_Imported (E) then
5743             Error_Pragma_Arg
5744               ("cannot export entity& that was previously imported", Arg);
5745
5746          elsif Present (Address_Clause (E)) and then not CodePeer_Mode then
5747             Error_Pragma_Arg
5748               ("cannot export entity& that has an address clause", Arg);
5749          end if;
5750
5751          Set_Is_Exported (E);
5752
5753          --  Generate a reference for entity explicitly, because the
5754          --  identifier may be overloaded and name resolution will not
5755          --  generate one.
5756
5757          Generate_Reference (E, Arg);
5758
5759          --  Deal with exporting non-library level entity
5760
5761          if not Is_Library_Level_Entity (E) then
5762
5763             --  Not allowed at all for subprograms
5764
5765             if Is_Subprogram (E) then
5766                Error_Pragma_Arg ("local subprogram& cannot be exported", Arg);
5767
5768             --  Otherwise set public and statically allocated
5769
5770             else
5771                Set_Is_Public (E);
5772                Set_Is_Statically_Allocated (E);
5773
5774                --  Warn if the corresponding W flag is set and the pragma comes
5775                --  from source. The latter may not be true e.g. on VMS where we
5776                --  expand export pragmas for exception codes associated with
5777                --  imported or exported exceptions. We do not want to generate
5778                --  a warning for something that the user did not write.
5779
5780                if Warn_On_Export_Import
5781                  and then Comes_From_Source (Arg)
5782                then
5783                   Error_Msg_NE
5784                     ("?& has been made static as a result of Export", Arg, E);
5785                   Error_Msg_N
5786                     ("\this usage is non-standard and non-portable", Arg);
5787                end if;
5788             end if;
5789          end if;
5790
5791          if Warn_On_Export_Import and then Is_Type (E) then
5792             Error_Msg_NE ("exporting a type has no effect?", Arg, E);
5793          end if;
5794
5795          if Warn_On_Export_Import and Inside_A_Generic then
5796             Error_Msg_NE
5797               ("all instances of& will have the same external name?", Arg, E);
5798          end if;
5799       end Set_Exported;
5800
5801       ----------------------------------------------
5802       -- Set_Extended_Import_Export_External_Name --
5803       ----------------------------------------------
5804
5805       procedure Set_Extended_Import_Export_External_Name
5806         (Internal_Ent : Entity_Id;
5807          Arg_External : Node_Id)
5808       is
5809          Old_Name : constant Node_Id := Interface_Name (Internal_Ent);
5810          New_Name : Node_Id;
5811
5812       begin
5813          if No (Arg_External) then
5814             return;
5815          end if;
5816
5817          Check_Arg_Is_External_Name (Arg_External);
5818
5819          if Nkind (Arg_External) = N_String_Literal then
5820             if String_Length (Strval (Arg_External)) = 0 then
5821                return;
5822             else
5823                New_Name := Adjust_External_Name_Case (Arg_External);
5824             end if;
5825
5826          elsif Nkind (Arg_External) = N_Identifier then
5827             New_Name := Get_Default_External_Name (Arg_External);
5828
5829          --  Check_Arg_Is_External_Name should let through only identifiers and
5830          --  string literals or static string expressions (which are folded to
5831          --  string literals).
5832
5833          else
5834             raise Program_Error;
5835          end if;
5836
5837          --  If we already have an external name set (by a prior normal Import
5838          --  or Export pragma), then the external names must match
5839
5840          if Present (Interface_Name (Internal_Ent)) then
5841             Check_Matching_Internal_Names : declare
5842                S1 : constant String_Id := Strval (Old_Name);
5843                S2 : constant String_Id := Strval (New_Name);
5844
5845                procedure Mismatch;
5846                --  Called if names do not match
5847
5848                --------------
5849                -- Mismatch --
5850                --------------
5851
5852                procedure Mismatch is
5853                begin
5854                   Error_Msg_Sloc := Sloc (Old_Name);
5855                   Error_Pragma_Arg
5856                     ("external name does not match that given #",
5857                      Arg_External);
5858                end Mismatch;
5859
5860             --  Start of processing for Check_Matching_Internal_Names
5861
5862             begin
5863                if String_Length (S1) /= String_Length (S2) then
5864                   Mismatch;
5865
5866                else
5867                   for J in 1 .. String_Length (S1) loop
5868                      if Get_String_Char (S1, J) /= Get_String_Char (S2, J) then
5869                         Mismatch;
5870                      end if;
5871                   end loop;
5872                end if;
5873             end Check_Matching_Internal_Names;
5874
5875          --  Otherwise set the given name
5876
5877          else
5878             Set_Encoded_Interface_Name (Internal_Ent, New_Name);
5879             Check_Duplicated_Export_Name (New_Name);
5880          end if;
5881       end Set_Extended_Import_Export_External_Name;
5882
5883       ------------------
5884       -- Set_Imported --
5885       ------------------
5886
5887       procedure Set_Imported (E : Entity_Id) is
5888       begin
5889          --  Error message if already imported or exported
5890
5891          if Is_Exported (E) or else Is_Imported (E) then
5892
5893             --  Error if being set Exported twice
5894
5895             if Is_Exported (E) then
5896                Error_Msg_NE ("entity& was previously exported", N, E);
5897
5898             --  OK if Import/Interface case
5899
5900             elsif Import_Interface_Present (N) then
5901                goto OK;
5902
5903             --  Error if being set Imported twice
5904
5905             else
5906                Error_Msg_NE ("entity& was previously imported", N, E);
5907             end if;
5908
5909             Error_Msg_Name_1 := Pname;
5910             Error_Msg_N
5911               ("\(pragma% applies to all previous entities)", N);
5912
5913             Error_Msg_Sloc  := Sloc (E);
5914             Error_Msg_NE ("\import not allowed for& declared#", N, E);
5915
5916          --  Here if not previously imported or exported, OK to import
5917
5918          else
5919             Set_Is_Imported (E);
5920
5921             --  If the entity is an object that is not at the library level,
5922             --  then it is statically allocated. We do not worry about objects
5923             --  with address clauses in this context since they are not really
5924             --  imported in the linker sense.
5925
5926             if Is_Object (E)
5927               and then not Is_Library_Level_Entity (E)
5928               and then No (Address_Clause (E))
5929             then
5930                Set_Is_Statically_Allocated (E);
5931             end if;
5932          end if;
5933
5934          <<OK>> null;
5935       end Set_Imported;
5936
5937       -------------------------
5938       -- Set_Mechanism_Value --
5939       -------------------------
5940
5941       --  Note: the mechanism name has not been analyzed (and cannot indeed be
5942       --  analyzed, since it is semantic nonsense), so we get it in the exact
5943       --  form created by the parser.
5944
5945       procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id) is
5946          Class        : Node_Id;
5947          Param        : Node_Id;
5948          Mech_Name_Id : Name_Id;
5949
5950          procedure Bad_Class;
5951          --  Signal bad descriptor class name
5952
5953          procedure Bad_Mechanism;
5954          --  Signal bad mechanism name
5955
5956          ---------------
5957          -- Bad_Class --
5958          ---------------
5959
5960          procedure Bad_Class is
5961          begin
5962             Error_Pragma_Arg ("unrecognized descriptor class name", Class);
5963          end Bad_Class;
5964
5965          -------------------------
5966          -- Bad_Mechanism_Value --
5967          -------------------------
5968
5969          procedure Bad_Mechanism is
5970          begin
5971             Error_Pragma_Arg ("unrecognized mechanism name", Mech_Name);
5972          end Bad_Mechanism;
5973
5974       --  Start of processing for Set_Mechanism_Value
5975
5976       begin
5977          if Mechanism (Ent) /= Default_Mechanism then
5978             Error_Msg_NE
5979               ("mechanism for & has already been set", Mech_Name, Ent);
5980          end if;
5981
5982          --  MECHANISM_NAME ::= value | reference | descriptor |
5983          --                     short_descriptor
5984
5985          if Nkind (Mech_Name) = N_Identifier then
5986             if Chars (Mech_Name) = Name_Value then
5987                Set_Mechanism (Ent, By_Copy);
5988                return;
5989
5990             elsif Chars (Mech_Name) = Name_Reference then
5991                Set_Mechanism (Ent, By_Reference);
5992                return;
5993
5994             elsif Chars (Mech_Name) = Name_Descriptor then
5995                Check_VMS (Mech_Name);
5996
5997                --  Descriptor => Short_Descriptor if pragma was given
5998
5999                if Short_Descriptors then
6000                   Set_Mechanism (Ent, By_Short_Descriptor);
6001                else
6002                   Set_Mechanism (Ent, By_Descriptor);
6003                end if;
6004
6005                return;
6006
6007             elsif Chars (Mech_Name) = Name_Short_Descriptor then
6008                Check_VMS (Mech_Name);
6009                Set_Mechanism (Ent, By_Short_Descriptor);
6010                return;
6011
6012             elsif Chars (Mech_Name) = Name_Copy then
6013                Error_Pragma_Arg
6014                  ("bad mechanism name, Value assumed", Mech_Name);
6015
6016             else
6017                Bad_Mechanism;
6018             end if;
6019
6020          --  MECHANISM_NAME ::= descriptor (CLASS_NAME) |
6021          --                     short_descriptor (CLASS_NAME)
6022          --  CLASS_NAME     ::= ubs | ubsb | uba | s | sb | a | nca
6023
6024          --  Note: this form is parsed as an indexed component
6025
6026          elsif Nkind (Mech_Name) = N_Indexed_Component then
6027             Class := First (Expressions (Mech_Name));
6028
6029             if Nkind (Prefix (Mech_Name)) /= N_Identifier
6030              or else not (Chars (Prefix (Mech_Name)) = Name_Descriptor or else
6031                           Chars (Prefix (Mech_Name)) = Name_Short_Descriptor)
6032              or else Present (Next (Class))
6033             then
6034                Bad_Mechanism;
6035             else
6036                Mech_Name_Id := Chars (Prefix (Mech_Name));
6037
6038                --  Change Descriptor => Short_Descriptor if pragma was given
6039
6040                if Mech_Name_Id = Name_Descriptor
6041                  and then Short_Descriptors
6042                then
6043                   Mech_Name_Id := Name_Short_Descriptor;
6044                end if;
6045             end if;
6046
6047          --  MECHANISM_NAME ::= descriptor (Class => CLASS_NAME) |
6048          --                     short_descriptor (Class => CLASS_NAME)
6049          --  CLASS_NAME     ::= ubs | ubsb | uba | s | sb | a | nca
6050
6051          --  Note: this form is parsed as a function call
6052
6053          elsif Nkind (Mech_Name) = N_Function_Call then
6054             Param := First (Parameter_Associations (Mech_Name));
6055
6056             if Nkind (Name (Mech_Name)) /= N_Identifier
6057               or else not (Chars (Name (Mech_Name)) = Name_Descriptor or else
6058                            Chars (Name (Mech_Name)) = Name_Short_Descriptor)
6059               or else Present (Next (Param))
6060               or else No (Selector_Name (Param))
6061               or else Chars (Selector_Name (Param)) /= Name_Class
6062             then
6063                Bad_Mechanism;
6064             else
6065                Class := Explicit_Actual_Parameter (Param);
6066                Mech_Name_Id := Chars (Name (Mech_Name));
6067             end if;
6068
6069          else
6070             Bad_Mechanism;
6071          end if;
6072
6073          --  Fall through here with Class set to descriptor class name
6074
6075          Check_VMS (Mech_Name);
6076
6077          if Nkind (Class) /= N_Identifier then
6078             Bad_Class;
6079
6080          elsif Mech_Name_Id = Name_Descriptor
6081            and then Chars (Class) = Name_UBS
6082          then
6083             Set_Mechanism (Ent, By_Descriptor_UBS);
6084
6085          elsif Mech_Name_Id = Name_Descriptor
6086            and then Chars (Class) = Name_UBSB
6087          then
6088             Set_Mechanism (Ent, By_Descriptor_UBSB);
6089
6090          elsif Mech_Name_Id = Name_Descriptor
6091            and then Chars (Class) = Name_UBA
6092          then
6093             Set_Mechanism (Ent, By_Descriptor_UBA);
6094
6095          elsif Mech_Name_Id = Name_Descriptor
6096            and then Chars (Class) = Name_S
6097          then
6098             Set_Mechanism (Ent, By_Descriptor_S);
6099
6100          elsif Mech_Name_Id = Name_Descriptor
6101            and then Chars (Class) = Name_SB
6102          then
6103             Set_Mechanism (Ent, By_Descriptor_SB);
6104
6105          elsif Mech_Name_Id = Name_Descriptor
6106            and then Chars (Class) = Name_A
6107          then
6108             Set_Mechanism (Ent, By_Descriptor_A);
6109
6110          elsif Mech_Name_Id = Name_Descriptor
6111            and then Chars (Class) = Name_NCA
6112          then
6113             Set_Mechanism (Ent, By_Descriptor_NCA);
6114
6115          elsif Mech_Name_Id = Name_Short_Descriptor
6116            and then Chars (Class) = Name_UBS
6117          then
6118             Set_Mechanism (Ent, By_Short_Descriptor_UBS);
6119
6120          elsif Mech_Name_Id = Name_Short_Descriptor
6121            and then Chars (Class) = Name_UBSB
6122          then
6123             Set_Mechanism (Ent, By_Short_Descriptor_UBSB);
6124
6125          elsif Mech_Name_Id = Name_Short_Descriptor
6126            and then Chars (Class) = Name_UBA
6127          then
6128             Set_Mechanism (Ent, By_Short_Descriptor_UBA);
6129
6130          elsif Mech_Name_Id = Name_Short_Descriptor
6131            and then Chars (Class) = Name_S
6132          then
6133             Set_Mechanism (Ent, By_Short_Descriptor_S);
6134
6135          elsif Mech_Name_Id = Name_Short_Descriptor
6136            and then Chars (Class) = Name_SB
6137          then
6138             Set_Mechanism (Ent, By_Short_Descriptor_SB);
6139
6140          elsif Mech_Name_Id = Name_Short_Descriptor
6141            and then Chars (Class) = Name_A
6142          then
6143             Set_Mechanism (Ent, By_Short_Descriptor_A);
6144
6145          elsif Mech_Name_Id = Name_Short_Descriptor
6146            and then Chars (Class) = Name_NCA
6147          then
6148             Set_Mechanism (Ent, By_Short_Descriptor_NCA);
6149
6150          else
6151             Bad_Class;
6152          end if;
6153       end Set_Mechanism_Value;
6154
6155       ---------------------------
6156       -- Set_Ravenscar_Profile --
6157       ---------------------------
6158
6159       --  The tasks to be done here are
6160
6161       --    Set required policies
6162
6163       --      pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
6164       --      pragma Locking_Policy (Ceiling_Locking)
6165
6166       --    Set Detect_Blocking mode
6167
6168       --    Set required restrictions (see System.Rident for detailed list)
6169
6170       --    Set the No_Dependence rules
6171       --      No_Dependence => Ada.Asynchronous_Task_Control
6172       --      No_Dependence => Ada.Calendar
6173       --      No_Dependence => Ada.Execution_Time.Group_Budget
6174       --      No_Dependence => Ada.Execution_Time.Timers
6175       --      No_Dependence => Ada.Task_Attributes
6176       --      No_Dependence => System.Multiprocessors.Dispatching_Domains
6177
6178       procedure Set_Ravenscar_Profile (N : Node_Id) is
6179          Prefix_Entity   : Entity_Id;
6180          Selector_Entity : Entity_Id;
6181          Prefix_Node     : Node_Id;
6182          Node            : Node_Id;
6183
6184       begin
6185          --  pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
6186
6187          if Task_Dispatching_Policy /= ' '
6188            and then Task_Dispatching_Policy /= 'F'
6189          then
6190             Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
6191             Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
6192
6193          --  Set the FIFO_Within_Priorities policy, but always preserve
6194          --  System_Location since we like the error message with the run time
6195          --  name.
6196
6197          else
6198             Task_Dispatching_Policy := 'F';
6199
6200             if Task_Dispatching_Policy_Sloc /= System_Location then
6201                Task_Dispatching_Policy_Sloc := Loc;
6202             end if;
6203          end if;
6204
6205          --  pragma Locking_Policy (Ceiling_Locking)
6206
6207          if Locking_Policy /= ' '
6208            and then Locking_Policy /= 'C'
6209          then
6210             Error_Msg_Sloc := Locking_Policy_Sloc;
6211             Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
6212
6213          --  Set the Ceiling_Locking policy, but preserve System_Location since
6214          --  we like the error message with the run time name.
6215
6216          else
6217             Locking_Policy := 'C';
6218
6219             if Locking_Policy_Sloc /= System_Location then
6220                Locking_Policy_Sloc := Loc;
6221             end if;
6222          end if;
6223
6224          --  pragma Detect_Blocking
6225
6226          Detect_Blocking := True;
6227
6228          --  Set the corresponding restrictions
6229
6230          Set_Profile_Restrictions
6231            (Ravenscar, N, Warn => Treat_Restrictions_As_Warnings);
6232
6233          --  Set the No_Dependence restrictions
6234
6235          --  The following No_Dependence restrictions:
6236          --    No_Dependence => Ada.Asynchronous_Task_Control
6237          --    No_Dependence => Ada.Calendar
6238          --    No_Dependence => Ada.Task_Attributes
6239          --  are already set by previous call to Set_Profile_Restrictions.
6240
6241          --  Set the following restrictions which were added to Ada 2005:
6242          --    No_Dependence => Ada.Execution_Time.Group_Budget
6243          --    No_Dependence => Ada.Execution_Time.Timers
6244
6245          if Ada_Version >= Ada_2005 then
6246             Name_Buffer (1 .. 3) := "ada";
6247             Name_Len := 3;
6248
6249             Prefix_Entity := Make_Identifier (Loc, Name_Find);
6250
6251             Name_Buffer (1 .. 14) := "execution_time";
6252             Name_Len := 14;
6253
6254             Selector_Entity := Make_Identifier (Loc, Name_Find);
6255
6256             Prefix_Node :=
6257               Make_Selected_Component
6258                 (Sloc          => Loc,
6259                  Prefix        => Prefix_Entity,
6260                  Selector_Name => Selector_Entity);
6261
6262             Name_Buffer (1 .. 13) := "group_budgets";
6263             Name_Len := 13;
6264
6265             Selector_Entity := Make_Identifier (Loc, Name_Find);
6266
6267             Node :=
6268               Make_Selected_Component
6269                 (Sloc          => Loc,
6270                  Prefix        => Prefix_Node,
6271                  Selector_Name => Selector_Entity);
6272
6273             Set_Restriction_No_Dependence
6274               (Unit    => Node,
6275                Warn    => Treat_Restrictions_As_Warnings,
6276                Profile => Ravenscar);
6277
6278             Name_Buffer (1 .. 6) := "timers";
6279             Name_Len := 6;
6280
6281             Selector_Entity := Make_Identifier (Loc, Name_Find);
6282
6283             Node :=
6284               Make_Selected_Component
6285                 (Sloc          => Loc,
6286                  Prefix        => Prefix_Node,
6287                  Selector_Name => Selector_Entity);
6288
6289             Set_Restriction_No_Dependence
6290               (Unit    => Node,
6291                Warn    => Treat_Restrictions_As_Warnings,
6292                Profile => Ravenscar);
6293          end if;
6294
6295          --  Set the following restrictions which was added to Ada 2012 (see
6296          --  AI-0171):
6297          --    No_Dependence => System.Multiprocessors.Dispatching_Domains
6298
6299          if Ada_Version >= Ada_2012 then
6300             Name_Buffer (1 .. 6) := "system";
6301             Name_Len := 6;
6302
6303             Prefix_Entity := Make_Identifier (Loc, Name_Find);
6304
6305             Name_Buffer (1 .. 15) := "multiprocessors";
6306             Name_Len := 15;
6307
6308             Selector_Entity := Make_Identifier (Loc, Name_Find);
6309
6310             Prefix_Node :=
6311               Make_Selected_Component
6312                 (Sloc          => Loc,
6313                  Prefix        => Prefix_Entity,
6314                  Selector_Name => Selector_Entity);
6315
6316             Name_Buffer (1 .. 19) := "dispatching_domains";
6317             Name_Len := 19;
6318
6319             Selector_Entity := Make_Identifier (Loc, Name_Find);
6320
6321             Node :=
6322               Make_Selected_Component
6323                 (Sloc          => Loc,
6324                  Prefix        => Prefix_Node,
6325                  Selector_Name => Selector_Entity);
6326
6327             Set_Restriction_No_Dependence
6328               (Unit    => Node,
6329                Warn    => Treat_Restrictions_As_Warnings,
6330                Profile => Ravenscar);
6331          end if;
6332       end Set_Ravenscar_Profile;
6333
6334    --  Start of processing for Analyze_Pragma
6335
6336    begin
6337       --  The following code is a defense against recursion. Not clear that
6338       --  this can happen legitimately, but perhaps some error situations
6339       --  can cause it, and we did see this recursion during testing.
6340
6341       if Analyzed (N) then
6342          return;
6343       else
6344          Set_Analyzed (N, True);
6345       end if;
6346
6347       --  Deal with unrecognized pragma
6348
6349       Pname := Pragma_Name (N);
6350
6351       if not Is_Pragma_Name (Pname) then
6352          if Warn_On_Unrecognized_Pragma then
6353             Error_Msg_Name_1 := Pname;
6354             Error_Msg_N ("?unrecognized pragma%!", Pragma_Identifier (N));
6355
6356             for PN in First_Pragma_Name .. Last_Pragma_Name loop
6357                if Is_Bad_Spelling_Of (Pname, PN) then
6358                   Error_Msg_Name_1 := PN;
6359                   Error_Msg_N -- CODEFIX
6360                     ("\?possible misspelling of %!", Pragma_Identifier (N));
6361                   exit;
6362                end if;
6363             end loop;
6364          end if;
6365
6366          return;
6367       end if;
6368
6369       --  Here to start processing for recognized pragma
6370
6371       Prag_Id := Get_Pragma_Id (Pname);
6372
6373       if Present (Corresponding_Aspect (N)) then
6374          Pname := Chars (Identifier (Corresponding_Aspect (N)));
6375       end if;
6376
6377       --  Preset arguments
6378
6379       Arg_Count := 0;
6380       Arg1      := Empty;
6381       Arg2      := Empty;
6382       Arg3      := Empty;
6383       Arg4      := Empty;
6384
6385       if Present (Pragma_Argument_Associations (N)) then
6386          Arg_Count := List_Length (Pragma_Argument_Associations (N));
6387          Arg1 := First (Pragma_Argument_Associations (N));
6388
6389          if Present (Arg1) then
6390             Arg2 := Next (Arg1);
6391
6392             if Present (Arg2) then
6393                Arg3 := Next (Arg2);
6394
6395                if Present (Arg3) then
6396                   Arg4 := Next (Arg3);
6397                end if;
6398             end if;
6399          end if;
6400       end if;
6401
6402       --  An enumeration type defines the pragmas that are supported by the
6403       --  implementation. Get_Pragma_Id (in package Prag) transforms a name
6404       --  into the corresponding enumeration value for the following case.
6405
6406       case Prag_Id is
6407
6408          -----------------
6409          -- Abort_Defer --
6410          -----------------
6411
6412          --  pragma Abort_Defer;
6413
6414          when Pragma_Abort_Defer =>
6415             GNAT_Pragma;
6416             Check_Arg_Count (0);
6417
6418             --  The only required semantic processing is to check the
6419             --  placement. This pragma must appear at the start of the
6420             --  statement sequence of a handled sequence of statements.
6421
6422             if Nkind (Parent (N)) /= N_Handled_Sequence_Of_Statements
6423               or else N /= First (Statements (Parent (N)))
6424             then
6425                Pragma_Misplaced;
6426             end if;
6427
6428          ------------
6429          -- Ada_83 --
6430          ------------
6431
6432          --  pragma Ada_83;
6433
6434          --  Note: this pragma also has some specific processing in Par.Prag
6435          --  because we want to set the Ada version mode during parsing.
6436
6437          when Pragma_Ada_83 =>
6438             GNAT_Pragma;
6439             Check_Arg_Count (0);
6440
6441             --  We really should check unconditionally for proper configuration
6442             --  pragma placement, since we really don't want mixed Ada modes
6443             --  within a single unit, and the GNAT reference manual has always
6444             --  said this was a configuration pragma, but we did not check and
6445             --  are hesitant to add the check now.
6446
6447             --  However, we really cannot tolerate mixing Ada 2005 or Ada 2012
6448             --  with Ada 83 or Ada 95, so we must check if we are in Ada 2005
6449             --  or Ada 2012 mode.
6450
6451             if Ada_Version >= Ada_2005 then
6452                Check_Valid_Configuration_Pragma;
6453             end if;
6454
6455             --  Now set Ada 83 mode
6456
6457             Ada_Version := Ada_83;
6458             Ada_Version_Explicit := Ada_Version;
6459
6460          ------------
6461          -- Ada_95 --
6462          ------------
6463
6464          --  pragma Ada_95;
6465
6466          --  Note: this pragma also has some specific processing in Par.Prag
6467          --  because we want to set the Ada 83 version mode during parsing.
6468
6469          when Pragma_Ada_95 =>
6470             GNAT_Pragma;
6471             Check_Arg_Count (0);
6472
6473             --  We really should check unconditionally for proper configuration
6474             --  pragma placement, since we really don't want mixed Ada modes
6475             --  within a single unit, and the GNAT reference manual has always
6476             --  said this was a configuration pragma, but we did not check and
6477             --  are hesitant to add the check now.
6478
6479             --  However, we really cannot tolerate mixing Ada 2005 with Ada 83
6480             --  or Ada 95, so we must check if we are in Ada 2005 mode.
6481
6482             if Ada_Version >= Ada_2005 then
6483                Check_Valid_Configuration_Pragma;
6484             end if;
6485
6486             --  Now set Ada 95 mode
6487
6488             Ada_Version := Ada_95;
6489             Ada_Version_Explicit := Ada_Version;
6490
6491          ---------------------
6492          -- Ada_05/Ada_2005 --
6493          ---------------------
6494
6495          --  pragma Ada_05;
6496          --  pragma Ada_05 (LOCAL_NAME);
6497
6498          --  pragma Ada_2005;
6499          --  pragma Ada_2005 (LOCAL_NAME):
6500
6501          --  Note: these pragmas also have some specific processing in Par.Prag
6502          --  because we want to set the Ada 2005 version mode during parsing.
6503
6504          when Pragma_Ada_05 | Pragma_Ada_2005 => declare
6505             E_Id : Node_Id;
6506
6507          begin
6508             GNAT_Pragma;
6509
6510             if Arg_Count = 1 then
6511                Check_Arg_Is_Local_Name (Arg1);
6512                E_Id := Get_Pragma_Arg (Arg1);
6513
6514                if Etype (E_Id) = Any_Type then
6515                   return;
6516                end if;
6517
6518                Set_Is_Ada_2005_Only (Entity (E_Id));
6519
6520             else
6521                Check_Arg_Count (0);
6522
6523                --  For Ada_2005 we unconditionally enforce the documented
6524                --  configuration pragma placement, since we do not want to
6525                --  tolerate mixed modes in a unit involving Ada 2005. That
6526                --  would cause real difficulties for those cases where there
6527                --  are incompatibilities between Ada 95 and Ada 2005.
6528
6529                Check_Valid_Configuration_Pragma;
6530
6531                --  Now set appropriate Ada mode
6532
6533                Ada_Version          := Ada_2005;
6534                Ada_Version_Explicit := Ada_2005;
6535             end if;
6536          end;
6537
6538          ---------------------
6539          -- Ada_12/Ada_2012 --
6540          ---------------------
6541
6542          --  pragma Ada_12;
6543          --  pragma Ada_12 (LOCAL_NAME);
6544
6545          --  pragma Ada_2012;
6546          --  pragma Ada_2012 (LOCAL_NAME):
6547
6548          --  Note: these pragmas also have some specific processing in Par.Prag
6549          --  because we want to set the Ada 2012 version mode during parsing.
6550
6551          when Pragma_Ada_12 | Pragma_Ada_2012 => declare
6552             E_Id : Node_Id;
6553
6554          begin
6555             GNAT_Pragma;
6556
6557             if Arg_Count = 1 then
6558                Check_Arg_Is_Local_Name (Arg1);
6559                E_Id := Get_Pragma_Arg (Arg1);
6560
6561                if Etype (E_Id) = Any_Type then
6562                   return;
6563                end if;
6564
6565                Set_Is_Ada_2012_Only (Entity (E_Id));
6566
6567             else
6568                Check_Arg_Count (0);
6569
6570                --  For Ada_2012 we unconditionally enforce the documented
6571                --  configuration pragma placement, since we do not want to
6572                --  tolerate mixed modes in a unit involving Ada 2012. That
6573                --  would cause real difficulties for those cases where there
6574                --  are incompatibilities between Ada 95 and Ada 2012. We could
6575                --  allow mixing of Ada 2005 and Ada 2012 but it's not worth it.
6576
6577                Check_Valid_Configuration_Pragma;
6578
6579                --  Now set appropriate Ada mode
6580
6581                Ada_Version          := Ada_2012;
6582                Ada_Version_Explicit := Ada_2012;
6583             end if;
6584          end;
6585
6586          ----------------------
6587          -- All_Calls_Remote --
6588          ----------------------
6589
6590          --  pragma All_Calls_Remote [(library_package_NAME)];
6591
6592          when Pragma_All_Calls_Remote => All_Calls_Remote : declare
6593             Lib_Entity : Entity_Id;
6594
6595          begin
6596             Check_Ada_83_Warning;
6597             Check_Valid_Library_Unit_Pragma;
6598
6599             if Nkind (N) = N_Null_Statement then
6600                return;
6601             end if;
6602
6603             Lib_Entity := Find_Lib_Unit_Name;
6604
6605             --  This pragma should only apply to a RCI unit (RM E.2.3(23))
6606
6607             if Present (Lib_Entity)
6608               and then not Debug_Flag_U
6609             then
6610                if not Is_Remote_Call_Interface (Lib_Entity) then
6611                   Error_Pragma ("pragma% only apply to rci unit");
6612
6613                --  Set flag for entity of the library unit
6614
6615                else
6616                   Set_Has_All_Calls_Remote (Lib_Entity);
6617                end if;
6618
6619             end if;
6620          end All_Calls_Remote;
6621
6622          --------------
6623          -- Annotate --
6624          --------------
6625
6626          --  pragma Annotate (IDENTIFIER [, IDENTIFIER {, ARG}]);
6627          --  ARG ::= NAME | EXPRESSION
6628
6629          --  The first two arguments are by convention intended to refer to an
6630          --  external tool and a tool-specific function. These arguments are
6631          --  not analyzed.
6632
6633          when Pragma_Annotate => Annotate : declare
6634             Arg : Node_Id;
6635             Exp : Node_Id;
6636
6637          begin
6638             GNAT_Pragma;
6639             Check_At_Least_N_Arguments (1);
6640             Check_Arg_Is_Identifier (Arg1);
6641             Check_No_Identifiers;
6642             Store_Note (N);
6643
6644             --  Second parameter is optional, it is never analyzed
6645
6646             if No (Arg2) then
6647                null;
6648
6649             --  Here if we have a second parameter
6650
6651             else
6652                --  Second parameter must be identifier
6653
6654                Check_Arg_Is_Identifier (Arg2);
6655
6656                --  Process remaining parameters if any
6657
6658                Arg := Next (Arg2);
6659                while Present (Arg) loop
6660                   Exp := Get_Pragma_Arg (Arg);
6661                   Analyze (Exp);
6662
6663                   if Is_Entity_Name (Exp) then
6664                      null;
6665
6666                   --  For string literals, we assume Standard_String as the
6667                   --  type, unless the string contains wide or wide_wide
6668                   --  characters.
6669
6670                   elsif Nkind (Exp) = N_String_Literal then
6671                      if Has_Wide_Wide_Character (Exp) then
6672                         Resolve (Exp, Standard_Wide_Wide_String);
6673                      elsif Has_Wide_Character (Exp) then
6674                         Resolve (Exp, Standard_Wide_String);
6675                      else
6676                         Resolve (Exp, Standard_String);
6677                      end if;
6678
6679                   elsif Is_Overloaded (Exp) then
6680                         Error_Pragma_Arg
6681                           ("ambiguous argument for pragma%", Exp);
6682
6683                   else
6684                      Resolve (Exp);
6685                   end if;
6686
6687                   Next (Arg);
6688                end loop;
6689             end if;
6690          end Annotate;
6691
6692          ------------
6693          -- Assert --
6694          ------------
6695
6696          --  pragma Assert ([Check =>] Boolean_EXPRESSION
6697          --                 [, [Message =>] Static_String_EXPRESSION]);
6698
6699          when Pragma_Assert => Assert : declare
6700             Expr : Node_Id;
6701             Newa : List_Id;
6702
6703          begin
6704             Ada_2005_Pragma;
6705             Check_At_Least_N_Arguments (1);
6706             Check_At_Most_N_Arguments (2);
6707             Check_Arg_Order ((Name_Check, Name_Message));
6708             Check_Optional_Identifier (Arg1, Name_Check);
6709
6710             --  We treat pragma Assert as equivalent to:
6711
6712             --    pragma Check (Assertion, condition [, msg]);
6713
6714             --  So rewrite pragma in this manner, and analyze the result
6715
6716             Expr := Get_Pragma_Arg (Arg1);
6717             Newa := New_List (
6718               Make_Pragma_Argument_Association (Loc,
6719                 Expression => Make_Identifier (Loc, Name_Assertion)),
6720
6721               Make_Pragma_Argument_Association (Sloc (Expr),
6722                 Expression => Expr));
6723
6724             if Arg_Count > 1 then
6725                Check_Optional_Identifier (Arg2, Name_Message);
6726                Analyze_And_Resolve (Get_Pragma_Arg (Arg2), Standard_String);
6727                Append_To (Newa, Relocate_Node (Arg2));
6728             end if;
6729
6730             Rewrite (N,
6731               Make_Pragma (Loc,
6732                 Chars                        => Name_Check,
6733                 Pragma_Argument_Associations => Newa));
6734             Analyze (N);
6735          end Assert;
6736
6737          ----------------------
6738          -- Assertion_Policy --
6739          ----------------------
6740
6741          --  pragma Assertion_Policy (Check | Disable |Ignore)
6742
6743          when Pragma_Assertion_Policy => Assertion_Policy : declare
6744             Policy : Node_Id;
6745
6746          begin
6747             Ada_2005_Pragma;
6748             Check_Valid_Configuration_Pragma;
6749             Check_Arg_Count (1);
6750             Check_No_Identifiers;
6751             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Disable, Name_Ignore);
6752
6753             --  We treat pragma Assertion_Policy as equivalent to:
6754
6755             --    pragma Check_Policy (Assertion, policy)
6756
6757             --  So rewrite the pragma in that manner and link on to the chain
6758             --  of Check_Policy pragmas, marking the pragma as analyzed.
6759
6760             Policy := Get_Pragma_Arg (Arg1);
6761
6762             Rewrite (N,
6763               Make_Pragma (Loc,
6764                 Chars => Name_Check_Policy,
6765
6766                 Pragma_Argument_Associations => New_List (
6767                   Make_Pragma_Argument_Association (Loc,
6768                     Expression => Make_Identifier (Loc, Name_Assertion)),
6769
6770                   Make_Pragma_Argument_Association (Loc,
6771                     Expression =>
6772                       Make_Identifier (Sloc (Policy), Chars (Policy))))));
6773
6774             Set_Analyzed (N);
6775             Set_Next_Pragma (N, Opt.Check_Policy_List);
6776             Opt.Check_Policy_List := N;
6777          end Assertion_Policy;
6778
6779          ------------------------------
6780          -- Assume_No_Invalid_Values --
6781          ------------------------------
6782
6783          --  pragma Assume_No_Invalid_Values (On | Off);
6784
6785          when Pragma_Assume_No_Invalid_Values =>
6786             GNAT_Pragma;
6787             Check_Valid_Configuration_Pragma;
6788             Check_Arg_Count (1);
6789             Check_No_Identifiers;
6790             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
6791
6792             if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
6793                Assume_No_Invalid_Values := True;
6794             else
6795                Assume_No_Invalid_Values := False;
6796             end if;
6797
6798          ---------------
6799          -- AST_Entry --
6800          ---------------
6801
6802          --  pragma AST_Entry (entry_IDENTIFIER);
6803
6804          when Pragma_AST_Entry => AST_Entry : declare
6805             Ent : Node_Id;
6806
6807          begin
6808             GNAT_Pragma;
6809             Check_VMS (N);
6810             Check_Arg_Count (1);
6811             Check_No_Identifiers;
6812             Check_Arg_Is_Local_Name (Arg1);
6813             Ent := Entity (Get_Pragma_Arg (Arg1));
6814
6815             --  Note: the implementation of the AST_Entry pragma could handle
6816             --  the entry family case fine, but for now we are consistent with
6817             --  the DEC rules, and do not allow the pragma, which of course
6818             --  has the effect of also forbidding the attribute.
6819
6820             if Ekind (Ent) /= E_Entry then
6821                Error_Pragma_Arg
6822                  ("pragma% argument must be simple entry name", Arg1);
6823
6824             elsif Is_AST_Entry (Ent) then
6825                Error_Pragma_Arg
6826                  ("duplicate % pragma for entry", Arg1);
6827
6828             elsif Has_Homonym (Ent) then
6829                Error_Pragma_Arg
6830                  ("pragma% argument cannot specify overloaded entry", Arg1);
6831
6832             else
6833                declare
6834                   FF : constant Entity_Id := First_Formal (Ent);
6835
6836                begin
6837                   if Present (FF) then
6838                      if Present (Next_Formal (FF)) then
6839                         Error_Pragma_Arg
6840                           ("entry for pragma% can have only one argument",
6841                            Arg1);
6842
6843                      elsif Parameter_Mode (FF) /= E_In_Parameter then
6844                         Error_Pragma_Arg
6845                           ("entry parameter for pragma% must have mode IN",
6846                            Arg1);
6847                      end if;
6848                   end if;
6849                end;
6850
6851                Set_Is_AST_Entry (Ent);
6852             end if;
6853          end AST_Entry;
6854
6855          ------------------
6856          -- Asynchronous --
6857          ------------------
6858
6859          --  pragma Asynchronous (LOCAL_NAME);
6860
6861          when Pragma_Asynchronous => Asynchronous : declare
6862             Nm     : Entity_Id;
6863             C_Ent  : Entity_Id;
6864             L      : List_Id;
6865             S      : Node_Id;
6866             N      : Node_Id;
6867             Formal : Entity_Id;
6868
6869             procedure Process_Async_Pragma;
6870             --  Common processing for procedure and access-to-procedure case
6871
6872             --------------------------
6873             -- Process_Async_Pragma --
6874             --------------------------
6875
6876             procedure Process_Async_Pragma is
6877             begin
6878                if No (L) then
6879                   Set_Is_Asynchronous (Nm);
6880                   return;
6881                end if;
6882
6883                --  The formals should be of mode IN (RM E.4.1(6))
6884
6885                S := First (L);
6886                while Present (S) loop
6887                   Formal := Defining_Identifier (S);
6888
6889                   if Nkind (Formal) = N_Defining_Identifier
6890                     and then Ekind (Formal) /= E_In_Parameter
6891                   then
6892                      Error_Pragma_Arg
6893                        ("pragma% procedure can only have IN parameter",
6894                         Arg1);
6895                   end if;
6896
6897                   Next (S);
6898                end loop;
6899
6900                Set_Is_Asynchronous (Nm);
6901             end Process_Async_Pragma;
6902
6903          --  Start of processing for pragma Asynchronous
6904
6905          begin
6906             Check_Ada_83_Warning;
6907             Check_No_Identifiers;
6908             Check_Arg_Count (1);
6909             Check_Arg_Is_Local_Name (Arg1);
6910
6911             if Debug_Flag_U then
6912                return;
6913             end if;
6914
6915             C_Ent := Cunit_Entity (Current_Sem_Unit);
6916             Analyze (Get_Pragma_Arg (Arg1));
6917             Nm := Entity (Get_Pragma_Arg (Arg1));
6918
6919             if not Is_Remote_Call_Interface (C_Ent)
6920               and then not Is_Remote_Types (C_Ent)
6921             then
6922                --  This pragma should only appear in an RCI or Remote Types
6923                --  unit (RM E.4.1(4)).
6924
6925                Error_Pragma
6926                  ("pragma% not in Remote_Call_Interface or " &
6927                   "Remote_Types unit");
6928             end if;
6929
6930             if Ekind (Nm) = E_Procedure
6931               and then Nkind (Parent (Nm)) = N_Procedure_Specification
6932             then
6933                if not Is_Remote_Call_Interface (Nm) then
6934                   Error_Pragma_Arg
6935                     ("pragma% cannot be applied on non-remote procedure",
6936                      Arg1);
6937                end if;
6938
6939                L := Parameter_Specifications (Parent (Nm));
6940                Process_Async_Pragma;
6941                return;
6942
6943             elsif Ekind (Nm) = E_Function then
6944                Error_Pragma_Arg
6945                  ("pragma% cannot be applied to function", Arg1);
6946
6947             elsif Is_Remote_Access_To_Subprogram_Type (Nm) then
6948                   if Is_Record_Type (Nm) then
6949
6950                   --  A record type that is the Equivalent_Type for a remote
6951                   --  access-to-subprogram type.
6952
6953                      N := Declaration_Node (Corresponding_Remote_Type (Nm));
6954
6955                   else
6956                      --  A non-expanded RAS type (distribution is not enabled)
6957
6958                      N := Declaration_Node (Nm);
6959                   end if;
6960
6961                if Nkind (N) = N_Full_Type_Declaration
6962                  and then Nkind (Type_Definition (N)) =
6963                                      N_Access_Procedure_Definition
6964                then
6965                   L := Parameter_Specifications (Type_Definition (N));
6966                   Process_Async_Pragma;
6967
6968                   if Is_Asynchronous (Nm)
6969                     and then Expander_Active
6970                     and then Get_PCS_Name /= Name_No_DSA
6971                   then
6972                      RACW_Type_Is_Asynchronous (Underlying_RACW_Type (Nm));
6973                   end if;
6974
6975                else
6976                   Error_Pragma_Arg
6977                     ("pragma% cannot reference access-to-function type",
6978                     Arg1);
6979                end if;
6980
6981             --  Only other possibility is Access-to-class-wide type
6982
6983             elsif Is_Access_Type (Nm)
6984               and then Is_Class_Wide_Type (Designated_Type (Nm))
6985             then
6986                Check_First_Subtype (Arg1);
6987                Set_Is_Asynchronous (Nm);
6988                if Expander_Active then
6989                   RACW_Type_Is_Asynchronous (Nm);
6990                end if;
6991
6992             else
6993                Error_Pragma_Arg ("inappropriate argument for pragma%", Arg1);
6994             end if;
6995          end Asynchronous;
6996
6997          ------------
6998          -- Atomic --
6999          ------------
7000
7001          --  pragma Atomic (LOCAL_NAME);
7002
7003          when Pragma_Atomic =>
7004             Process_Atomic_Shared_Volatile;
7005
7006          -----------------------
7007          -- Atomic_Components --
7008          -----------------------
7009
7010          --  pragma Atomic_Components (array_LOCAL_NAME);
7011
7012          --  This processing is shared by Volatile_Components
7013
7014          when Pragma_Atomic_Components   |
7015               Pragma_Volatile_Components =>
7016
7017          Atomic_Components : declare
7018             E_Id : Node_Id;
7019             E    : Entity_Id;
7020             D    : Node_Id;
7021             K    : Node_Kind;
7022
7023          begin
7024             Check_Ada_83_Warning;
7025             Check_No_Identifiers;
7026             Check_Arg_Count (1);
7027             Check_Arg_Is_Local_Name (Arg1);
7028             E_Id := Get_Pragma_Arg (Arg1);
7029
7030             if Etype (E_Id) = Any_Type then
7031                return;
7032             end if;
7033
7034             E := Entity (E_Id);
7035
7036             Check_Duplicate_Pragma (E);
7037
7038             if Rep_Item_Too_Early (E, N)
7039                  or else
7040                Rep_Item_Too_Late (E, N)
7041             then
7042                return;
7043             end if;
7044
7045             D := Declaration_Node (E);
7046             K := Nkind (D);
7047
7048             if (K = N_Full_Type_Declaration and then Is_Array_Type (E))
7049               or else
7050                 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
7051                    and then Nkind (D) = N_Object_Declaration
7052                    and then Nkind (Object_Definition (D)) =
7053                                        N_Constrained_Array_Definition)
7054             then
7055                --  The flag is set on the object, or on the base type
7056
7057                if Nkind (D) /= N_Object_Declaration then
7058                   E := Base_Type (E);
7059                end if;
7060
7061                Set_Has_Volatile_Components (E);
7062
7063                if Prag_Id = Pragma_Atomic_Components then
7064                   Set_Has_Atomic_Components (E);
7065                end if;
7066
7067             else
7068                Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
7069             end if;
7070          end Atomic_Components;
7071          --------------------
7072          -- Attach_Handler --
7073          --------------------
7074
7075          --  pragma Attach_Handler (handler_NAME, EXPRESSION);
7076
7077          when Pragma_Attach_Handler =>
7078             Check_Ada_83_Warning;
7079             Check_No_Identifiers;
7080             Check_Arg_Count (2);
7081
7082             if No_Run_Time_Mode then
7083                Error_Msg_CRT ("Attach_Handler pragma", N);
7084             else
7085                Check_Interrupt_Or_Attach_Handler;
7086
7087                --  The expression that designates the attribute may depend on a
7088                --  discriminant, and is therefore a per-object expression, to
7089                --  be expanded in the init proc. If expansion is enabled, then
7090                --  perform semantic checks on a copy only.
7091
7092                if Expander_Active then
7093                   declare
7094                      Temp : constant Node_Id :=
7095                               New_Copy_Tree (Get_Pragma_Arg (Arg2));
7096                   begin
7097                      Set_Parent (Temp, N);
7098                      Preanalyze_And_Resolve (Temp, RTE (RE_Interrupt_ID));
7099                   end;
7100
7101                else
7102                   Analyze (Get_Pragma_Arg (Arg2));
7103                   Resolve (Get_Pragma_Arg (Arg2), RTE (RE_Interrupt_ID));
7104                end if;
7105
7106                Process_Interrupt_Or_Attach_Handler;
7107             end if;
7108
7109          --------------------
7110          -- C_Pass_By_Copy --
7111          --------------------
7112
7113          --  pragma C_Pass_By_Copy ([Max_Size =>] static_integer_EXPRESSION);
7114
7115          when Pragma_C_Pass_By_Copy => C_Pass_By_Copy : declare
7116             Arg : Node_Id;
7117             Val : Uint;
7118
7119          begin
7120             GNAT_Pragma;
7121             Check_Valid_Configuration_Pragma;
7122             Check_Arg_Count (1);
7123             Check_Optional_Identifier (Arg1, "max_size");
7124
7125             Arg := Get_Pragma_Arg (Arg1);
7126             Check_Arg_Is_Static_Expression (Arg, Any_Integer);
7127
7128             Val := Expr_Value (Arg);
7129
7130             if Val <= 0 then
7131                Error_Pragma_Arg
7132                  ("maximum size for pragma% must be positive", Arg1);
7133
7134             elsif UI_Is_In_Int_Range (Val) then
7135                Default_C_Record_Mechanism := UI_To_Int (Val);
7136
7137             --  If a giant value is given, Int'Last will do well enough.
7138             --  If sometime someone complains that a record larger than
7139             --  two gigabytes is not copied, we will worry about it then!
7140
7141             else
7142                Default_C_Record_Mechanism := Mechanism_Type'Last;
7143             end if;
7144          end C_Pass_By_Copy;
7145
7146          -----------
7147          -- Check --
7148          -----------
7149
7150          --  pragma Check ([Name    =>] IDENTIFIER,
7151          --                [Check   =>] Boolean_EXPRESSION
7152          --              [,[Message =>] String_EXPRESSION]);
7153
7154          when Pragma_Check => Check : declare
7155             Expr : Node_Id;
7156             Eloc : Source_Ptr;
7157
7158             Check_On : Boolean;
7159             --  Set True if category of assertions referenced by Name enabled
7160
7161          begin
7162             GNAT_Pragma;
7163             Check_At_Least_N_Arguments (2);
7164             Check_At_Most_N_Arguments (3);
7165             Check_Optional_Identifier (Arg1, Name_Name);
7166             Check_Optional_Identifier (Arg2, Name_Check);
7167
7168             if Arg_Count = 3 then
7169                Check_Optional_Identifier (Arg3, Name_Message);
7170                Analyze_And_Resolve (Get_Pragma_Arg (Arg3), Standard_String);
7171             end if;
7172
7173             Check_Arg_Is_Identifier (Arg1);
7174
7175             --  Completely ignore if disabled
7176
7177             if Check_Disabled (Chars (Get_Pragma_Arg (Arg1))) then
7178                Rewrite (N, Make_Null_Statement (Loc));
7179                Analyze (N);
7180                return;
7181             end if;
7182
7183             --  Indicate if pragma is enabled. The Original_Node reference here
7184             --  is to deal with pragma Assert rewritten as a Check pragma.
7185
7186             Check_On := Check_Enabled (Chars (Get_Pragma_Arg (Arg1)));
7187
7188             if Check_On then
7189                Set_SCO_Pragma_Enabled (Loc);
7190             end if;
7191
7192             --  If expansion is active and the check is not enabled then we
7193             --  rewrite the Check as:
7194
7195             --    if False and then condition then
7196             --       null;
7197             --    end if;
7198
7199             --  The reason we do this rewriting during semantic analysis rather
7200             --  than as part of normal expansion is that we cannot analyze and
7201             --  expand the code for the boolean expression directly, or it may
7202             --  cause insertion of actions that would escape the attempt to
7203             --  suppress the check code.
7204
7205             --  Note that the Sloc for the if statement corresponds to the
7206             --  argument condition, not the pragma itself. The reason for this
7207             --  is that we may generate a warning if the condition is False at
7208             --  compile time, and we do not want to delete this warning when we
7209             --  delete the if statement.
7210
7211             Expr := Get_Pragma_Arg (Arg2);
7212
7213             if Expander_Active and then not Check_On then
7214                Eloc := Sloc (Expr);
7215
7216                Rewrite (N,
7217                  Make_If_Statement (Eloc,
7218                    Condition =>
7219                      Make_And_Then (Eloc,
7220                        Left_Opnd  => New_Occurrence_Of (Standard_False, Eloc),
7221                        Right_Opnd => Expr),
7222                    Then_Statements => New_List (
7223                      Make_Null_Statement (Eloc))));
7224
7225                Analyze (N);
7226
7227             --  Check is active
7228
7229             else
7230                Analyze_And_Resolve (Expr, Any_Boolean);
7231             end if;
7232          end Check;
7233
7234          ----------------
7235          -- Check_Name --
7236          ----------------
7237
7238          --  pragma Check_Name (check_IDENTIFIER);
7239
7240          when Pragma_Check_Name =>
7241             Check_No_Identifiers;
7242             GNAT_Pragma;
7243             Check_Valid_Configuration_Pragma;
7244             Check_Arg_Count (1);
7245             Check_Arg_Is_Identifier (Arg1);
7246
7247             declare
7248                Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
7249
7250             begin
7251                for J in Check_Names.First .. Check_Names.Last loop
7252                   if Check_Names.Table (J) = Nam then
7253                      return;
7254                   end if;
7255                end loop;
7256
7257                Check_Names.Append (Nam);
7258             end;
7259
7260          ------------------
7261          -- Check_Policy --
7262          ------------------
7263
7264          --  pragma Check_Policy (
7265          --    [Name   =>] IDENTIFIER,
7266          --    [Policy =>] POLICY_IDENTIFIER);
7267
7268          --  POLICY_IDENTIFIER ::= ON | OFF | CHECK | DISABLE | IGNORE
7269
7270          --  Note: this is a configuration pragma, but it is allowed to appear
7271          --  anywhere else.
7272
7273          when Pragma_Check_Policy =>
7274             GNAT_Pragma;
7275             Check_Arg_Count (2);
7276             Check_Optional_Identifier (Arg1, Name_Name);
7277             Check_Optional_Identifier (Arg2, Name_Policy);
7278             Check_Arg_Is_One_Of
7279               (Arg2, Name_On, Name_Off, Name_Check, Name_Disable, Name_Ignore);
7280
7281             --  A Check_Policy pragma can appear either as a configuration
7282             --  pragma, or in a declarative part or a package spec (see RM
7283             --  11.5(5) for rules for Suppress/Unsuppress which are also
7284             --  followed for Check_Policy).
7285
7286             if not Is_Configuration_Pragma then
7287                Check_Is_In_Decl_Part_Or_Package_Spec;
7288             end if;
7289
7290             Set_Next_Pragma (N, Opt.Check_Policy_List);
7291             Opt.Check_Policy_List := N;
7292
7293          ---------------------
7294          -- CIL_Constructor --
7295          ---------------------
7296
7297          --  pragma CIL_Constructor ([Entity =>] LOCAL_NAME);
7298
7299          --  Processing for this pragma is shared with Java_Constructor
7300
7301          -------------
7302          -- Comment --
7303          -------------
7304
7305          --  pragma Comment (static_string_EXPRESSION)
7306
7307          --  Processing for pragma Comment shares the circuitry for pragma
7308          --  Ident. The only differences are that Ident enforces a limit of 31
7309          --  characters on its argument, and also enforces limitations on
7310          --  placement for DEC compatibility. Pragma Comment shares neither of
7311          --  these restrictions.
7312
7313          -------------------
7314          -- Common_Object --
7315          -------------------
7316
7317          --  pragma Common_Object (
7318          --        [Internal =>] LOCAL_NAME
7319          --     [, [External =>] EXTERNAL_SYMBOL]
7320          --     [, [Size     =>] EXTERNAL_SYMBOL]);
7321
7322          --  Processing for this pragma is shared with Psect_Object
7323
7324          ------------------------
7325          -- Compile_Time_Error --
7326          ------------------------
7327
7328          --  pragma Compile_Time_Error
7329          --    (boolean_EXPRESSION, static_string_EXPRESSION);
7330
7331          when Pragma_Compile_Time_Error =>
7332             GNAT_Pragma;
7333             Process_Compile_Time_Warning_Or_Error;
7334
7335          --------------------------
7336          -- Compile_Time_Warning --
7337          --------------------------
7338
7339          --  pragma Compile_Time_Warning
7340          --    (boolean_EXPRESSION, static_string_EXPRESSION);
7341
7342          when Pragma_Compile_Time_Warning =>
7343             GNAT_Pragma;
7344             Process_Compile_Time_Warning_Or_Error;
7345
7346          -------------------
7347          -- Compiler_Unit --
7348          -------------------
7349
7350          when Pragma_Compiler_Unit =>
7351             GNAT_Pragma;
7352             Check_Arg_Count (0);
7353             Set_Is_Compiler_Unit (Get_Source_Unit (N));
7354
7355          -----------------------------
7356          -- Complete_Representation --
7357          -----------------------------
7358
7359          --  pragma Complete_Representation;
7360
7361          when Pragma_Complete_Representation =>
7362             GNAT_Pragma;
7363             Check_Arg_Count (0);
7364
7365             if Nkind (Parent (N)) /= N_Record_Representation_Clause then
7366                Error_Pragma
7367                  ("pragma & must appear within record representation clause");
7368             end if;
7369
7370          ----------------------------
7371          -- Complex_Representation --
7372          ----------------------------
7373
7374          --  pragma Complex_Representation ([Entity =>] LOCAL_NAME);
7375
7376          when Pragma_Complex_Representation => Complex_Representation : declare
7377             E_Id : Entity_Id;
7378             E    : Entity_Id;
7379             Ent  : Entity_Id;
7380
7381          begin
7382             GNAT_Pragma;
7383             Check_Arg_Count (1);
7384             Check_Optional_Identifier (Arg1, Name_Entity);
7385             Check_Arg_Is_Local_Name (Arg1);
7386             E_Id := Get_Pragma_Arg (Arg1);
7387
7388             if Etype (E_Id) = Any_Type then
7389                return;
7390             end if;
7391
7392             E := Entity (E_Id);
7393
7394             if not Is_Record_Type (E) then
7395                Error_Pragma_Arg
7396                  ("argument for pragma% must be record type", Arg1);
7397             end if;
7398
7399             Ent := First_Entity (E);
7400
7401             if No (Ent)
7402               or else No (Next_Entity (Ent))
7403               or else Present (Next_Entity (Next_Entity (Ent)))
7404               or else not Is_Floating_Point_Type (Etype (Ent))
7405               or else Etype (Ent) /= Etype (Next_Entity (Ent))
7406             then
7407                Error_Pragma_Arg
7408                  ("record for pragma% must have two fields of the same "
7409                   & "floating-point type", Arg1);
7410
7411             else
7412                Set_Has_Complex_Representation (Base_Type (E));
7413
7414                --  We need to treat the type has having a non-standard
7415                --  representation, for back-end purposes, even though in
7416                --  general a complex will have the default representation
7417                --  of a record with two real components.
7418
7419                Set_Has_Non_Standard_Rep (Base_Type (E));
7420             end if;
7421          end Complex_Representation;
7422
7423          -------------------------
7424          -- Component_Alignment --
7425          -------------------------
7426
7427          --  pragma Component_Alignment (
7428          --        [Form =>] ALIGNMENT_CHOICE
7429          --     [, [Name =>] type_LOCAL_NAME]);
7430          --
7431          --   ALIGNMENT_CHOICE ::=
7432          --     Component_Size
7433          --   | Component_Size_4
7434          --   | Storage_Unit
7435          --   | Default
7436
7437          when Pragma_Component_Alignment => Component_AlignmentP : declare
7438             Args  : Args_List (1 .. 2);
7439             Names : constant Name_List (1 .. 2) := (
7440                       Name_Form,
7441                       Name_Name);
7442
7443             Form  : Node_Id renames Args (1);
7444             Name  : Node_Id renames Args (2);
7445
7446             Atype : Component_Alignment_Kind;
7447             Typ   : Entity_Id;
7448
7449          begin
7450             GNAT_Pragma;
7451             Gather_Associations (Names, Args);
7452
7453             if No (Form) then
7454                Error_Pragma ("missing Form argument for pragma%");
7455             end if;
7456
7457             Check_Arg_Is_Identifier (Form);
7458
7459             --  Get proper alignment, note that Default = Component_Size on all
7460             --  machines we have so far, and we want to set this value rather
7461             --  than the default value to indicate that it has been explicitly
7462             --  set (and thus will not get overridden by the default component
7463             --  alignment for the current scope)
7464
7465             if Chars (Form) = Name_Component_Size then
7466                Atype := Calign_Component_Size;
7467
7468             elsif Chars (Form) = Name_Component_Size_4 then
7469                Atype := Calign_Component_Size_4;
7470
7471             elsif Chars (Form) = Name_Default then
7472                Atype := Calign_Component_Size;
7473
7474             elsif Chars (Form) = Name_Storage_Unit then
7475                Atype := Calign_Storage_Unit;
7476
7477             else
7478                Error_Pragma_Arg
7479                  ("invalid Form parameter for pragma%", Form);
7480             end if;
7481
7482             --  Case with no name, supplied, affects scope table entry
7483
7484             if No (Name) then
7485                Scope_Stack.Table
7486                  (Scope_Stack.Last).Component_Alignment_Default := Atype;
7487
7488             --  Case of name supplied
7489
7490             else
7491                Check_Arg_Is_Local_Name (Name);
7492                Find_Type (Name);
7493                Typ := Entity (Name);
7494
7495                if Typ = Any_Type
7496                  or else Rep_Item_Too_Early (Typ, N)
7497                then
7498                   return;
7499                else
7500                   Typ := Underlying_Type (Typ);
7501                end if;
7502
7503                if not Is_Record_Type (Typ)
7504                  and then not Is_Array_Type (Typ)
7505                then
7506                   Error_Pragma_Arg
7507                     ("Name parameter of pragma% must identify record or " &
7508                      "array type", Name);
7509                end if;
7510
7511                --  An explicit Component_Alignment pragma overrides an
7512                --  implicit pragma Pack, but not an explicit one.
7513
7514                if not Has_Pragma_Pack (Base_Type (Typ)) then
7515                   Set_Is_Packed (Base_Type (Typ), False);
7516                   Set_Component_Alignment (Base_Type (Typ), Atype);
7517                end if;
7518             end if;
7519          end Component_AlignmentP;
7520
7521          ----------------
7522          -- Controlled --
7523          ----------------
7524
7525          --  pragma Controlled (first_subtype_LOCAL_NAME);
7526
7527          when Pragma_Controlled => Controlled : declare
7528             Arg : Node_Id;
7529
7530          begin
7531             Check_No_Identifiers;
7532             Check_Arg_Count (1);
7533             Check_Arg_Is_Local_Name (Arg1);
7534             Arg := Get_Pragma_Arg (Arg1);
7535
7536             if not Is_Entity_Name (Arg)
7537               or else not Is_Access_Type (Entity (Arg))
7538             then
7539                Error_Pragma_Arg ("pragma% requires access type", Arg1);
7540             else
7541                Set_Has_Pragma_Controlled (Base_Type (Entity (Arg)));
7542             end if;
7543          end Controlled;
7544
7545          ----------------
7546          -- Convention --
7547          ----------------
7548
7549          --  pragma Convention ([Convention =>] convention_IDENTIFIER,
7550          --    [Entity =>] LOCAL_NAME);
7551
7552          when Pragma_Convention => Convention : declare
7553             C : Convention_Id;
7554             E : Entity_Id;
7555             pragma Warnings (Off, C);
7556             pragma Warnings (Off, E);
7557          begin
7558             Check_Arg_Order ((Name_Convention, Name_Entity));
7559             Check_Ada_83_Warning;
7560             Check_Arg_Count (2);
7561             Process_Convention (C, E);
7562          end Convention;
7563
7564          ---------------------------
7565          -- Convention_Identifier --
7566          ---------------------------
7567
7568          --  pragma Convention_Identifier ([Name =>] IDENTIFIER,
7569          --    [Convention =>] convention_IDENTIFIER);
7570
7571          when Pragma_Convention_Identifier => Convention_Identifier : declare
7572             Idnam : Name_Id;
7573             Cname : Name_Id;
7574
7575          begin
7576             GNAT_Pragma;
7577             Check_Arg_Order ((Name_Name, Name_Convention));
7578             Check_Arg_Count (2);
7579             Check_Optional_Identifier (Arg1, Name_Name);
7580             Check_Optional_Identifier (Arg2, Name_Convention);
7581             Check_Arg_Is_Identifier (Arg1);
7582             Check_Arg_Is_Identifier (Arg2);
7583             Idnam := Chars (Get_Pragma_Arg (Arg1));
7584             Cname := Chars (Get_Pragma_Arg (Arg2));
7585
7586             if Is_Convention_Name (Cname) then
7587                Record_Convention_Identifier
7588                  (Idnam, Get_Convention_Id (Cname));
7589             else
7590                Error_Pragma_Arg
7591                  ("second arg for % pragma must be convention", Arg2);
7592             end if;
7593          end Convention_Identifier;
7594
7595          ---------------
7596          -- CPP_Class --
7597          ---------------
7598
7599          --  pragma CPP_Class ([Entity =>] local_NAME)
7600
7601          when Pragma_CPP_Class => CPP_Class : declare
7602             Arg : Node_Id;
7603             Typ : Entity_Id;
7604
7605          begin
7606             if Warn_On_Obsolescent_Feature then
7607                Error_Msg_N
7608                  ("'G'N'A'T pragma cpp'_class is now obsolete; replace it" &
7609                   " by pragma import?", N);
7610             end if;
7611
7612             GNAT_Pragma;
7613             Check_Arg_Count (1);
7614             Check_Optional_Identifier (Arg1, Name_Entity);
7615             Check_Arg_Is_Local_Name (Arg1);
7616
7617             Arg := Get_Pragma_Arg (Arg1);
7618             Analyze (Arg);
7619
7620             if Etype (Arg) = Any_Type then
7621                return;
7622             end if;
7623
7624             if not Is_Entity_Name (Arg)
7625               or else not Is_Type (Entity (Arg))
7626             then
7627                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
7628             end if;
7629
7630             Typ := Entity (Arg);
7631
7632             if not Is_Tagged_Type (Typ) then
7633                Error_Pragma_Arg ("pragma% applicable to tagged types ", Arg1);
7634             end if;
7635
7636             --  Types treated as CPP classes must be declared limited (note:
7637             --  this used to be a warning but there is no real benefit to it
7638             --  since we did effectively intend to treat the type as limited
7639             --  anyway).
7640
7641             if not Is_Limited_Type (Typ) then
7642                Error_Msg_N
7643                  ("imported 'C'P'P type must be limited",
7644                   Get_Pragma_Arg (Arg1));
7645             end if;
7646
7647             Set_Is_CPP_Class (Typ);
7648             Set_Convention (Typ, Convention_CPP);
7649
7650             --  Imported CPP types must not have discriminants (because C++
7651             --  classes do not have discriminants).
7652
7653             if Has_Discriminants (Typ) then
7654                Error_Msg_N
7655                  ("imported 'C'P'P type cannot have discriminants",
7656                   First (Discriminant_Specifications
7657                           (Declaration_Node (Typ))));
7658             end if;
7659
7660             --  Components of imported CPP types must not have default
7661             --  expressions because the constructor (if any) is in the
7662             --  C++ side.
7663
7664             if Is_Incomplete_Or_Private_Type (Typ)
7665               and then No (Underlying_Type (Typ))
7666             then
7667                --  It should be an error to apply pragma CPP to a private
7668                --  type if the underlying type is not visible (as it is
7669                --  for any representation item). For now, for backward
7670                --  compatibility we do nothing but we cannot check components
7671                --  because they are not available at this stage. All this code
7672                --  will be removed when we cleanup this obsolete GNAT pragma???
7673
7674                null;
7675
7676             else
7677                declare
7678                   Tdef  : constant Node_Id :=
7679                             Type_Definition (Declaration_Node (Typ));
7680                   Clist : Node_Id;
7681                   Comp  : Node_Id;
7682
7683                begin
7684                   if Nkind (Tdef) = N_Record_Definition then
7685                      Clist := Component_List (Tdef);
7686                   else
7687                      pragma Assert (Nkind (Tdef) = N_Derived_Type_Definition);
7688                      Clist := Component_List (Record_Extension_Part (Tdef));
7689                   end if;
7690
7691                   if Present (Clist) then
7692                      Comp := First (Component_Items (Clist));
7693                      while Present (Comp) loop
7694                         if Present (Expression (Comp)) then
7695                            Error_Msg_N
7696                              ("component of imported 'C'P'P type cannot have" &
7697                               " default expression", Expression (Comp));
7698                         end if;
7699
7700                         Next (Comp);
7701                      end loop;
7702                   end if;
7703                end;
7704             end if;
7705          end CPP_Class;
7706
7707          ---------------------
7708          -- CPP_Constructor --
7709          ---------------------
7710
7711          --  pragma CPP_Constructor ([Entity =>] LOCAL_NAME
7712          --    [, [External_Name =>] static_string_EXPRESSION ]
7713          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
7714
7715          when Pragma_CPP_Constructor => CPP_Constructor : declare
7716             Elmt    : Elmt_Id;
7717             Id      : Entity_Id;
7718             Def_Id  : Entity_Id;
7719             Tag_Typ : Entity_Id;
7720
7721          begin
7722             GNAT_Pragma;
7723             Check_At_Least_N_Arguments (1);
7724             Check_At_Most_N_Arguments (3);
7725             Check_Optional_Identifier (Arg1, Name_Entity);
7726             Check_Arg_Is_Local_Name (Arg1);
7727
7728             Id := Get_Pragma_Arg (Arg1);
7729             Find_Program_Unit_Name (Id);
7730
7731             --  If we did not find the name, we are done
7732
7733             if Etype (Id) = Any_Type then
7734                return;
7735             end if;
7736
7737             Def_Id := Entity (Id);
7738
7739             --  Check if already defined as constructor
7740
7741             if Is_Constructor (Def_Id) then
7742                Error_Msg_N
7743                  ("?duplicate argument for pragma 'C'P'P_Constructor", Arg1);
7744                return;
7745             end if;
7746
7747             if Ekind (Def_Id) = E_Function
7748               and then (Is_CPP_Class (Etype (Def_Id))
7749                          or else (Is_Class_Wide_Type (Etype (Def_Id))
7750                                    and then
7751                                   Is_CPP_Class (Root_Type (Etype (Def_Id)))))
7752             then
7753                if Arg_Count >= 2 then
7754                   Set_Imported (Def_Id);
7755                   Set_Is_Public (Def_Id);
7756                   Process_Interface_Name (Def_Id, Arg2, Arg3);
7757                end if;
7758
7759                Set_Has_Completion (Def_Id);
7760                Set_Is_Constructor (Def_Id);
7761
7762                --  Imported C++ constructors are not dispatching primitives
7763                --  because in C++ they don't have a dispatch table slot.
7764                --  However, in Ada the constructor has the profile of a
7765                --  function that returns a tagged type and therefore it has
7766                --  been treated as a primitive operation during semantic
7767                --  analysis. We now remove it from the list of primitive
7768                --  operations of the type.
7769
7770                if Is_Tagged_Type (Etype (Def_Id))
7771                  and then not Is_Class_Wide_Type (Etype (Def_Id))
7772                then
7773                   pragma Assert (Is_Dispatching_Operation (Def_Id));
7774                   Tag_Typ := Etype (Def_Id);
7775
7776                   Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
7777                   while Present (Elmt) and then Node (Elmt) /= Def_Id loop
7778                      Next_Elmt (Elmt);
7779                   end loop;
7780
7781                   Remove_Elmt (Primitive_Operations (Tag_Typ), Elmt);
7782                   Set_Is_Dispatching_Operation (Def_Id, False);
7783                end if;
7784
7785                --  For backward compatibility, if the constructor returns a
7786                --  class wide type, and we internally change the return type to
7787                --  the corresponding root type.
7788
7789                if Is_Class_Wide_Type (Etype (Def_Id)) then
7790                   Set_Etype (Def_Id, Root_Type (Etype (Def_Id)));
7791                end if;
7792             else
7793                Error_Pragma_Arg
7794                  ("pragma% requires function returning a 'C'P'P_Class type",
7795                    Arg1);
7796             end if;
7797          end CPP_Constructor;
7798
7799          -----------------
7800          -- CPP_Virtual --
7801          -----------------
7802
7803          when Pragma_CPP_Virtual => CPP_Virtual : declare
7804          begin
7805             GNAT_Pragma;
7806
7807             if Warn_On_Obsolescent_Feature then
7808                Error_Msg_N
7809                  ("'G'N'A'T pragma cpp'_virtual is now obsolete and has " &
7810                   "no effect?", N);
7811             end if;
7812          end CPP_Virtual;
7813
7814          ----------------
7815          -- CPP_Vtable --
7816          ----------------
7817
7818          when Pragma_CPP_Vtable => CPP_Vtable : declare
7819          begin
7820             GNAT_Pragma;
7821
7822             if Warn_On_Obsolescent_Feature then
7823                Error_Msg_N
7824                  ("'G'N'A'T pragma cpp'_vtable is now obsolete and has " &
7825                   "no effect?", N);
7826             end if;
7827          end CPP_Vtable;
7828
7829          ---------
7830          -- CPU --
7831          ---------
7832
7833          --  pragma CPU (EXPRESSION);
7834
7835          when Pragma_CPU => CPU : declare
7836             P   : constant Node_Id := Parent (N);
7837             Arg : Node_Id;
7838
7839          begin
7840             Ada_2012_Pragma;
7841             Check_No_Identifiers;
7842             Check_Arg_Count (1);
7843
7844             --  Subprogram case
7845
7846             if Nkind (P) = N_Subprogram_Body then
7847                Check_In_Main_Program;
7848
7849                Arg := Get_Pragma_Arg (Arg1);
7850                Analyze_And_Resolve (Arg, Any_Integer);
7851
7852                --  Must be static
7853
7854                if not Is_Static_Expression (Arg) then
7855                   Flag_Non_Static_Expr
7856                     ("main subprogram affinity is not static!", Arg);
7857                   raise Pragma_Exit;
7858
7859                --  If constraint error, then we already signalled an error
7860
7861                elsif Raises_Constraint_Error (Arg) then
7862                   null;
7863
7864                --  Otherwise check in range
7865
7866                else
7867                   declare
7868                      CPU_Id : constant Entity_Id := RTE (RE_CPU_Range);
7869                      --  This is the entity System.Multiprocessors.CPU_Range;
7870
7871                      Val : constant Uint := Expr_Value (Arg);
7872
7873                   begin
7874                      if Val < Expr_Value (Type_Low_Bound (CPU_Id))
7875                           or else
7876                         Val > Expr_Value (Type_High_Bound (CPU_Id))
7877                      then
7878                         Error_Pragma_Arg
7879                           ("main subprogram CPU is out of range", Arg1);
7880                      end if;
7881                   end;
7882                end if;
7883
7884                Set_Main_CPU
7885                     (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
7886
7887             --  Task case
7888
7889             elsif Nkind (P) = N_Task_Definition then
7890                Arg := Get_Pragma_Arg (Arg1);
7891
7892                --  The expression must be analyzed in the special manner
7893                --  described in "Handling of Default and Per-Object
7894                --  Expressions" in sem.ads.
7895
7896                Preanalyze_Spec_Expression (Arg, RTE (RE_CPU_Range));
7897
7898             --  Anything else is incorrect
7899
7900             else
7901                Pragma_Misplaced;
7902             end if;
7903
7904             if Has_Pragma_CPU (P) then
7905                Error_Pragma ("duplicate pragma% not allowed");
7906             else
7907                Set_Has_Pragma_CPU (P, True);
7908
7909                if Nkind (P) = N_Task_Definition then
7910                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
7911                end if;
7912             end if;
7913          end CPU;
7914
7915          -----------
7916          -- Debug --
7917          -----------
7918
7919          --  pragma Debug ([boolean_EXPRESSION,] PROCEDURE_CALL_STATEMENT);
7920
7921          when Pragma_Debug => Debug : declare
7922             Cond : Node_Id;
7923             Call : Node_Id;
7924
7925          begin
7926             GNAT_Pragma;
7927
7928             --  Skip analysis if disabled
7929
7930             if Debug_Pragmas_Disabled then
7931                Rewrite (N, Make_Null_Statement (Loc));
7932                Analyze (N);
7933                return;
7934             end if;
7935
7936             Cond :=
7937               New_Occurrence_Of
7938                 (Boolean_Literals (Debug_Pragmas_Enabled and Expander_Active),
7939                  Loc);
7940
7941             if Debug_Pragmas_Enabled then
7942                Set_SCO_Pragma_Enabled (Loc);
7943             end if;
7944
7945             if Arg_Count = 2 then
7946                Cond :=
7947                  Make_And_Then (Loc,
7948                    Left_Opnd  => Relocate_Node (Cond),
7949                    Right_Opnd => Get_Pragma_Arg (Arg1));
7950                Call := Get_Pragma_Arg (Arg2);
7951             else
7952                Call := Get_Pragma_Arg (Arg1);
7953             end if;
7954
7955             if Nkind_In (Call,
7956                  N_Indexed_Component,
7957                  N_Function_Call,
7958                  N_Identifier,
7959                  N_Expanded_Name,
7960                  N_Selected_Component)
7961             then
7962                --  If this pragma Debug comes from source, its argument was
7963                --  parsed as a name form (which is syntactically identical).
7964                --  In a generic context a parameterless call will be left as
7965                --  an expanded name (if global) or selected_component if local.
7966                --  Change it to a procedure call statement now.
7967
7968                Change_Name_To_Procedure_Call_Statement (Call);
7969
7970             elsif Nkind (Call) = N_Procedure_Call_Statement then
7971
7972                --  Already in the form of a procedure call statement: nothing
7973                --  to do (could happen in case of an internally generated
7974                --  pragma Debug).
7975
7976                null;
7977
7978             else
7979                --  All other cases: diagnose error
7980
7981                Error_Msg
7982                  ("argument of pragma ""Debug"" is not procedure call",
7983                   Sloc (Call));
7984                return;
7985             end if;
7986
7987             --  Rewrite into a conditional with an appropriate condition. We
7988             --  wrap the procedure call in a block so that overhead from e.g.
7989             --  use of the secondary stack does not generate execution overhead
7990             --  for suppressed conditions.
7991
7992             --  Normally the analysis that follows will freeze the subprogram
7993             --  being called. However, if the call is to a null procedure,
7994             --  we want to freeze it before creating the block, because the
7995             --  analysis that follows may be done with expansion disabled, in
7996             --  which case the body will not be generated, leading to spurious
7997             --  errors.
7998
7999             if Nkind (Call) = N_Procedure_Call_Statement
8000               and then Is_Entity_Name (Name (Call))
8001             then
8002                Analyze (Name (Call));
8003                Freeze_Before (N, Entity (Name (Call)));
8004             end if;
8005
8006             Rewrite (N, Make_Implicit_If_Statement (N,
8007               Condition => Cond,
8008                  Then_Statements => New_List (
8009                    Make_Block_Statement (Loc,
8010                      Handled_Statement_Sequence =>
8011                        Make_Handled_Sequence_Of_Statements (Loc,
8012                          Statements => New_List (Relocate_Node (Call)))))));
8013             Analyze (N);
8014          end Debug;
8015
8016          ------------------
8017          -- Debug_Policy --
8018          ------------------
8019
8020          --  pragma Debug_Policy (Check | Ignore)
8021
8022          when Pragma_Debug_Policy =>
8023             GNAT_Pragma;
8024             Check_Arg_Count (1);
8025             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Disable, Name_Ignore);
8026             Debug_Pragmas_Enabled :=
8027               Chars (Get_Pragma_Arg (Arg1)) = Name_Check;
8028             Debug_Pragmas_Disabled :=
8029               Chars (Get_Pragma_Arg (Arg1)) = Name_Disable;
8030
8031          ---------------------
8032          -- Detect_Blocking --
8033          ---------------------
8034
8035          --  pragma Detect_Blocking;
8036
8037          when Pragma_Detect_Blocking =>
8038             Ada_2005_Pragma;
8039             Check_Arg_Count (0);
8040             Check_Valid_Configuration_Pragma;
8041             Detect_Blocking := True;
8042
8043          --------------------------
8044          -- Default_Storage_Pool --
8045          --------------------------
8046
8047          --  pragma Default_Storage_Pool (storage_pool_NAME | null);
8048
8049          when Pragma_Default_Storage_Pool =>
8050             Ada_2012_Pragma;
8051             Check_Arg_Count (1);
8052
8053             --  Default_Storage_Pool can appear as a configuration pragma, or
8054             --  in a declarative part or a package spec.
8055
8056             if not Is_Configuration_Pragma then
8057                Check_Is_In_Decl_Part_Or_Package_Spec;
8058             end if;
8059
8060             --  Case of Default_Storage_Pool (null);
8061
8062             if Nkind (Expression (Arg1)) = N_Null then
8063                Analyze (Expression (Arg1));
8064
8065                --  This is an odd case, this is not really an expression, so
8066                --  we don't have a type for it. So just set the type to Empty.
8067
8068                Set_Etype (Expression (Arg1), Empty);
8069
8070             --  Case of Default_Storage_Pool (storage_pool_NAME);
8071
8072             else
8073                --  If it's a configuration pragma, then the only allowed
8074                --  argument is "null".
8075
8076                if Is_Configuration_Pragma then
8077                   Error_Pragma_Arg ("NULL expected", Arg1);
8078                end if;
8079
8080                --  The expected type for a non-"null" argument is
8081                --  Root_Storage_Pool'Class.
8082
8083                Analyze_And_Resolve
8084                  (Get_Pragma_Arg (Arg1),
8085                   Typ => Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
8086             end if;
8087
8088             --  Finally, record the pool name (or null). Freeze.Freeze_Entity
8089             --  for an access type will use this information to set the
8090             --  appropriate attributes of the access type.
8091
8092             Default_Pool := Expression (Arg1);
8093
8094          ------------------------------------
8095          -- Disable_Atomic_Synchronization --
8096          ------------------------------------
8097
8098          --  pragma Disable_Atomic_Synchronization [(Entity)];
8099
8100          when Pragma_Disable_Atomic_Synchronization =>
8101             Process_Disable_Enable_Atomic_Sync (Name_Suppress);
8102
8103          -------------------
8104          -- Discard_Names --
8105          -------------------
8106
8107          --  pragma Discard_Names [([On =>] LOCAL_NAME)];
8108
8109          when Pragma_Discard_Names => Discard_Names : declare
8110             E    : Entity_Id;
8111             E_Id : Entity_Id;
8112
8113          begin
8114             Check_Ada_83_Warning;
8115
8116             --  Deal with configuration pragma case
8117
8118             if Arg_Count = 0 and then Is_Configuration_Pragma then
8119                Global_Discard_Names := True;
8120                return;
8121
8122             --  Otherwise, check correct appropriate context
8123
8124             else
8125                Check_Is_In_Decl_Part_Or_Package_Spec;
8126
8127                if Arg_Count = 0 then
8128
8129                   --  If there is no parameter, then from now on this pragma
8130                   --  applies to any enumeration, exception or tagged type
8131                   --  defined in the current declarative part, and recursively
8132                   --  to any nested scope.
8133
8134                   Set_Discard_Names (Current_Scope);
8135                   return;
8136
8137                else
8138                   Check_Arg_Count (1);
8139                   Check_Optional_Identifier (Arg1, Name_On);
8140                   Check_Arg_Is_Local_Name (Arg1);
8141
8142                   E_Id := Get_Pragma_Arg (Arg1);
8143
8144                   if Etype (E_Id) = Any_Type then
8145                      return;
8146                   else
8147                      E := Entity (E_Id);
8148                   end if;
8149
8150                   if (Is_First_Subtype (E)
8151                       and then
8152                         (Is_Enumeration_Type (E) or else Is_Tagged_Type (E)))
8153                     or else Ekind (E) = E_Exception
8154                   then
8155                      Set_Discard_Names (E);
8156                   else
8157                      Error_Pragma_Arg
8158                        ("inappropriate entity for pragma%", Arg1);
8159                   end if;
8160
8161                end if;
8162             end if;
8163          end Discard_Names;
8164
8165          ------------------------
8166          -- Dispatching_Domain --
8167          ------------------------
8168
8169          --  pragma Dispatching_Domain (EXPRESSION);
8170
8171          when Pragma_Dispatching_Domain => Dispatching_Domain : declare
8172             P   : constant Node_Id := Parent (N);
8173             Arg : Node_Id;
8174
8175          begin
8176             Ada_2012_Pragma;
8177             Check_No_Identifiers;
8178             Check_Arg_Count (1);
8179
8180             --  This pragma is born obsolete, but not the aspect
8181
8182             if not From_Aspect_Specification (N) then
8183                Check_Restriction
8184                  (No_Obsolescent_Features, Pragma_Identifier (N));
8185             end if;
8186
8187             if Nkind (P) = N_Task_Definition then
8188                Arg := Get_Pragma_Arg (Arg1);
8189
8190                --  The expression must be analyzed in the special manner
8191                --  described in "Handling of Default and Per-Object
8192                --  Expressions" in sem.ads.
8193
8194                Preanalyze_Spec_Expression (Arg, RTE (RE_Dispatching_Domain));
8195
8196             --  Anything else is incorrect
8197
8198             else
8199                Pragma_Misplaced;
8200             end if;
8201
8202             if Has_Pragma_Dispatching_Domain (P) then
8203                Error_Pragma ("duplicate pragma% not allowed");
8204             else
8205                Set_Has_Pragma_Dispatching_Domain (P, True);
8206
8207                if Nkind (P) = N_Task_Definition then
8208                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
8209                end if;
8210             end if;
8211          end Dispatching_Domain;
8212
8213          ---------------
8214          -- Elaborate --
8215          ---------------
8216
8217          --  pragma Elaborate (library_unit_NAME {, library_unit_NAME});
8218
8219          when Pragma_Elaborate => Elaborate : declare
8220             Arg   : Node_Id;
8221             Citem : Node_Id;
8222
8223          begin
8224             --  Pragma must be in context items list of a compilation unit
8225
8226             if not Is_In_Context_Clause then
8227                Pragma_Misplaced;
8228             end if;
8229
8230             --  Must be at least one argument
8231
8232             if Arg_Count = 0 then
8233                Error_Pragma ("pragma% requires at least one argument");
8234             end if;
8235
8236             --  In Ada 83 mode, there can be no items following it in the
8237             --  context list except other pragmas and implicit with clauses
8238             --  (e.g. those added by use of Rtsfind). In Ada 95 mode, this
8239             --  placement rule does not apply.
8240
8241             if Ada_Version = Ada_83 and then Comes_From_Source (N) then
8242                Citem := Next (N);
8243                while Present (Citem) loop
8244                   if Nkind (Citem) = N_Pragma
8245                     or else (Nkind (Citem) = N_With_Clause
8246                               and then Implicit_With (Citem))
8247                   then
8248                      null;
8249                   else
8250                      Error_Pragma
8251                        ("(Ada 83) pragma% must be at end of context clause");
8252                   end if;
8253
8254                   Next (Citem);
8255                end loop;
8256             end if;
8257
8258             --  Finally, the arguments must all be units mentioned in a with
8259             --  clause in the same context clause. Note we already checked (in
8260             --  Par.Prag) that the arguments are all identifiers or selected
8261             --  components.
8262
8263             Arg := Arg1;
8264             Outer : while Present (Arg) loop
8265                Citem := First (List_Containing (N));
8266                Inner : while Citem /= N loop
8267                   if Nkind (Citem) = N_With_Clause
8268                     and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
8269                   then
8270                      Set_Elaborate_Present (Citem, True);
8271                      Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
8272                      Generate_Reference (Entity (Name (Citem)), Citem);
8273
8274                      --  With the pragma present, elaboration calls on
8275                      --  subprograms from the named unit need no further
8276                      --  checks, as long as the pragma appears in the current
8277                      --  compilation unit. If the pragma appears in some unit
8278                      --  in the context, there might still be a need for an
8279                      --  Elaborate_All_Desirable from the current compilation
8280                      --  to the named unit, so we keep the check enabled.
8281
8282                      if In_Extended_Main_Source_Unit (N) then
8283                         Set_Suppress_Elaboration_Warnings
8284                           (Entity (Name (Citem)));
8285                      end if;
8286
8287                      exit Inner;
8288                   end if;
8289
8290                   Next (Citem);
8291                end loop Inner;
8292
8293                if Citem = N then
8294                   Error_Pragma_Arg
8295                     ("argument of pragma% is not withed unit", Arg);
8296                end if;
8297
8298                Next (Arg);
8299             end loop Outer;
8300
8301             --  Give a warning if operating in static mode with -gnatwl
8302             --  (elaboration warnings enabled) switch set.
8303
8304             if Elab_Warnings and not Dynamic_Elaboration_Checks then
8305                Error_Msg_N
8306                  ("?use of pragma Elaborate may not be safe", N);
8307                Error_Msg_N
8308                  ("?use pragma Elaborate_All instead if possible", N);
8309             end if;
8310          end Elaborate;
8311
8312          -------------------
8313          -- Elaborate_All --
8314          -------------------
8315
8316          --  pragma Elaborate_All (library_unit_NAME {, library_unit_NAME});
8317
8318          when Pragma_Elaborate_All => Elaborate_All : declare
8319             Arg   : Node_Id;
8320             Citem : Node_Id;
8321
8322          begin
8323             Check_Ada_83_Warning;
8324
8325             --  Pragma must be in context items list of a compilation unit
8326
8327             if not Is_In_Context_Clause then
8328                Pragma_Misplaced;
8329             end if;
8330
8331             --  Must be at least one argument
8332
8333             if Arg_Count = 0 then
8334                Error_Pragma ("pragma% requires at least one argument");
8335             end if;
8336
8337             --  Note: unlike pragma Elaborate, pragma Elaborate_All does not
8338             --  have to appear at the end of the context clause, but may
8339             --  appear mixed in with other items, even in Ada 83 mode.
8340
8341             --  Final check: the arguments must all be units mentioned in
8342             --  a with clause in the same context clause. Note that we
8343             --  already checked (in Par.Prag) that all the arguments are
8344             --  either identifiers or selected components.
8345
8346             Arg := Arg1;
8347             Outr : while Present (Arg) loop
8348                Citem := First (List_Containing (N));
8349                Innr : while Citem /= N loop
8350                   if Nkind (Citem) = N_With_Clause
8351                     and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
8352                   then
8353                      Set_Elaborate_All_Present (Citem, True);
8354                      Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
8355
8356                      --  Suppress warnings and elaboration checks on the named
8357                      --  unit if the pragma is in the current compilation, as
8358                      --  for pragma Elaborate.
8359
8360                      if In_Extended_Main_Source_Unit (N) then
8361                         Set_Suppress_Elaboration_Warnings
8362                           (Entity (Name (Citem)));
8363                      end if;
8364                      exit Innr;
8365                   end if;
8366
8367                   Next (Citem);
8368                end loop Innr;
8369
8370                if Citem = N then
8371                   Set_Error_Posted (N);
8372                   Error_Pragma_Arg
8373                     ("argument of pragma% is not withed unit", Arg);
8374                end if;
8375
8376                Next (Arg);
8377             end loop Outr;
8378          end Elaborate_All;
8379
8380          --------------------
8381          -- Elaborate_Body --
8382          --------------------
8383
8384          --  pragma Elaborate_Body [( library_unit_NAME )];
8385
8386          when Pragma_Elaborate_Body => Elaborate_Body : declare
8387             Cunit_Node : Node_Id;
8388             Cunit_Ent  : Entity_Id;
8389
8390          begin
8391             Check_Ada_83_Warning;
8392             Check_Valid_Library_Unit_Pragma;
8393
8394             if Nkind (N) = N_Null_Statement then
8395                return;
8396             end if;
8397
8398             Cunit_Node := Cunit (Current_Sem_Unit);
8399             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
8400
8401             if Nkind_In (Unit (Cunit_Node), N_Package_Body,
8402                                             N_Subprogram_Body)
8403             then
8404                Error_Pragma ("pragma% must refer to a spec, not a body");
8405             else
8406                Set_Body_Required (Cunit_Node, True);
8407                Set_Has_Pragma_Elaborate_Body (Cunit_Ent);
8408
8409                --  If we are in dynamic elaboration mode, then we suppress
8410                --  elaboration warnings for the unit, since it is definitely
8411                --  fine NOT to do dynamic checks at the first level (and such
8412                --  checks will be suppressed because no elaboration boolean
8413                --  is created for Elaborate_Body packages).
8414
8415                --  But in the static model of elaboration, Elaborate_Body is
8416                --  definitely NOT good enough to ensure elaboration safety on
8417                --  its own, since the body may WITH other units that are not
8418                --  safe from an elaboration point of view, so a client must
8419                --  still do an Elaborate_All on such units.
8420
8421                --  Debug flag -gnatdD restores the old behavior of 3.13, where
8422                --  Elaborate_Body always suppressed elab warnings.
8423
8424                if Dynamic_Elaboration_Checks or Debug_Flag_DD then
8425                   Set_Suppress_Elaboration_Warnings (Cunit_Ent);
8426                end if;
8427             end if;
8428          end Elaborate_Body;
8429
8430          ------------------------
8431          -- Elaboration_Checks --
8432          ------------------------
8433
8434          --  pragma Elaboration_Checks (Static | Dynamic);
8435
8436          when Pragma_Elaboration_Checks =>
8437             GNAT_Pragma;
8438             Check_Arg_Count (1);
8439             Check_Arg_Is_One_Of (Arg1, Name_Static, Name_Dynamic);
8440             Dynamic_Elaboration_Checks :=
8441               (Chars (Get_Pragma_Arg (Arg1)) = Name_Dynamic);
8442
8443          ---------------
8444          -- Eliminate --
8445          ---------------
8446
8447          --  pragma Eliminate (
8448          --      [Unit_Name  =>] IDENTIFIER | SELECTED_COMPONENT,
8449          --    [,[Entity     =>] IDENTIFIER |
8450          --                      SELECTED_COMPONENT |
8451          --                      STRING_LITERAL]
8452          --    [,                OVERLOADING_RESOLUTION]);
8453
8454          --  OVERLOADING_RESOLUTION ::= PARAMETER_AND_RESULT_TYPE_PROFILE |
8455          --                             SOURCE_LOCATION
8456
8457          --  PARAMETER_AND_RESULT_TYPE_PROFILE ::= PROCEDURE_PROFILE |
8458          --                                        FUNCTION_PROFILE
8459
8460          --  PROCEDURE_PROFILE ::= Parameter_Types => PARAMETER_TYPES
8461
8462          --  FUNCTION_PROFILE ::= [Parameter_Types => PARAMETER_TYPES,]
8463          --                       Result_Type => result_SUBTYPE_NAME]
8464
8465          --  PARAMETER_TYPES ::= (SUBTYPE_NAME {, SUBTYPE_NAME})
8466          --  SUBTYPE_NAME    ::= STRING_LITERAL
8467
8468          --  SOURCE_LOCATION ::= Source_Location => SOURCE_TRACE
8469          --  SOURCE_TRACE    ::= STRING_LITERAL
8470
8471          when Pragma_Eliminate => Eliminate : declare
8472             Args  : Args_List (1 .. 5);
8473             Names : constant Name_List (1 .. 5) := (
8474                       Name_Unit_Name,
8475                       Name_Entity,
8476                       Name_Parameter_Types,
8477                       Name_Result_Type,
8478                       Name_Source_Location);
8479
8480             Unit_Name       : Node_Id renames Args (1);
8481             Entity          : Node_Id renames Args (2);
8482             Parameter_Types : Node_Id renames Args (3);
8483             Result_Type     : Node_Id renames Args (4);
8484             Source_Location : Node_Id renames Args (5);
8485
8486          begin
8487             GNAT_Pragma;
8488             Check_Valid_Configuration_Pragma;
8489             Gather_Associations (Names, Args);
8490
8491             if No (Unit_Name) then
8492                Error_Pragma ("missing Unit_Name argument for pragma%");
8493             end if;
8494
8495             if No (Entity)
8496               and then (Present (Parameter_Types)
8497                           or else
8498                         Present (Result_Type)
8499                           or else
8500                         Present (Source_Location))
8501             then
8502                Error_Pragma ("missing Entity argument for pragma%");
8503             end if;
8504
8505             if (Present (Parameter_Types)
8506                   or else
8507                 Present (Result_Type))
8508               and then
8509                 Present (Source_Location)
8510             then
8511                Error_Pragma
8512                  ("parameter profile and source location cannot " &
8513                   "be used together in pragma%");
8514             end if;
8515
8516             Process_Eliminate_Pragma
8517               (N,
8518                Unit_Name,
8519                Entity,
8520                Parameter_Types,
8521                Result_Type,
8522                Source_Location);
8523          end Eliminate;
8524
8525          -----------------------------------
8526          -- Enable_Atomic_Synchronization --
8527          -----------------------------------
8528
8529          --  pragma Enable_Atomic_Synchronization [(Entity)];
8530
8531          when Pragma_Enable_Atomic_Synchronization =>
8532             Process_Disable_Enable_Atomic_Sync (Name_Unsuppress);
8533
8534          ------------
8535          -- Export --
8536          ------------
8537
8538          --  pragma Export (
8539          --    [   Convention    =>] convention_IDENTIFIER,
8540          --    [   Entity        =>] local_NAME
8541          --    [, [External_Name =>] static_string_EXPRESSION ]
8542          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
8543
8544          when Pragma_Export => Export : declare
8545             C      : Convention_Id;
8546             Def_Id : Entity_Id;
8547
8548             pragma Warnings (Off, C);
8549
8550          begin
8551             Check_Ada_83_Warning;
8552             Check_Arg_Order
8553               ((Name_Convention,
8554                 Name_Entity,
8555                 Name_External_Name,
8556                 Name_Link_Name));
8557             Check_At_Least_N_Arguments (2);
8558             Check_At_Most_N_Arguments  (4);
8559             Process_Convention (C, Def_Id);
8560
8561             if Ekind (Def_Id) /= E_Constant then
8562                Note_Possible_Modification
8563                  (Get_Pragma_Arg (Arg2), Sure => False);
8564             end if;
8565
8566             Process_Interface_Name (Def_Id, Arg3, Arg4);
8567             Set_Exported (Def_Id, Arg2);
8568
8569             --  If the entity is a deferred constant, propagate the information
8570             --  to the full view, because gigi elaborates the full view only.
8571
8572             if Ekind (Def_Id) = E_Constant
8573               and then Present (Full_View (Def_Id))
8574             then
8575                declare
8576                   Id2 : constant Entity_Id := Full_View (Def_Id);
8577                begin
8578                   Set_Is_Exported    (Id2, Is_Exported          (Def_Id));
8579                   Set_First_Rep_Item (Id2, First_Rep_Item       (Def_Id));
8580                   Set_Interface_Name (Id2, Einfo.Interface_Name (Def_Id));
8581                end;
8582             end if;
8583          end Export;
8584
8585          ----------------------
8586          -- Export_Exception --
8587          ----------------------
8588
8589          --  pragma Export_Exception (
8590          --        [Internal         =>] LOCAL_NAME
8591          --     [, [External         =>] EXTERNAL_SYMBOL]
8592          --     [, [Form     =>] Ada | VMS]
8593          --     [, [Code     =>] static_integer_EXPRESSION]);
8594
8595          when Pragma_Export_Exception => Export_Exception : declare
8596             Args  : Args_List (1 .. 4);
8597             Names : constant Name_List (1 .. 4) := (
8598                       Name_Internal,
8599                       Name_External,
8600                       Name_Form,
8601                       Name_Code);
8602
8603             Internal : Node_Id renames Args (1);
8604             External : Node_Id renames Args (2);
8605             Form     : Node_Id renames Args (3);
8606             Code     : Node_Id renames Args (4);
8607
8608          begin
8609             GNAT_Pragma;
8610
8611             if Inside_A_Generic then
8612                Error_Pragma ("pragma% cannot be used for generic entities");
8613             end if;
8614
8615             Gather_Associations (Names, Args);
8616             Process_Extended_Import_Export_Exception_Pragma (
8617               Arg_Internal => Internal,
8618               Arg_External => External,
8619               Arg_Form     => Form,
8620               Arg_Code     => Code);
8621
8622             if not Is_VMS_Exception (Entity (Internal)) then
8623                Set_Exported (Entity (Internal), Internal);
8624             end if;
8625          end Export_Exception;
8626
8627          ---------------------
8628          -- Export_Function --
8629          ---------------------
8630
8631          --  pragma Export_Function (
8632          --        [Internal         =>] LOCAL_NAME
8633          --     [, [External         =>] EXTERNAL_SYMBOL]
8634          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8635          --     [, [Result_Type      =>] TYPE_DESIGNATOR]
8636          --     [, [Mechanism        =>] MECHANISM]
8637          --     [, [Result_Mechanism =>] MECHANISM_NAME]);
8638
8639          --  EXTERNAL_SYMBOL ::=
8640          --    IDENTIFIER
8641          --  | static_string_EXPRESSION
8642
8643          --  PARAMETER_TYPES ::=
8644          --    null
8645          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8646
8647          --  TYPE_DESIGNATOR ::=
8648          --    subtype_NAME
8649          --  | subtype_Name ' Access
8650
8651          --  MECHANISM ::=
8652          --    MECHANISM_NAME
8653          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8654
8655          --  MECHANISM_ASSOCIATION ::=
8656          --    [formal_parameter_NAME =>] MECHANISM_NAME
8657
8658          --  MECHANISM_NAME ::=
8659          --    Value
8660          --  | Reference
8661          --  | Descriptor [([Class =>] CLASS_NAME)]
8662
8663          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8664
8665          when Pragma_Export_Function => Export_Function : declare
8666             Args  : Args_List (1 .. 6);
8667             Names : constant Name_List (1 .. 6) := (
8668                       Name_Internal,
8669                       Name_External,
8670                       Name_Parameter_Types,
8671                       Name_Result_Type,
8672                       Name_Mechanism,
8673                       Name_Result_Mechanism);
8674
8675             Internal         : Node_Id renames Args (1);
8676             External         : Node_Id renames Args (2);
8677             Parameter_Types  : Node_Id renames Args (3);
8678             Result_Type      : Node_Id renames Args (4);
8679             Mechanism        : Node_Id renames Args (5);
8680             Result_Mechanism : Node_Id renames Args (6);
8681
8682          begin
8683             GNAT_Pragma;
8684             Gather_Associations (Names, Args);
8685             Process_Extended_Import_Export_Subprogram_Pragma (
8686               Arg_Internal         => Internal,
8687               Arg_External         => External,
8688               Arg_Parameter_Types  => Parameter_Types,
8689               Arg_Result_Type      => Result_Type,
8690               Arg_Mechanism        => Mechanism,
8691               Arg_Result_Mechanism => Result_Mechanism);
8692          end Export_Function;
8693
8694          -------------------
8695          -- Export_Object --
8696          -------------------
8697
8698          --  pragma Export_Object (
8699          --        [Internal =>] LOCAL_NAME
8700          --     [, [External =>] EXTERNAL_SYMBOL]
8701          --     [, [Size     =>] EXTERNAL_SYMBOL]);
8702
8703          --  EXTERNAL_SYMBOL ::=
8704          --    IDENTIFIER
8705          --  | static_string_EXPRESSION
8706
8707          --  PARAMETER_TYPES ::=
8708          --    null
8709          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8710
8711          --  TYPE_DESIGNATOR ::=
8712          --    subtype_NAME
8713          --  | subtype_Name ' Access
8714
8715          --  MECHANISM ::=
8716          --    MECHANISM_NAME
8717          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8718
8719          --  MECHANISM_ASSOCIATION ::=
8720          --    [formal_parameter_NAME =>] MECHANISM_NAME
8721
8722          --  MECHANISM_NAME ::=
8723          --    Value
8724          --  | Reference
8725          --  | Descriptor [([Class =>] CLASS_NAME)]
8726
8727          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8728
8729          when Pragma_Export_Object => Export_Object : declare
8730             Args  : Args_List (1 .. 3);
8731             Names : constant Name_List (1 .. 3) := (
8732                       Name_Internal,
8733                       Name_External,
8734                       Name_Size);
8735
8736             Internal : Node_Id renames Args (1);
8737             External : Node_Id renames Args (2);
8738             Size     : Node_Id renames Args (3);
8739
8740          begin
8741             GNAT_Pragma;
8742             Gather_Associations (Names, Args);
8743             Process_Extended_Import_Export_Object_Pragma (
8744               Arg_Internal => Internal,
8745               Arg_External => External,
8746               Arg_Size     => Size);
8747          end Export_Object;
8748
8749          ----------------------
8750          -- Export_Procedure --
8751          ----------------------
8752
8753          --  pragma Export_Procedure (
8754          --        [Internal         =>] LOCAL_NAME
8755          --     [, [External         =>] EXTERNAL_SYMBOL]
8756          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8757          --     [, [Mechanism        =>] MECHANISM]);
8758
8759          --  EXTERNAL_SYMBOL ::=
8760          --    IDENTIFIER
8761          --  | static_string_EXPRESSION
8762
8763          --  PARAMETER_TYPES ::=
8764          --    null
8765          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8766
8767          --  TYPE_DESIGNATOR ::=
8768          --    subtype_NAME
8769          --  | subtype_Name ' Access
8770
8771          --  MECHANISM ::=
8772          --    MECHANISM_NAME
8773          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8774
8775          --  MECHANISM_ASSOCIATION ::=
8776          --    [formal_parameter_NAME =>] MECHANISM_NAME
8777
8778          --  MECHANISM_NAME ::=
8779          --    Value
8780          --  | Reference
8781          --  | Descriptor [([Class =>] CLASS_NAME)]
8782
8783          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8784
8785          when Pragma_Export_Procedure => Export_Procedure : declare
8786             Args  : Args_List (1 .. 4);
8787             Names : constant Name_List (1 .. 4) := (
8788                       Name_Internal,
8789                       Name_External,
8790                       Name_Parameter_Types,
8791                       Name_Mechanism);
8792
8793             Internal        : Node_Id renames Args (1);
8794             External        : Node_Id renames Args (2);
8795             Parameter_Types : Node_Id renames Args (3);
8796             Mechanism       : Node_Id renames Args (4);
8797
8798          begin
8799             GNAT_Pragma;
8800             Gather_Associations (Names, Args);
8801             Process_Extended_Import_Export_Subprogram_Pragma (
8802               Arg_Internal        => Internal,
8803               Arg_External        => External,
8804               Arg_Parameter_Types => Parameter_Types,
8805               Arg_Mechanism       => Mechanism);
8806          end Export_Procedure;
8807
8808          ------------------
8809          -- Export_Value --
8810          ------------------
8811
8812          --  pragma Export_Value (
8813          --     [Value     =>] static_integer_EXPRESSION,
8814          --     [Link_Name =>] static_string_EXPRESSION);
8815
8816          when Pragma_Export_Value =>
8817             GNAT_Pragma;
8818             Check_Arg_Order ((Name_Value, Name_Link_Name));
8819             Check_Arg_Count (2);
8820
8821             Check_Optional_Identifier (Arg1, Name_Value);
8822             Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
8823
8824             Check_Optional_Identifier (Arg2, Name_Link_Name);
8825             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
8826
8827          -----------------------------
8828          -- Export_Valued_Procedure --
8829          -----------------------------
8830
8831          --  pragma Export_Valued_Procedure (
8832          --        [Internal         =>] LOCAL_NAME
8833          --     [, [External         =>] EXTERNAL_SYMBOL,]
8834          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8835          --     [, [Mechanism        =>] MECHANISM]);
8836
8837          --  EXTERNAL_SYMBOL ::=
8838          --    IDENTIFIER
8839          --  | static_string_EXPRESSION
8840
8841          --  PARAMETER_TYPES ::=
8842          --    null
8843          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8844
8845          --  TYPE_DESIGNATOR ::=
8846          --    subtype_NAME
8847          --  | subtype_Name ' Access
8848
8849          --  MECHANISM ::=
8850          --    MECHANISM_NAME
8851          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8852
8853          --  MECHANISM_ASSOCIATION ::=
8854          --    [formal_parameter_NAME =>] MECHANISM_NAME
8855
8856          --  MECHANISM_NAME ::=
8857          --    Value
8858          --  | Reference
8859          --  | Descriptor [([Class =>] CLASS_NAME)]
8860
8861          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8862
8863          when Pragma_Export_Valued_Procedure =>
8864          Export_Valued_Procedure : declare
8865             Args  : Args_List (1 .. 4);
8866             Names : constant Name_List (1 .. 4) := (
8867                       Name_Internal,
8868                       Name_External,
8869                       Name_Parameter_Types,
8870                       Name_Mechanism);
8871
8872             Internal        : Node_Id renames Args (1);
8873             External        : Node_Id renames Args (2);
8874             Parameter_Types : Node_Id renames Args (3);
8875             Mechanism       : Node_Id renames Args (4);
8876
8877          begin
8878             GNAT_Pragma;
8879             Gather_Associations (Names, Args);
8880             Process_Extended_Import_Export_Subprogram_Pragma (
8881               Arg_Internal        => Internal,
8882               Arg_External        => External,
8883               Arg_Parameter_Types => Parameter_Types,
8884               Arg_Mechanism       => Mechanism);
8885          end Export_Valued_Procedure;
8886
8887          -------------------
8888          -- Extend_System --
8889          -------------------
8890
8891          --  pragma Extend_System ([Name =>] Identifier);
8892
8893          when Pragma_Extend_System => Extend_System : declare
8894          begin
8895             GNAT_Pragma;
8896             Check_Valid_Configuration_Pragma;
8897             Check_Arg_Count (1);
8898             Check_Optional_Identifier (Arg1, Name_Name);
8899             Check_Arg_Is_Identifier (Arg1);
8900
8901             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
8902
8903             if Name_Len > 4
8904               and then Name_Buffer (1 .. 4) = "aux_"
8905             then
8906                if Present (System_Extend_Pragma_Arg) then
8907                   if Chars (Get_Pragma_Arg (Arg1)) =
8908                      Chars (Expression (System_Extend_Pragma_Arg))
8909                   then
8910                      null;
8911                   else
8912                      Error_Msg_Sloc := Sloc (System_Extend_Pragma_Arg);
8913                      Error_Pragma ("pragma% conflicts with that #");
8914                   end if;
8915
8916                else
8917                   System_Extend_Pragma_Arg := Arg1;
8918
8919                   if not GNAT_Mode then
8920                      System_Extend_Unit := Arg1;
8921                   end if;
8922                end if;
8923             else
8924                Error_Pragma ("incorrect name for pragma%, must be Aux_xxx");
8925             end if;
8926          end Extend_System;
8927
8928          ------------------------
8929          -- Extensions_Allowed --
8930          ------------------------
8931
8932          --  pragma Extensions_Allowed (ON | OFF);
8933
8934          when Pragma_Extensions_Allowed =>
8935             GNAT_Pragma;
8936             Check_Arg_Count (1);
8937             Check_No_Identifiers;
8938             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
8939
8940             if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
8941                Extensions_Allowed := True;
8942                Ada_Version := Ada_Version_Type'Last;
8943
8944             else
8945                Extensions_Allowed := False;
8946                Ada_Version := Ada_Version_Explicit;
8947             end if;
8948
8949          --------------
8950          -- External --
8951          --------------
8952
8953          --  pragma External (
8954          --    [   Convention    =>] convention_IDENTIFIER,
8955          --    [   Entity        =>] local_NAME
8956          --    [, [External_Name =>] static_string_EXPRESSION ]
8957          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
8958
8959          when Pragma_External => External : declare
8960                Def_Id : Entity_Id;
8961
8962                C : Convention_Id;
8963                pragma Warnings (Off, C);
8964
8965          begin
8966             GNAT_Pragma;
8967             Check_Arg_Order
8968               ((Name_Convention,
8969                 Name_Entity,
8970                 Name_External_Name,
8971                 Name_Link_Name));
8972             Check_At_Least_N_Arguments (2);
8973             Check_At_Most_N_Arguments  (4);
8974             Process_Convention (C, Def_Id);
8975             Note_Possible_Modification
8976               (Get_Pragma_Arg (Arg2), Sure => False);
8977             Process_Interface_Name (Def_Id, Arg3, Arg4);
8978             Set_Exported (Def_Id, Arg2);
8979          end External;
8980
8981          --------------------------
8982          -- External_Name_Casing --
8983          --------------------------
8984
8985          --  pragma External_Name_Casing (
8986          --    UPPERCASE | LOWERCASE
8987          --    [, AS_IS | UPPERCASE | LOWERCASE]);
8988
8989          when Pragma_External_Name_Casing => External_Name_Casing : declare
8990          begin
8991             GNAT_Pragma;
8992             Check_No_Identifiers;
8993
8994             if Arg_Count = 2 then
8995                Check_Arg_Is_One_Of
8996                  (Arg2, Name_As_Is, Name_Uppercase, Name_Lowercase);
8997
8998                case Chars (Get_Pragma_Arg (Arg2)) is
8999                   when Name_As_Is     =>
9000                      Opt.External_Name_Exp_Casing := As_Is;
9001
9002                   when Name_Uppercase =>
9003                      Opt.External_Name_Exp_Casing := Uppercase;
9004
9005                   when Name_Lowercase =>
9006                      Opt.External_Name_Exp_Casing := Lowercase;
9007
9008                   when others =>
9009                      null;
9010                end case;
9011
9012             else
9013                Check_Arg_Count (1);
9014             end if;
9015
9016             Check_Arg_Is_One_Of (Arg1, Name_Uppercase, Name_Lowercase);
9017
9018             case Chars (Get_Pragma_Arg (Arg1)) is
9019                when Name_Uppercase =>
9020                   Opt.External_Name_Imp_Casing := Uppercase;
9021
9022                when Name_Lowercase =>
9023                   Opt.External_Name_Imp_Casing := Lowercase;
9024
9025                when others =>
9026                   null;
9027             end case;
9028          end External_Name_Casing;
9029
9030          --------------------------
9031          -- Favor_Top_Level --
9032          --------------------------
9033
9034          --  pragma Favor_Top_Level (type_NAME);
9035
9036          when Pragma_Favor_Top_Level => Favor_Top_Level : declare
9037                Named_Entity : Entity_Id;
9038
9039          begin
9040             GNAT_Pragma;
9041             Check_No_Identifiers;
9042             Check_Arg_Count (1);
9043             Check_Arg_Is_Local_Name (Arg1);
9044             Named_Entity := Entity (Get_Pragma_Arg (Arg1));
9045
9046             --  If it's an access-to-subprogram type (in particular, not a
9047             --  subtype), set the flag on that type.
9048
9049             if Is_Access_Subprogram_Type (Named_Entity) then
9050                Set_Can_Use_Internal_Rep (Named_Entity, False);
9051
9052             --  Otherwise it's an error (name denotes the wrong sort of entity)
9053
9054             else
9055                Error_Pragma_Arg
9056                  ("access-to-subprogram type expected",
9057                   Get_Pragma_Arg (Arg1));
9058             end if;
9059          end Favor_Top_Level;
9060
9061          ---------------
9062          -- Fast_Math --
9063          ---------------
9064
9065          --  pragma Fast_Math;
9066
9067          when Pragma_Fast_Math =>
9068             GNAT_Pragma;
9069             Check_No_Identifiers;
9070             Check_Valid_Configuration_Pragma;
9071             Fast_Math := True;
9072
9073          ---------------------------
9074          -- Finalize_Storage_Only --
9075          ---------------------------
9076
9077          --  pragma Finalize_Storage_Only (first_subtype_LOCAL_NAME);
9078
9079          when Pragma_Finalize_Storage_Only => Finalize_Storage : declare
9080             Assoc   : constant Node_Id := Arg1;
9081             Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
9082             Typ     : Entity_Id;
9083
9084          begin
9085             GNAT_Pragma;
9086             Check_No_Identifiers;
9087             Check_Arg_Count (1);
9088             Check_Arg_Is_Local_Name (Arg1);
9089
9090             Find_Type (Type_Id);
9091             Typ := Entity (Type_Id);
9092
9093             if Typ = Any_Type
9094               or else Rep_Item_Too_Early (Typ, N)
9095             then
9096                return;
9097             else
9098                Typ := Underlying_Type (Typ);
9099             end if;
9100
9101             if not Is_Controlled (Typ) then
9102                Error_Pragma ("pragma% must specify controlled type");
9103             end if;
9104
9105             Check_First_Subtype (Arg1);
9106
9107             if Finalize_Storage_Only (Typ) then
9108                Error_Pragma ("duplicate pragma%, only one allowed");
9109
9110             elsif not Rep_Item_Too_Late (Typ, N) then
9111                Set_Finalize_Storage_Only (Base_Type (Typ), True);
9112             end if;
9113          end Finalize_Storage;
9114
9115          --------------------------
9116          -- Float_Representation --
9117          --------------------------
9118
9119          --  pragma Float_Representation (FLOAT_REP[, float_type_LOCAL_NAME]);
9120
9121          --  FLOAT_REP ::= VAX_Float | IEEE_Float
9122
9123          when Pragma_Float_Representation => Float_Representation : declare
9124             Argx : Node_Id;
9125             Digs : Nat;
9126             Ent  : Entity_Id;
9127
9128          begin
9129             GNAT_Pragma;
9130
9131             if Arg_Count = 1 then
9132                Check_Valid_Configuration_Pragma;
9133             else
9134                Check_Arg_Count (2);
9135                Check_Optional_Identifier (Arg2, Name_Entity);
9136                Check_Arg_Is_Local_Name (Arg2);
9137             end if;
9138
9139             Check_No_Identifier (Arg1);
9140             Check_Arg_Is_One_Of (Arg1, Name_VAX_Float, Name_IEEE_Float);
9141
9142             if not OpenVMS_On_Target then
9143                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9144                   Error_Pragma
9145                     ("?pragma% ignored (applies only to Open'V'M'S)");
9146                end if;
9147
9148                return;
9149             end if;
9150
9151             --  One argument case
9152
9153             if Arg_Count = 1 then
9154                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9155                   if Opt.Float_Format = 'I' then
9156                      Error_Pragma ("'I'E'E'E format previously specified");
9157                   end if;
9158
9159                   Opt.Float_Format := 'V';
9160
9161                else
9162                   if Opt.Float_Format = 'V' then
9163                      Error_Pragma ("'V'A'X format previously specified");
9164                   end if;
9165
9166                   Opt.Float_Format := 'I';
9167                end if;
9168
9169                Set_Standard_Fpt_Formats;
9170
9171             --  Two argument case
9172
9173             else
9174                Argx := Get_Pragma_Arg (Arg2);
9175
9176                if not Is_Entity_Name (Argx)
9177                  or else not Is_Floating_Point_Type (Entity (Argx))
9178                then
9179                   Error_Pragma_Arg
9180                     ("second argument of% pragma must be floating-point type",
9181                      Arg2);
9182                end if;
9183
9184                Ent  := Entity (Argx);
9185                Digs := UI_To_Int (Digits_Value (Ent));
9186
9187                --  Two arguments, VAX_Float case
9188
9189                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9190                   case Digs is
9191                      when  6 => Set_F_Float (Ent);
9192                      when  9 => Set_D_Float (Ent);
9193                      when 15 => Set_G_Float (Ent);
9194
9195                      when others =>
9196                         Error_Pragma_Arg
9197                           ("wrong digits value, must be 6,9 or 15", Arg2);
9198                   end case;
9199
9200                --  Two arguments, IEEE_Float case
9201
9202                else
9203                   case Digs is
9204                      when  6 => Set_IEEE_Short (Ent);
9205                      when 15 => Set_IEEE_Long  (Ent);
9206
9207                      when others =>
9208                         Error_Pragma_Arg
9209                           ("wrong digits value, must be 6 or 15", Arg2);
9210                   end case;
9211                end if;
9212             end if;
9213          end Float_Representation;
9214
9215          -----------
9216          -- Ident --
9217          -----------
9218
9219          --  pragma Ident (static_string_EXPRESSION)
9220
9221          --  Note: pragma Comment shares this processing. Pragma Comment is
9222          --  identical to Ident, except that the restriction of the argument to
9223          --  31 characters and the placement restrictions are not enforced for
9224          --  pragma Comment.
9225
9226          when Pragma_Ident | Pragma_Comment => Ident : declare
9227             Str : Node_Id;
9228
9229          begin
9230             GNAT_Pragma;
9231             Check_Arg_Count (1);
9232             Check_No_Identifiers;
9233             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
9234             Store_Note (N);
9235
9236             --  For pragma Ident, preserve DEC compatibility by requiring the
9237             --  pragma to appear in a declarative part or package spec.
9238
9239             if Prag_Id = Pragma_Ident then
9240                Check_Is_In_Decl_Part_Or_Package_Spec;
9241             end if;
9242
9243             Str := Expr_Value_S (Get_Pragma_Arg (Arg1));
9244
9245             declare
9246                CS : Node_Id;
9247                GP : Node_Id;
9248
9249             begin
9250                GP := Parent (Parent (N));
9251
9252                if Nkind_In (GP, N_Package_Declaration,
9253                                 N_Generic_Package_Declaration)
9254                then
9255                   GP := Parent (GP);
9256                end if;
9257
9258                --  If we have a compilation unit, then record the ident value,
9259                --  checking for improper duplication.
9260
9261                if Nkind (GP) = N_Compilation_Unit then
9262                   CS := Ident_String (Current_Sem_Unit);
9263
9264                   if Present (CS) then
9265
9266                      --  For Ident, we do not permit multiple instances
9267
9268                      if Prag_Id = Pragma_Ident then
9269                         Error_Pragma ("duplicate% pragma not permitted");
9270
9271                      --  For Comment, we concatenate the string, unless we want
9272                      --  to preserve the tree structure for ASIS.
9273
9274                      elsif not ASIS_Mode then
9275                         Start_String (Strval (CS));
9276                         Store_String_Char (' ');
9277                         Store_String_Chars (Strval (Str));
9278                         Set_Strval (CS, End_String);
9279                      end if;
9280
9281                   else
9282                      --  In VMS, the effect of IDENT is achieved by passing
9283                      --  --identification=name as a --for-linker switch.
9284
9285                      if OpenVMS_On_Target then
9286                         Start_String;
9287                         Store_String_Chars
9288                           ("--for-linker=--identification=");
9289                         String_To_Name_Buffer (Strval (Str));
9290                         Store_String_Chars (Name_Buffer (1 .. Name_Len));
9291
9292                         --  Only the last processed IDENT is saved. The main
9293                         --  purpose is so an IDENT associated with a main
9294                         --  procedure will be used in preference to an IDENT
9295                         --  associated with a with'd package.
9296
9297                         Replace_Linker_Option_String
9298                           (End_String, "--for-linker=--identification=");
9299                      end if;
9300
9301                      Set_Ident_String (Current_Sem_Unit, Str);
9302                   end if;
9303
9304                --  For subunits, we just ignore the Ident, since in GNAT these
9305                --  are not separate object files, and hence not separate units
9306                --  in the unit table.
9307
9308                elsif Nkind (GP) = N_Subunit then
9309                   null;
9310
9311                --  Otherwise we have a misplaced pragma Ident, but we ignore
9312                --  this if we are in an instantiation, since it comes from
9313                --  a generic, and has no relevance to the instantiation.
9314
9315                elsif Prag_Id = Pragma_Ident then
9316                   if Instantiation_Location (Loc) = No_Location then
9317                      Error_Pragma ("pragma% only allowed at outer level");
9318                   end if;
9319                end if;
9320             end;
9321          end Ident;
9322
9323          ----------------------------
9324          -- Implementation_Defined --
9325          ----------------------------
9326
9327          --  pragma Implementation_Defined (local_NAME);
9328
9329          --  Marks previously declared entity as implementation defined. For
9330          --  an overloaded entity, applies to the most recent homonym.
9331
9332          --  pragma Implementation_Defined;
9333
9334          --  The form with no arguments appears anywhere within a scope, most
9335          --  typically a package spec, and indicates that all entities that are
9336          --  defined within the package spec are Implementation_Defined.
9337
9338          when Pragma_Implementation_Defined => Implementation_Defined : declare
9339             Ent : Entity_Id;
9340
9341          begin
9342             Check_No_Identifiers;
9343
9344             --  Form with no arguments
9345
9346             if Arg_Count = 0 then
9347                Set_Is_Implementation_Defined (Current_Scope);
9348
9349             --  Form with one argument
9350
9351             else
9352                Check_Arg_Count (1);
9353                Check_Arg_Is_Local_Name (Arg1);
9354                Ent := Entity (Get_Pragma_Arg (Arg1));
9355                Set_Is_Implementation_Defined (Ent);
9356             end if;
9357          end Implementation_Defined;
9358
9359          -----------------
9360          -- Implemented --
9361          -----------------
9362
9363          --  pragma Implemented (procedure_LOCAL_NAME, implementation_kind);
9364          --  implementation_kind ::=
9365          --    By_Entry | By_Protected_Procedure | By_Any | Optional
9366
9367          --  "By_Any" and "Optional" are treated as synonyms in order to
9368          --  support Ada 2012 aspect Synchronization.
9369
9370          when Pragma_Implemented => Implemented : declare
9371             Proc_Id : Entity_Id;
9372             Typ     : Entity_Id;
9373
9374          begin
9375             Ada_2012_Pragma;
9376             Check_Arg_Count (2);
9377             Check_No_Identifiers;
9378             Check_Arg_Is_Identifier (Arg1);
9379             Check_Arg_Is_Local_Name (Arg1);
9380             Check_Arg_Is_One_Of (Arg2,
9381               Name_By_Any,
9382               Name_By_Entry,
9383               Name_By_Protected_Procedure,
9384               Name_Optional);
9385
9386             --  Extract the name of the local procedure
9387
9388             Proc_Id := Entity (Get_Pragma_Arg (Arg1));
9389
9390             --  Ada 2012 (AI05-0030): The procedure_LOCAL_NAME must denote a
9391             --  primitive procedure of a synchronized tagged type.
9392
9393             if Ekind (Proc_Id) = E_Procedure
9394               and then Is_Primitive (Proc_Id)
9395               and then Present (First_Formal (Proc_Id))
9396             then
9397                Typ := Etype (First_Formal (Proc_Id));
9398
9399                if Is_Tagged_Type (Typ)
9400                  and then
9401
9402                   --  Check for a protected, a synchronized or a task interface
9403
9404                    ((Is_Interface (Typ)
9405                        and then Is_Synchronized_Interface (Typ))
9406
9407                   --  Check for a protected type or a task type that implements
9408                   --  an interface.
9409
9410                    or else
9411                     (Is_Concurrent_Record_Type (Typ)
9412                        and then Present (Interfaces (Typ)))
9413
9414                   --  Check for a private record extension with keyword
9415                   --  "synchronized".
9416
9417                    or else
9418                     (Ekind_In (Typ, E_Record_Type_With_Private,
9419                                     E_Record_Subtype_With_Private)
9420                        and then Synchronized_Present (Parent (Typ))))
9421                then
9422                   null;
9423                else
9424                   Error_Pragma_Arg
9425                     ("controlling formal must be of synchronized " &
9426                      "tagged type", Arg1);
9427                   return;
9428                end if;
9429
9430             --  Procedures declared inside a protected type must be accepted
9431
9432             elsif Ekind (Proc_Id) = E_Procedure
9433               and then Is_Protected_Type (Scope (Proc_Id))
9434             then
9435                null;
9436
9437             --  The first argument is not a primitive procedure
9438
9439             else
9440                Error_Pragma_Arg
9441                  ("pragma % must be applied to a primitive procedure", Arg1);
9442                return;
9443             end if;
9444
9445             --  Ada 2012 (AI05-0030): Cannot apply the implementation_kind
9446             --  By_Protected_Procedure to the primitive procedure of a task
9447             --  interface.
9448
9449             if Chars (Arg2) = Name_By_Protected_Procedure
9450               and then Is_Interface (Typ)
9451               and then Is_Task_Interface (Typ)
9452             then
9453                Error_Pragma_Arg
9454                  ("implementation kind By_Protected_Procedure cannot be " &
9455                   "applied to a task interface primitive", Arg2);
9456                return;
9457             end if;
9458
9459             Record_Rep_Item (Proc_Id, N);
9460          end Implemented;
9461
9462          ----------------------
9463          -- Implicit_Packing --
9464          ----------------------
9465
9466          --  pragma Implicit_Packing;
9467
9468          when Pragma_Implicit_Packing =>
9469             GNAT_Pragma;
9470             Check_Arg_Count (0);
9471             Implicit_Packing := True;
9472
9473          ------------
9474          -- Import --
9475          ------------
9476
9477          --  pragma Import (
9478          --       [Convention    =>] convention_IDENTIFIER,
9479          --       [Entity        =>] local_NAME
9480          --    [, [External_Name =>] static_string_EXPRESSION ]
9481          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
9482
9483          when Pragma_Import =>
9484             Check_Ada_83_Warning;
9485             Check_Arg_Order
9486               ((Name_Convention,
9487                 Name_Entity,
9488                 Name_External_Name,
9489                 Name_Link_Name));
9490             Check_At_Least_N_Arguments (2);
9491             Check_At_Most_N_Arguments  (4);
9492             Process_Import_Or_Interface;
9493
9494          ----------------------
9495          -- Import_Exception --
9496          ----------------------
9497
9498          --  pragma Import_Exception (
9499          --        [Internal         =>] LOCAL_NAME
9500          --     [, [External         =>] EXTERNAL_SYMBOL]
9501          --     [, [Form     =>] Ada | VMS]
9502          --     [, [Code     =>] static_integer_EXPRESSION]);
9503
9504          when Pragma_Import_Exception => Import_Exception : declare
9505             Args  : Args_List (1 .. 4);
9506             Names : constant Name_List (1 .. 4) := (
9507                       Name_Internal,
9508                       Name_External,
9509                       Name_Form,
9510                       Name_Code);
9511
9512             Internal : Node_Id renames Args (1);
9513             External : Node_Id renames Args (2);
9514             Form     : Node_Id renames Args (3);
9515             Code     : Node_Id renames Args (4);
9516
9517          begin
9518             GNAT_Pragma;
9519             Gather_Associations (Names, Args);
9520
9521             if Present (External) and then Present (Code) then
9522                Error_Pragma
9523                  ("cannot give both External and Code options for pragma%");
9524             end if;
9525
9526             Process_Extended_Import_Export_Exception_Pragma (
9527               Arg_Internal => Internal,
9528               Arg_External => External,
9529               Arg_Form     => Form,
9530               Arg_Code     => Code);
9531
9532             if not Is_VMS_Exception (Entity (Internal)) then
9533                Set_Imported (Entity (Internal));
9534             end if;
9535          end Import_Exception;
9536
9537          ---------------------
9538          -- Import_Function --
9539          ---------------------
9540
9541          --  pragma Import_Function (
9542          --        [Internal                 =>] LOCAL_NAME,
9543          --     [, [External                 =>] EXTERNAL_SYMBOL]
9544          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9545          --     [, [Result_Type              =>] SUBTYPE_MARK]
9546          --     [, [Mechanism                =>] MECHANISM]
9547          --     [, [Result_Mechanism         =>] MECHANISM_NAME]
9548          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9549
9550          --  EXTERNAL_SYMBOL ::=
9551          --    IDENTIFIER
9552          --  | static_string_EXPRESSION
9553
9554          --  PARAMETER_TYPES ::=
9555          --    null
9556          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9557
9558          --  TYPE_DESIGNATOR ::=
9559          --    subtype_NAME
9560          --  | subtype_Name ' Access
9561
9562          --  MECHANISM ::=
9563          --    MECHANISM_NAME
9564          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9565
9566          --  MECHANISM_ASSOCIATION ::=
9567          --    [formal_parameter_NAME =>] MECHANISM_NAME
9568
9569          --  MECHANISM_NAME ::=
9570          --    Value
9571          --  | Reference
9572          --  | Descriptor [([Class =>] CLASS_NAME)]
9573
9574          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9575
9576          when Pragma_Import_Function => Import_Function : declare
9577             Args  : Args_List (1 .. 7);
9578             Names : constant Name_List (1 .. 7) := (
9579                       Name_Internal,
9580                       Name_External,
9581                       Name_Parameter_Types,
9582                       Name_Result_Type,
9583                       Name_Mechanism,
9584                       Name_Result_Mechanism,
9585                       Name_First_Optional_Parameter);
9586
9587             Internal                 : Node_Id renames Args (1);
9588             External                 : Node_Id renames Args (2);
9589             Parameter_Types          : Node_Id renames Args (3);
9590             Result_Type              : Node_Id renames Args (4);
9591             Mechanism                : Node_Id renames Args (5);
9592             Result_Mechanism         : Node_Id renames Args (6);
9593             First_Optional_Parameter : Node_Id renames Args (7);
9594
9595          begin
9596             GNAT_Pragma;
9597             Gather_Associations (Names, Args);
9598             Process_Extended_Import_Export_Subprogram_Pragma (
9599               Arg_Internal                 => Internal,
9600               Arg_External                 => External,
9601               Arg_Parameter_Types          => Parameter_Types,
9602               Arg_Result_Type              => Result_Type,
9603               Arg_Mechanism                => Mechanism,
9604               Arg_Result_Mechanism         => Result_Mechanism,
9605               Arg_First_Optional_Parameter => First_Optional_Parameter);
9606          end Import_Function;
9607
9608          -------------------
9609          -- Import_Object --
9610          -------------------
9611
9612          --  pragma Import_Object (
9613          --        [Internal =>] LOCAL_NAME
9614          --     [, [External =>] EXTERNAL_SYMBOL]
9615          --     [, [Size     =>] EXTERNAL_SYMBOL]);
9616
9617          --  EXTERNAL_SYMBOL ::=
9618          --    IDENTIFIER
9619          --  | static_string_EXPRESSION
9620
9621          when Pragma_Import_Object => Import_Object : declare
9622             Args  : Args_List (1 .. 3);
9623             Names : constant Name_List (1 .. 3) := (
9624                       Name_Internal,
9625                       Name_External,
9626                       Name_Size);
9627
9628             Internal : Node_Id renames Args (1);
9629             External : Node_Id renames Args (2);
9630             Size     : Node_Id renames Args (3);
9631
9632          begin
9633             GNAT_Pragma;
9634             Gather_Associations (Names, Args);
9635             Process_Extended_Import_Export_Object_Pragma (
9636               Arg_Internal => Internal,
9637               Arg_External => External,
9638               Arg_Size     => Size);
9639          end Import_Object;
9640
9641          ----------------------
9642          -- Import_Procedure --
9643          ----------------------
9644
9645          --  pragma Import_Procedure (
9646          --        [Internal                 =>] LOCAL_NAME
9647          --     [, [External                 =>] EXTERNAL_SYMBOL]
9648          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9649          --     [, [Mechanism                =>] MECHANISM]
9650          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9651
9652          --  EXTERNAL_SYMBOL ::=
9653          --    IDENTIFIER
9654          --  | static_string_EXPRESSION
9655
9656          --  PARAMETER_TYPES ::=
9657          --    null
9658          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9659
9660          --  TYPE_DESIGNATOR ::=
9661          --    subtype_NAME
9662          --  | subtype_Name ' Access
9663
9664          --  MECHANISM ::=
9665          --    MECHANISM_NAME
9666          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9667
9668          --  MECHANISM_ASSOCIATION ::=
9669          --    [formal_parameter_NAME =>] MECHANISM_NAME
9670
9671          --  MECHANISM_NAME ::=
9672          --    Value
9673          --  | Reference
9674          --  | Descriptor [([Class =>] CLASS_NAME)]
9675
9676          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9677
9678          when Pragma_Import_Procedure => Import_Procedure : declare
9679             Args  : Args_List (1 .. 5);
9680             Names : constant Name_List (1 .. 5) := (
9681                       Name_Internal,
9682                       Name_External,
9683                       Name_Parameter_Types,
9684                       Name_Mechanism,
9685                       Name_First_Optional_Parameter);
9686
9687             Internal                 : Node_Id renames Args (1);
9688             External                 : Node_Id renames Args (2);
9689             Parameter_Types          : Node_Id renames Args (3);
9690             Mechanism                : Node_Id renames Args (4);
9691             First_Optional_Parameter : Node_Id renames Args (5);
9692
9693          begin
9694             GNAT_Pragma;
9695             Gather_Associations (Names, Args);
9696             Process_Extended_Import_Export_Subprogram_Pragma (
9697               Arg_Internal                 => Internal,
9698               Arg_External                 => External,
9699               Arg_Parameter_Types          => Parameter_Types,
9700               Arg_Mechanism                => Mechanism,
9701               Arg_First_Optional_Parameter => First_Optional_Parameter);
9702          end Import_Procedure;
9703
9704          -----------------------------
9705          -- Import_Valued_Procedure --
9706          -----------------------------
9707
9708          --  pragma Import_Valued_Procedure (
9709          --        [Internal                 =>] LOCAL_NAME
9710          --     [, [External                 =>] EXTERNAL_SYMBOL]
9711          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9712          --     [, [Mechanism                =>] MECHANISM]
9713          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9714
9715          --  EXTERNAL_SYMBOL ::=
9716          --    IDENTIFIER
9717          --  | static_string_EXPRESSION
9718
9719          --  PARAMETER_TYPES ::=
9720          --    null
9721          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9722
9723          --  TYPE_DESIGNATOR ::=
9724          --    subtype_NAME
9725          --  | subtype_Name ' Access
9726
9727          --  MECHANISM ::=
9728          --    MECHANISM_NAME
9729          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9730
9731          --  MECHANISM_ASSOCIATION ::=
9732          --    [formal_parameter_NAME =>] MECHANISM_NAME
9733
9734          --  MECHANISM_NAME ::=
9735          --    Value
9736          --  | Reference
9737          --  | Descriptor [([Class =>] CLASS_NAME)]
9738
9739          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9740
9741          when Pragma_Import_Valued_Procedure =>
9742          Import_Valued_Procedure : declare
9743             Args  : Args_List (1 .. 5);
9744             Names : constant Name_List (1 .. 5) := (
9745                       Name_Internal,
9746                       Name_External,
9747                       Name_Parameter_Types,
9748                       Name_Mechanism,
9749                       Name_First_Optional_Parameter);
9750
9751             Internal                 : Node_Id renames Args (1);
9752             External                 : Node_Id renames Args (2);
9753             Parameter_Types          : Node_Id renames Args (3);
9754             Mechanism                : Node_Id renames Args (4);
9755             First_Optional_Parameter : Node_Id renames Args (5);
9756
9757          begin
9758             GNAT_Pragma;
9759             Gather_Associations (Names, Args);
9760             Process_Extended_Import_Export_Subprogram_Pragma (
9761               Arg_Internal                 => Internal,
9762               Arg_External                 => External,
9763               Arg_Parameter_Types          => Parameter_Types,
9764               Arg_Mechanism                => Mechanism,
9765               Arg_First_Optional_Parameter => First_Optional_Parameter);
9766          end Import_Valued_Procedure;
9767
9768          -----------------
9769          -- Independent --
9770          -----------------
9771
9772          --  pragma Independent (LOCAL_NAME);
9773
9774          when Pragma_Independent => Independent : declare
9775             E_Id : Node_Id;
9776             E    : Entity_Id;
9777             D    : Node_Id;
9778             K    : Node_Kind;
9779
9780          begin
9781             Check_Ada_83_Warning;
9782             Ada_2012_Pragma;
9783             Check_No_Identifiers;
9784             Check_Arg_Count (1);
9785             Check_Arg_Is_Local_Name (Arg1);
9786             E_Id := Get_Pragma_Arg (Arg1);
9787
9788             if Etype (E_Id) = Any_Type then
9789                return;
9790             end if;
9791
9792             E := Entity (E_Id);
9793             D := Declaration_Node (E);
9794             K := Nkind (D);
9795
9796             --  Check duplicate before we chain ourselves!
9797
9798             Check_Duplicate_Pragma (E);
9799
9800             --  Check appropriate entity
9801
9802             if Is_Type (E) then
9803                if Rep_Item_Too_Early (E, N)
9804                     or else
9805                   Rep_Item_Too_Late (E, N)
9806                then
9807                   return;
9808                else
9809                   Check_First_Subtype (Arg1);
9810                end if;
9811
9812             elsif K = N_Object_Declaration
9813               or else (K = N_Component_Declaration
9814                        and then Original_Record_Component (E) = E)
9815             then
9816                if Rep_Item_Too_Late (E, N) then
9817                   return;
9818                end if;
9819
9820             else
9821                Error_Pragma_Arg
9822                  ("inappropriate entity for pragma%", Arg1);
9823             end if;
9824
9825             Independence_Checks.Append ((N, E));
9826          end Independent;
9827
9828          ----------------------------
9829          -- Independent_Components --
9830          ----------------------------
9831
9832          --  pragma Atomic_Components (array_LOCAL_NAME);
9833
9834          --  This processing is shared by Volatile_Components
9835
9836          when Pragma_Independent_Components => Independent_Components : declare
9837             E_Id : Node_Id;
9838             E    : Entity_Id;
9839             D    : Node_Id;
9840             K    : Node_Kind;
9841
9842          begin
9843             Check_Ada_83_Warning;
9844             Ada_2012_Pragma;
9845             Check_No_Identifiers;
9846             Check_Arg_Count (1);
9847             Check_Arg_Is_Local_Name (Arg1);
9848             E_Id := Get_Pragma_Arg (Arg1);
9849
9850             if Etype (E_Id) = Any_Type then
9851                return;
9852             end if;
9853
9854             E := Entity (E_Id);
9855
9856             --  Check duplicate before we chain ourselves!
9857
9858             Check_Duplicate_Pragma (E);
9859
9860             --  Check appropriate entity
9861
9862             if Rep_Item_Too_Early (E, N)
9863                  or else
9864                Rep_Item_Too_Late (E, N)
9865             then
9866                return;
9867             end if;
9868
9869             D := Declaration_Node (E);
9870             K := Nkind (D);
9871
9872             if (K = N_Full_Type_Declaration
9873                  and then (Is_Array_Type (E) or else Is_Record_Type (E)))
9874               or else
9875                 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
9876                    and then Nkind (D) = N_Object_Declaration
9877                    and then Nkind (Object_Definition (D)) =
9878                                        N_Constrained_Array_Definition)
9879             then
9880                Independence_Checks.Append ((N, E));
9881
9882             else
9883                Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
9884             end if;
9885          end Independent_Components;
9886
9887          ------------------------
9888          -- Initialize_Scalars --
9889          ------------------------
9890
9891          --  pragma Initialize_Scalars;
9892
9893          when Pragma_Initialize_Scalars =>
9894             GNAT_Pragma;
9895             Check_Arg_Count (0);
9896             Check_Valid_Configuration_Pragma;
9897             Check_Restriction (No_Initialize_Scalars, N);
9898
9899             --  Initialize_Scalars creates false positives in CodePeer, and
9900             --  incorrect negative results in Alfa mode, so ignore this pragma
9901             --  in these modes.
9902
9903             if not Restriction_Active (No_Initialize_Scalars)
9904               and then not (CodePeer_Mode or Alfa_Mode)
9905             then
9906                Init_Or_Norm_Scalars := True;
9907                Initialize_Scalars := True;
9908             end if;
9909
9910          ------------
9911          -- Inline --
9912          ------------
9913
9914          --  pragma Inline ( NAME {, NAME} );
9915
9916          when Pragma_Inline =>
9917
9918             --  Pragma is active if inlining option is active
9919
9920             Process_Inline (Inline_Active);
9921
9922          -------------------
9923          -- Inline_Always --
9924          -------------------
9925
9926          --  pragma Inline_Always ( NAME {, NAME} );
9927
9928          when Pragma_Inline_Always =>
9929             GNAT_Pragma;
9930
9931             --  Pragma always active unless in CodePeer or Alfa mode, since
9932             --  this causes walk order issues.
9933
9934             if not (CodePeer_Mode or Alfa_Mode) then
9935                Process_Inline (True);
9936             end if;
9937
9938          --------------------
9939          -- Inline_Generic --
9940          --------------------
9941
9942          --  pragma Inline_Generic (NAME {, NAME});
9943
9944          when Pragma_Inline_Generic =>
9945             GNAT_Pragma;
9946             Process_Generic_List;
9947
9948          ----------------------
9949          -- Inspection_Point --
9950          ----------------------
9951
9952          --  pragma Inspection_Point [(object_NAME {, object_NAME})];
9953
9954          when Pragma_Inspection_Point => Inspection_Point : declare
9955             Arg : Node_Id;
9956             Exp : Node_Id;
9957
9958          begin
9959             if Arg_Count > 0 then
9960                Arg := Arg1;
9961                loop
9962                   Exp := Get_Pragma_Arg (Arg);
9963                   Analyze (Exp);
9964
9965                   if not Is_Entity_Name (Exp)
9966                     or else not Is_Object (Entity (Exp))
9967                   then
9968                      Error_Pragma_Arg ("object name required", Arg);
9969                   end if;
9970
9971                   Next (Arg);
9972                   exit when No (Arg);
9973                end loop;
9974             end if;
9975          end Inspection_Point;
9976
9977          ---------------
9978          -- Interface --
9979          ---------------
9980
9981          --  pragma Interface (
9982          --    [   Convention    =>] convention_IDENTIFIER,
9983          --    [   Entity        =>] local_NAME
9984          --    [, [External_Name =>] static_string_EXPRESSION ]
9985          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
9986
9987          when Pragma_Interface =>
9988             GNAT_Pragma;
9989             Check_Arg_Order
9990               ((Name_Convention,
9991                 Name_Entity,
9992                 Name_External_Name,
9993                 Name_Link_Name));
9994             Check_At_Least_N_Arguments (2);
9995             Check_At_Most_N_Arguments  (4);
9996             Process_Import_Or_Interface;
9997
9998             --  In Ada 2005, the permission to use Interface (a reserved word)
9999             --  as a pragma name is considered an obsolescent feature.
10000
10001             if Ada_Version >= Ada_2005 then
10002                Check_Restriction
10003                  (No_Obsolescent_Features, Pragma_Identifier (N));
10004             end if;
10005
10006          --------------------
10007          -- Interface_Name --
10008          --------------------
10009
10010          --  pragma Interface_Name (
10011          --    [  Entity        =>] local_NAME
10012          --    [,[External_Name =>] static_string_EXPRESSION ]
10013          --    [,[Link_Name     =>] static_string_EXPRESSION ]);
10014
10015          when Pragma_Interface_Name => Interface_Name : declare
10016             Id     : Node_Id;
10017             Def_Id : Entity_Id;
10018             Hom_Id : Entity_Id;
10019             Found  : Boolean;
10020
10021          begin
10022             GNAT_Pragma;
10023             Check_Arg_Order
10024               ((Name_Entity, Name_External_Name, Name_Link_Name));
10025             Check_At_Least_N_Arguments (2);
10026             Check_At_Most_N_Arguments  (3);
10027             Id := Get_Pragma_Arg (Arg1);
10028             Analyze (Id);
10029
10030             if not Is_Entity_Name (Id) then
10031                Error_Pragma_Arg
10032                  ("first argument for pragma% must be entity name", Arg1);
10033             elsif Etype (Id) = Any_Type then
10034                return;
10035             else
10036                Def_Id := Entity (Id);
10037             end if;
10038
10039             --  Special DEC-compatible processing for the object case, forces
10040             --  object to be imported.
10041
10042             if Ekind (Def_Id) = E_Variable then
10043                Kill_Size_Check_Code (Def_Id);
10044                Note_Possible_Modification (Id, Sure => False);
10045
10046                --  Initialization is not allowed for imported variable
10047
10048                if Present (Expression (Parent (Def_Id)))
10049                  and then Comes_From_Source (Expression (Parent (Def_Id)))
10050                then
10051                   Error_Msg_Sloc := Sloc (Def_Id);
10052                   Error_Pragma_Arg
10053                     ("no initialization allowed for declaration of& #",
10054                      Arg2);
10055
10056                else
10057                   --  For compatibility, support VADS usage of providing both
10058                   --  pragmas Interface and Interface_Name to obtain the effect
10059                   --  of a single Import pragma.
10060
10061                   if Is_Imported (Def_Id)
10062                     and then Present (First_Rep_Item (Def_Id))
10063                     and then Nkind (First_Rep_Item (Def_Id)) = N_Pragma
10064                     and then
10065                       Pragma_Name (First_Rep_Item (Def_Id)) = Name_Interface
10066                   then
10067                      null;
10068                   else
10069                      Set_Imported (Def_Id);
10070                   end if;
10071
10072                   Set_Is_Public (Def_Id);
10073                   Process_Interface_Name (Def_Id, Arg2, Arg3);
10074                end if;
10075
10076             --  Otherwise must be subprogram
10077
10078             elsif not Is_Subprogram (Def_Id) then
10079                Error_Pragma_Arg
10080                  ("argument of pragma% is not subprogram", Arg1);
10081
10082             else
10083                Check_At_Most_N_Arguments (3);
10084                Hom_Id := Def_Id;
10085                Found := False;
10086
10087                --  Loop through homonyms
10088
10089                loop
10090                   Def_Id := Get_Base_Subprogram (Hom_Id);
10091
10092                   if Is_Imported (Def_Id) then
10093                      Process_Interface_Name (Def_Id, Arg2, Arg3);
10094                      Found := True;
10095                   end if;
10096
10097                   exit when From_Aspect_Specification (N);
10098                   Hom_Id := Homonym (Hom_Id);
10099
10100                   exit when No (Hom_Id)
10101                     or else Scope (Hom_Id) /= Current_Scope;
10102                end loop;
10103
10104                if not Found then
10105                   Error_Pragma_Arg
10106                     ("argument of pragma% is not imported subprogram",
10107                      Arg1);
10108                end if;
10109             end if;
10110          end Interface_Name;
10111
10112          -----------------------
10113          -- Interrupt_Handler --
10114          -----------------------
10115
10116          --  pragma Interrupt_Handler (handler_NAME);
10117
10118          when Pragma_Interrupt_Handler =>
10119             Check_Ada_83_Warning;
10120             Check_Arg_Count (1);
10121             Check_No_Identifiers;
10122
10123             if No_Run_Time_Mode then
10124                Error_Msg_CRT ("Interrupt_Handler pragma", N);
10125             else
10126                Check_Interrupt_Or_Attach_Handler;
10127                Process_Interrupt_Or_Attach_Handler;
10128             end if;
10129
10130          ------------------------
10131          -- Interrupt_Priority --
10132          ------------------------
10133
10134          --  pragma Interrupt_Priority [(EXPRESSION)];
10135
10136          when Pragma_Interrupt_Priority => Interrupt_Priority : declare
10137             P   : constant Node_Id := Parent (N);
10138             Arg : Node_Id;
10139
10140          begin
10141             Check_Ada_83_Warning;
10142
10143             if Arg_Count /= 0 then
10144                Arg := Get_Pragma_Arg (Arg1);
10145                Check_Arg_Count (1);
10146                Check_No_Identifiers;
10147
10148                --  The expression must be analyzed in the special manner
10149                --  described in "Handling of Default and Per-Object
10150                --  Expressions" in sem.ads.
10151
10152                Preanalyze_Spec_Expression (Arg, RTE (RE_Interrupt_Priority));
10153             end if;
10154
10155             if not Nkind_In (P, N_Task_Definition, N_Protected_Definition) then
10156                Pragma_Misplaced;
10157                return;
10158
10159             elsif Has_Pragma_Priority (P) then
10160                Error_Pragma ("duplicate pragma% not allowed");
10161
10162             else
10163                Set_Has_Pragma_Priority (P, True);
10164                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
10165             end if;
10166          end Interrupt_Priority;
10167
10168          ---------------------
10169          -- Interrupt_State --
10170          ---------------------
10171
10172          --  pragma Interrupt_State (
10173          --    [Name  =>] INTERRUPT_ID,
10174          --    [State =>] INTERRUPT_STATE);
10175
10176          --  INTERRUPT_ID => IDENTIFIER | static_integer_EXPRESSION
10177          --  INTERRUPT_STATE => System | Runtime | User
10178
10179          --  Note: if the interrupt id is given as an identifier, then it must
10180          --  be one of the identifiers in Ada.Interrupts.Names. Otherwise it is
10181          --  given as a static integer expression which must be in the range of
10182          --  Ada.Interrupts.Interrupt_ID.
10183
10184          when Pragma_Interrupt_State => Interrupt_State : declare
10185
10186             Int_Id : constant Entity_Id := RTE (RE_Interrupt_ID);
10187             --  This is the entity Ada.Interrupts.Interrupt_ID;
10188
10189             State_Type : Character;
10190             --  Set to 's'/'r'/'u' for System/Runtime/User
10191
10192             IST_Num : Pos;
10193             --  Index to entry in Interrupt_States table
10194
10195             Int_Val : Uint;
10196             --  Value of interrupt
10197
10198             Arg1X : constant Node_Id := Get_Pragma_Arg (Arg1);
10199             --  The first argument to the pragma
10200
10201             Int_Ent : Entity_Id;
10202             --  Interrupt entity in Ada.Interrupts.Names
10203
10204          begin
10205             GNAT_Pragma;
10206             Check_Arg_Order ((Name_Name, Name_State));
10207             Check_Arg_Count (2);
10208
10209             Check_Optional_Identifier (Arg1, Name_Name);
10210             Check_Optional_Identifier (Arg2, Name_State);
10211             Check_Arg_Is_Identifier (Arg2);
10212
10213             --  First argument is identifier
10214
10215             if Nkind (Arg1X) = N_Identifier then
10216
10217                --  Search list of names in Ada.Interrupts.Names
10218
10219                Int_Ent := First_Entity (RTE (RE_Names));
10220                loop
10221                   if No (Int_Ent) then
10222                      Error_Pragma_Arg ("invalid interrupt name", Arg1);
10223
10224                   elsif Chars (Int_Ent) = Chars (Arg1X) then
10225                      Int_Val := Expr_Value (Constant_Value (Int_Ent));
10226                      exit;
10227                   end if;
10228
10229                   Next_Entity (Int_Ent);
10230                end loop;
10231
10232             --  First argument is not an identifier, so it must be a static
10233             --  expression of type Ada.Interrupts.Interrupt_ID.
10234
10235             else
10236                Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
10237                Int_Val := Expr_Value (Arg1X);
10238
10239                if Int_Val < Expr_Value (Type_Low_Bound (Int_Id))
10240                     or else
10241                   Int_Val > Expr_Value (Type_High_Bound (Int_Id))
10242                then
10243                   Error_Pragma_Arg
10244                     ("value not in range of type " &
10245                      """Ada.Interrupts.Interrupt_'I'D""", Arg1);
10246                end if;
10247             end if;
10248
10249             --  Check OK state
10250
10251             case Chars (Get_Pragma_Arg (Arg2)) is
10252                when Name_Runtime => State_Type := 'r';
10253                when Name_System  => State_Type := 's';
10254                when Name_User    => State_Type := 'u';
10255
10256                when others =>
10257                   Error_Pragma_Arg ("invalid interrupt state", Arg2);
10258             end case;
10259
10260             --  Check if entry is already stored
10261
10262             IST_Num := Interrupt_States.First;
10263             loop
10264                --  If entry not found, add it
10265
10266                if IST_Num > Interrupt_States.Last then
10267                   Interrupt_States.Append
10268                     ((Interrupt_Number => UI_To_Int (Int_Val),
10269                       Interrupt_State  => State_Type,
10270                       Pragma_Loc       => Loc));
10271                   exit;
10272
10273                --  Case of entry for the same entry
10274
10275                elsif Int_Val = Interrupt_States.Table (IST_Num).
10276                                                            Interrupt_Number
10277                then
10278                   --  If state matches, done, no need to make redundant entry
10279
10280                   exit when
10281                     State_Type = Interrupt_States.Table (IST_Num).
10282                                                            Interrupt_State;
10283
10284                   --  Otherwise if state does not match, error
10285
10286                   Error_Msg_Sloc :=
10287                     Interrupt_States.Table (IST_Num).Pragma_Loc;
10288                   Error_Pragma_Arg
10289                     ("state conflicts with that given #", Arg2);
10290                   exit;
10291                end if;
10292
10293                IST_Num := IST_Num + 1;
10294             end loop;
10295          end Interrupt_State;
10296
10297          ---------------
10298          -- Invariant --
10299          ---------------
10300
10301          --  pragma Invariant
10302          --    ([Entity =>]    type_LOCAL_NAME,
10303          --     [Check  =>]    EXPRESSION
10304          --     [,[Message =>] String_Expression]);
10305
10306          when Pragma_Invariant => Invariant : declare
10307             Type_Id : Node_Id;
10308             Typ     : Entity_Id;
10309
10310             Discard : Boolean;
10311             pragma Unreferenced (Discard);
10312
10313          begin
10314             GNAT_Pragma;
10315             Check_At_Least_N_Arguments (2);
10316             Check_At_Most_N_Arguments (3);
10317             Check_Optional_Identifier (Arg1, Name_Entity);
10318             Check_Optional_Identifier (Arg2, Name_Check);
10319
10320             if Arg_Count = 3 then
10321                Check_Optional_Identifier (Arg3, Name_Message);
10322                Check_Arg_Is_Static_Expression (Arg3, Standard_String);
10323             end if;
10324
10325             Check_Arg_Is_Local_Name (Arg1);
10326
10327             Type_Id := Get_Pragma_Arg (Arg1);
10328             Find_Type (Type_Id);
10329             Typ := Entity (Type_Id);
10330
10331             if Typ = Any_Type then
10332                return;
10333
10334             --  An invariant must apply to a private type, or appear in the
10335             --  private part of a package spec and apply to a completion.
10336
10337             elsif Ekind_In (Typ, E_Private_Type,
10338                                  E_Record_Type_With_Private,
10339                                  E_Limited_Private_Type)
10340             then
10341                null;
10342
10343             elsif In_Private_Part (Current_Scope)
10344               and then Has_Private_Declaration (Typ)
10345             then
10346                null;
10347
10348             elsif In_Private_Part (Current_Scope) then
10349                Error_Pragma_Arg
10350                  ("pragma% only allowed for private type " &
10351                   "declared in visible part", Arg1);
10352
10353             else
10354                Error_Pragma_Arg
10355                  ("pragma% only allowed for private type", Arg1);
10356             end if;
10357
10358             --  Note that the type has at least one invariant, and also that
10359             --  it has inheritable invariants if we have Invariant'Class.
10360
10361             Set_Has_Invariants (Typ);
10362
10363             if Class_Present (N) then
10364                Set_Has_Inheritable_Invariants (Typ);
10365             end if;
10366
10367             --  The remaining processing is simply to link the pragma on to
10368             --  the rep item chain, for processing when the type is frozen.
10369             --  This is accomplished by a call to Rep_Item_Too_Late.
10370
10371             Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
10372          end Invariant;
10373
10374          ----------------------
10375          -- Java_Constructor --
10376          ----------------------
10377
10378          --  pragma Java_Constructor ([Entity =>] LOCAL_NAME);
10379
10380          --  Also handles pragma CIL_Constructor
10381
10382          when Pragma_CIL_Constructor | Pragma_Java_Constructor =>
10383          Java_Constructor : declare
10384             Convention  : Convention_Id;
10385             Def_Id      : Entity_Id;
10386             Hom_Id      : Entity_Id;
10387             Id          : Entity_Id;
10388             This_Formal : Entity_Id;
10389
10390          begin
10391             GNAT_Pragma;
10392             Check_Arg_Count (1);
10393             Check_Optional_Identifier (Arg1, Name_Entity);
10394             Check_Arg_Is_Local_Name (Arg1);
10395
10396             Id := Get_Pragma_Arg (Arg1);
10397             Find_Program_Unit_Name (Id);
10398
10399             --  If we did not find the name, we are done
10400
10401             if Etype (Id) = Any_Type then
10402                return;
10403             end if;
10404
10405             --  Check wrong use of pragma in wrong VM target
10406
10407             if VM_Target = No_VM then
10408                return;
10409
10410             elsif VM_Target = CLI_Target
10411               and then Prag_Id = Pragma_Java_Constructor
10412             then
10413                Error_Pragma ("must use pragma 'C'I'L_'Constructor");
10414
10415             elsif VM_Target = JVM_Target
10416               and then Prag_Id = Pragma_CIL_Constructor
10417             then
10418                Error_Pragma ("must use pragma 'Java_'Constructor");
10419             end if;
10420
10421             case Prag_Id is
10422                when Pragma_CIL_Constructor  => Convention := Convention_CIL;
10423                when Pragma_Java_Constructor => Convention := Convention_Java;
10424                when others                  => null;
10425             end case;
10426
10427             Hom_Id := Entity (Id);
10428
10429             --  Loop through homonyms
10430
10431             loop
10432                Def_Id := Get_Base_Subprogram (Hom_Id);
10433
10434                --  The constructor is required to be a function
10435
10436                if Ekind (Def_Id) /= E_Function then
10437                   if VM_Target = JVM_Target then
10438                      Error_Pragma_Arg
10439                        ("pragma% requires function returning a " &
10440                         "'Java access type", Def_Id);
10441                   else
10442                      Error_Pragma_Arg
10443                        ("pragma% requires function returning a " &
10444                         "'C'I'L access type", Def_Id);
10445                   end if;
10446                end if;
10447
10448                --  Check arguments: For tagged type the first formal must be
10449                --  named "this" and its type must be a named access type
10450                --  designating a class-wide tagged type that has convention
10451                --  CIL/Java. The first formal must also have a null default
10452                --  value. For example:
10453
10454                --      type Typ is tagged ...
10455                --      type Ref is access all Typ;
10456                --      pragma Convention (CIL, Typ);
10457
10458                --      function New_Typ (This : Ref) return Ref;
10459                --      function New_Typ (This : Ref; I : Integer) return Ref;
10460                --      pragma Cil_Constructor (New_Typ);
10461
10462                --  Reason: The first formal must NOT be a primitive of the
10463                --  tagged type.
10464
10465                --  This rule also applies to constructors of delegates used
10466                --  to interface with standard target libraries. For example:
10467
10468                --      type Delegate is access procedure ...
10469                --      pragma Import (CIL, Delegate, ...);
10470
10471                --      function new_Delegate
10472                --        (This : Delegate := null; ... ) return Delegate;
10473
10474                --  For value-types this rule does not apply.
10475
10476                if not Is_Value_Type (Etype (Def_Id)) then
10477                   if No (First_Formal (Def_Id)) then
10478                      Error_Msg_Name_1 := Pname;
10479                      Error_Msg_N ("% function must have parameters", Def_Id);
10480                      return;
10481                   end if;
10482
10483                   --  In the JRE library we have several occurrences in which
10484                   --  the "this" parameter is not the first formal.
10485
10486                   This_Formal := First_Formal (Def_Id);
10487
10488                   --  In the JRE library we have several occurrences in which
10489                   --  the "this" parameter is not the first formal. Search for
10490                   --  it.
10491
10492                   if VM_Target = JVM_Target then
10493                      while Present (This_Formal)
10494                        and then Get_Name_String (Chars (This_Formal)) /= "this"
10495                      loop
10496                         Next_Formal (This_Formal);
10497                      end loop;
10498
10499                      if No (This_Formal) then
10500                         This_Formal := First_Formal (Def_Id);
10501                      end if;
10502                   end if;
10503
10504                   --  Warning: The first parameter should be named "this".
10505                   --  We temporarily allow it because we have the following
10506                   --  case in the Java runtime (file s-osinte.ads) ???
10507
10508                   --    function new_Thread
10509                   --      (Self_Id : System.Address) return Thread_Id;
10510                   --    pragma Java_Constructor (new_Thread);
10511
10512                   if VM_Target = JVM_Target
10513                     and then Get_Name_String (Chars (First_Formal (Def_Id)))
10514                                = "self_id"
10515                     and then Etype (First_Formal (Def_Id)) = RTE (RE_Address)
10516                   then
10517                      null;
10518
10519                   elsif Get_Name_String (Chars (This_Formal)) /= "this" then
10520                      Error_Msg_Name_1 := Pname;
10521                      Error_Msg_N
10522                        ("first formal of % function must be named `this`",
10523                         Parent (This_Formal));
10524
10525                   elsif not Is_Access_Type (Etype (This_Formal)) then
10526                      Error_Msg_Name_1 := Pname;
10527                      Error_Msg_N
10528                        ("first formal of % function must be an access type",
10529                         Parameter_Type (Parent (This_Formal)));
10530
10531                   --  For delegates the type of the first formal must be a
10532                   --  named access-to-subprogram type (see previous example)
10533
10534                   elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type
10535                     and then Ekind (Etype (This_Formal))
10536                                /= E_Access_Subprogram_Type
10537                   then
10538                      Error_Msg_Name_1 := Pname;
10539                      Error_Msg_N
10540                        ("first formal of % function must be a named access" &
10541                         " to subprogram type",
10542                         Parameter_Type (Parent (This_Formal)));
10543
10544                   --  Warning: We should reject anonymous access types because
10545                   --  the constructor must not be handled as a primitive of the
10546                   --  tagged type. We temporarily allow it because this profile
10547                   --  is currently generated by cil2ada???
10548
10549                   elsif Ekind (Etype (Def_Id)) /= E_Access_Subprogram_Type
10550                     and then not Ekind_In (Etype (This_Formal),
10551                                              E_Access_Type,
10552                                              E_General_Access_Type,
10553                                              E_Anonymous_Access_Type)
10554                   then
10555                      Error_Msg_Name_1 := Pname;
10556                      Error_Msg_N
10557                        ("first formal of % function must be a named access" &
10558                         " type",
10559                         Parameter_Type (Parent (This_Formal)));
10560
10561                   elsif Atree.Convention
10562                          (Designated_Type (Etype (This_Formal))) /= Convention
10563                   then
10564                      Error_Msg_Name_1 := Pname;
10565
10566                      if Convention = Convention_Java then
10567                         Error_Msg_N
10568                           ("pragma% requires convention 'Cil in designated" &
10569                            " type",
10570                            Parameter_Type (Parent (This_Formal)));
10571                      else
10572                         Error_Msg_N
10573                           ("pragma% requires convention 'Java in designated" &
10574                            " type",
10575                            Parameter_Type (Parent (This_Formal)));
10576                      end if;
10577
10578                   elsif No (Expression (Parent (This_Formal)))
10579                     or else Nkind (Expression (Parent (This_Formal))) /= N_Null
10580                   then
10581                      Error_Msg_Name_1 := Pname;
10582                      Error_Msg_N
10583                        ("pragma% requires first formal with default `null`",
10584                         Parameter_Type (Parent (This_Formal)));
10585                   end if;
10586                end if;
10587
10588                --  Check result type: the constructor must be a function
10589                --  returning:
10590                --   * a value type (only allowed in the CIL compiler)
10591                --   * an access-to-subprogram type with convention Java/CIL
10592                --   * an access-type designating a type that has convention
10593                --     Java/CIL.
10594
10595                if Is_Value_Type (Etype (Def_Id)) then
10596                   null;
10597
10598                --  Access-to-subprogram type with convention Java/CIL
10599
10600                elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type then
10601                   if Atree.Convention (Etype (Def_Id)) /= Convention then
10602                      if Convention = Convention_Java then
10603                         Error_Pragma_Arg
10604                           ("pragma% requires function returning a " &
10605                            "'Java access type", Arg1);
10606                      else
10607                         pragma Assert (Convention = Convention_CIL);
10608                         Error_Pragma_Arg
10609                           ("pragma% requires function returning a " &
10610                            "'C'I'L access type", Arg1);
10611                      end if;
10612                   end if;
10613
10614                elsif Ekind (Etype (Def_Id)) in Access_Kind then
10615                   if not Ekind_In (Etype (Def_Id), E_Access_Type,
10616                                                    E_General_Access_Type)
10617                     or else
10618                       Atree.Convention
10619                         (Designated_Type (Etype (Def_Id))) /= Convention
10620                   then
10621                      Error_Msg_Name_1 := Pname;
10622
10623                      if Convention = Convention_Java then
10624                         Error_Pragma_Arg
10625                           ("pragma% requires function returning a named" &
10626                            "'Java access type", Arg1);
10627                      else
10628                         Error_Pragma_Arg
10629                           ("pragma% requires function returning a named" &
10630                            "'C'I'L access type", Arg1);
10631                      end if;
10632                   end if;
10633                end if;
10634
10635                Set_Is_Constructor (Def_Id);
10636                Set_Convention     (Def_Id, Convention);
10637                Set_Is_Imported    (Def_Id);
10638
10639                exit when From_Aspect_Specification (N);
10640                Hom_Id := Homonym (Hom_Id);
10641
10642                exit when No (Hom_Id) or else Scope (Hom_Id) /= Current_Scope;
10643             end loop;
10644          end Java_Constructor;
10645
10646          ----------------------
10647          -- Java_Interface --
10648          ----------------------
10649
10650          --  pragma Java_Interface ([Entity =>] LOCAL_NAME);
10651
10652          when Pragma_Java_Interface => Java_Interface : declare
10653             Arg : Node_Id;
10654             Typ : Entity_Id;
10655
10656          begin
10657             GNAT_Pragma;
10658             Check_Arg_Count (1);
10659             Check_Optional_Identifier (Arg1, Name_Entity);
10660             Check_Arg_Is_Local_Name (Arg1);
10661
10662             Arg := Get_Pragma_Arg (Arg1);
10663             Analyze (Arg);
10664
10665             if Etype (Arg) = Any_Type then
10666                return;
10667             end if;
10668
10669             if not Is_Entity_Name (Arg)
10670               or else not Is_Type (Entity (Arg))
10671             then
10672                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
10673             end if;
10674
10675             Typ := Underlying_Type (Entity (Arg));
10676
10677             --  For now simply check some of the semantic constraints on the
10678             --  type. This currently leaves out some restrictions on interface
10679             --  types, namely that the parent type must be java.lang.Object.Typ
10680             --  and that all primitives of the type should be declared
10681             --  abstract. ???
10682
10683             if not Is_Tagged_Type (Typ) or else not Is_Abstract_Type (Typ) then
10684                Error_Pragma_Arg ("pragma% requires an abstract "
10685                  & "tagged type", Arg1);
10686
10687             elsif not Has_Discriminants (Typ)
10688               or else Ekind (Etype (First_Discriminant (Typ)))
10689                         /= E_Anonymous_Access_Type
10690               or else
10691                 not Is_Class_Wide_Type
10692                       (Designated_Type (Etype (First_Discriminant (Typ))))
10693             then
10694                Error_Pragma_Arg
10695                  ("type must have a class-wide access discriminant", Arg1);
10696             end if;
10697          end Java_Interface;
10698
10699          ----------------
10700          -- Keep_Names --
10701          ----------------
10702
10703          --  pragma Keep_Names ([On => ] local_NAME);
10704
10705          when Pragma_Keep_Names => Keep_Names : declare
10706             Arg : Node_Id;
10707
10708          begin
10709             GNAT_Pragma;
10710             Check_Arg_Count (1);
10711             Check_Optional_Identifier (Arg1, Name_On);
10712             Check_Arg_Is_Local_Name (Arg1);
10713
10714             Arg := Get_Pragma_Arg (Arg1);
10715             Analyze (Arg);
10716
10717             if Etype (Arg) = Any_Type then
10718                return;
10719             end if;
10720
10721             if not Is_Entity_Name (Arg)
10722               or else Ekind (Entity (Arg)) /= E_Enumeration_Type
10723             then
10724                Error_Pragma_Arg
10725                  ("pragma% requires a local enumeration type", Arg1);
10726             end if;
10727
10728             Set_Discard_Names (Entity (Arg), False);
10729          end Keep_Names;
10730
10731          -------------
10732          -- License --
10733          -------------
10734
10735          --  pragma License (RESTRICTED | UNRESTRICTED | GPL | MODIFIED_GPL);
10736
10737          when Pragma_License =>
10738             GNAT_Pragma;
10739             Check_Arg_Count (1);
10740             Check_No_Identifiers;
10741             Check_Valid_Configuration_Pragma;
10742             Check_Arg_Is_Identifier (Arg1);
10743
10744             declare
10745                Sind : constant Source_File_Index :=
10746                         Source_Index (Current_Sem_Unit);
10747
10748             begin
10749                case Chars (Get_Pragma_Arg (Arg1)) is
10750                   when Name_GPL =>
10751                      Set_License (Sind, GPL);
10752
10753                   when Name_Modified_GPL =>
10754                      Set_License (Sind, Modified_GPL);
10755
10756                   when Name_Restricted =>
10757                      Set_License (Sind, Restricted);
10758
10759                   when Name_Unrestricted =>
10760                      Set_License (Sind, Unrestricted);
10761
10762                   when others =>
10763                      Error_Pragma_Arg ("invalid license name", Arg1);
10764                end case;
10765             end;
10766
10767          ---------------
10768          -- Link_With --
10769          ---------------
10770
10771          --  pragma Link_With (string_EXPRESSION {, string_EXPRESSION});
10772
10773          when Pragma_Link_With => Link_With : declare
10774             Arg : Node_Id;
10775
10776          begin
10777             GNAT_Pragma;
10778
10779             if Operating_Mode = Generate_Code
10780               and then In_Extended_Main_Source_Unit (N)
10781             then
10782                Check_At_Least_N_Arguments (1);
10783                Check_No_Identifiers;
10784                Check_Is_In_Decl_Part_Or_Package_Spec;
10785                Check_Arg_Is_Static_Expression (Arg1, Standard_String);
10786                Start_String;
10787
10788                Arg := Arg1;
10789                while Present (Arg) loop
10790                   Check_Arg_Is_Static_Expression (Arg, Standard_String);
10791
10792                   --  Store argument, converting sequences of spaces to a
10793                   --  single null character (this is one of the differences
10794                   --  in processing between Link_With and Linker_Options).
10795
10796                   Arg_Store : declare
10797                      C : constant Char_Code := Get_Char_Code (' ');
10798                      S : constant String_Id :=
10799                            Strval (Expr_Value_S (Get_Pragma_Arg (Arg)));
10800                      L : constant Nat := String_Length (S);
10801                      F : Nat := 1;
10802
10803                      procedure Skip_Spaces;
10804                      --  Advance F past any spaces
10805
10806                      -----------------
10807                      -- Skip_Spaces --
10808                      -----------------
10809
10810                      procedure Skip_Spaces is
10811                      begin
10812                         while F <= L and then Get_String_Char (S, F) = C loop
10813                            F := F + 1;
10814                         end loop;
10815                      end Skip_Spaces;
10816
10817                   --  Start of processing for Arg_Store
10818
10819                   begin
10820                      Skip_Spaces; -- skip leading spaces
10821
10822                      --  Loop through characters, changing any embedded
10823                      --  sequence of spaces to a single null character (this
10824                      --  is how Link_With/Linker_Options differ)
10825
10826                      while F <= L loop
10827                         if Get_String_Char (S, F) = C then
10828                            Skip_Spaces;
10829                            exit when F > L;
10830                            Store_String_Char (ASCII.NUL);
10831
10832                         else
10833                            Store_String_Char (Get_String_Char (S, F));
10834                            F := F + 1;
10835                         end if;
10836                      end loop;
10837                   end Arg_Store;
10838
10839                   Arg := Next (Arg);
10840
10841                   if Present (Arg) then
10842                      Store_String_Char (ASCII.NUL);
10843                   end if;
10844                end loop;
10845
10846                Store_Linker_Option_String (End_String);
10847             end if;
10848          end Link_With;
10849
10850          ------------------
10851          -- Linker_Alias --
10852          ------------------
10853
10854          --  pragma Linker_Alias (
10855          --      [Entity =>]  LOCAL_NAME
10856          --      [Target =>]  static_string_EXPRESSION);
10857
10858          when Pragma_Linker_Alias =>
10859             GNAT_Pragma;
10860             Check_Arg_Order ((Name_Entity, Name_Target));
10861             Check_Arg_Count (2);
10862             Check_Optional_Identifier (Arg1, Name_Entity);
10863             Check_Optional_Identifier (Arg2, Name_Target);
10864             Check_Arg_Is_Library_Level_Local_Name (Arg1);
10865             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10866
10867             --  The only processing required is to link this item on to the
10868             --  list of rep items for the given entity. This is accomplished
10869             --  by the call to Rep_Item_Too_Late (when no error is detected
10870             --  and False is returned).
10871
10872             if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
10873                return;
10874             else
10875                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10876             end if;
10877
10878          ------------------------
10879          -- Linker_Constructor --
10880          ------------------------
10881
10882          --  pragma Linker_Constructor (procedure_LOCAL_NAME);
10883
10884          --  Code is shared with Linker_Destructor
10885
10886          -----------------------
10887          -- Linker_Destructor --
10888          -----------------------
10889
10890          --  pragma Linker_Destructor (procedure_LOCAL_NAME);
10891
10892          when Pragma_Linker_Constructor |
10893               Pragma_Linker_Destructor =>
10894          Linker_Constructor : declare
10895             Arg1_X : Node_Id;
10896             Proc   : Entity_Id;
10897
10898          begin
10899             GNAT_Pragma;
10900             Check_Arg_Count (1);
10901             Check_No_Identifiers;
10902             Check_Arg_Is_Local_Name (Arg1);
10903             Arg1_X := Get_Pragma_Arg (Arg1);
10904             Analyze (Arg1_X);
10905             Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
10906
10907             if not Is_Library_Level_Entity (Proc) then
10908                Error_Pragma_Arg
10909                 ("argument for pragma% must be library level entity", Arg1);
10910             end if;
10911
10912             --  The only processing required is to link this item on to the
10913             --  list of rep items for the given entity. This is accomplished
10914             --  by the call to Rep_Item_Too_Late (when no error is detected
10915             --  and False is returned).
10916
10917             if Rep_Item_Too_Late (Proc, N) then
10918                return;
10919             else
10920                Set_Has_Gigi_Rep_Item (Proc);
10921             end if;
10922          end Linker_Constructor;
10923
10924          --------------------
10925          -- Linker_Options --
10926          --------------------
10927
10928          --  pragma Linker_Options (string_EXPRESSION {, string_EXPRESSION});
10929
10930          when Pragma_Linker_Options => Linker_Options : declare
10931             Arg : Node_Id;
10932
10933          begin
10934             Check_Ada_83_Warning;
10935             Check_No_Identifiers;
10936             Check_Arg_Count (1);
10937             Check_Is_In_Decl_Part_Or_Package_Spec;
10938             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
10939             Start_String (Strval (Expr_Value_S (Get_Pragma_Arg (Arg1))));
10940
10941             Arg := Arg2;
10942             while Present (Arg) loop
10943                Check_Arg_Is_Static_Expression (Arg, Standard_String);
10944                Store_String_Char (ASCII.NUL);
10945                Store_String_Chars
10946                  (Strval (Expr_Value_S (Get_Pragma_Arg (Arg))));
10947                Arg := Next (Arg);
10948             end loop;
10949
10950             if Operating_Mode = Generate_Code
10951               and then In_Extended_Main_Source_Unit (N)
10952             then
10953                Store_Linker_Option_String (End_String);
10954             end if;
10955          end Linker_Options;
10956
10957          --------------------
10958          -- Linker_Section --
10959          --------------------
10960
10961          --  pragma Linker_Section (
10962          --      [Entity  =>]  LOCAL_NAME
10963          --      [Section =>]  static_string_EXPRESSION);
10964
10965          when Pragma_Linker_Section =>
10966             GNAT_Pragma;
10967             Check_Arg_Order ((Name_Entity, Name_Section));
10968             Check_Arg_Count (2);
10969             Check_Optional_Identifier (Arg1, Name_Entity);
10970             Check_Optional_Identifier (Arg2, Name_Section);
10971             Check_Arg_Is_Library_Level_Local_Name (Arg1);
10972             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10973
10974             --  This pragma applies only to objects
10975
10976             if not Is_Object (Entity (Get_Pragma_Arg (Arg1))) then
10977                Error_Pragma_Arg ("pragma% applies only to objects", Arg1);
10978             end if;
10979
10980             --  The only processing required is to link this item on to the
10981             --  list of rep items for the given entity. This is accomplished
10982             --  by the call to Rep_Item_Too_Late (when no error is detected
10983             --  and False is returned).
10984
10985             if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
10986                return;
10987             else
10988                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10989             end if;
10990
10991          ----------
10992          -- List --
10993          ----------
10994
10995          --  pragma List (On | Off)
10996
10997          --  There is nothing to do here, since we did all the processing for
10998          --  this pragma in Par.Prag (so that it works properly even in syntax
10999          --  only mode).
11000
11001          when Pragma_List =>
11002             null;
11003
11004          --------------------
11005          -- Locking_Policy --
11006          --------------------
11007
11008          --  pragma Locking_Policy (policy_IDENTIFIER);
11009
11010          when Pragma_Locking_Policy => declare
11011             subtype LP_Range is Name_Id
11012               range First_Locking_Policy_Name .. Last_Locking_Policy_Name;
11013             LP_Val : LP_Range;
11014             LP     : Character;
11015          begin
11016             Check_Ada_83_Warning;
11017             Check_Arg_Count (1);
11018             Check_No_Identifiers;
11019             Check_Arg_Is_Locking_Policy (Arg1);
11020             Check_Valid_Configuration_Pragma;
11021             LP_Val := Chars (Get_Pragma_Arg (Arg1));
11022
11023             case LP_Val is
11024                when Name_Ceiling_Locking            => LP := 'C';
11025                when Name_Inheritance_Locking        => LP := 'I';
11026                when Name_Concurrent_Readers_Locking => LP := 'R';
11027             end case;
11028
11029             if Locking_Policy /= ' '
11030               and then Locking_Policy /= LP
11031             then
11032                Error_Msg_Sloc := Locking_Policy_Sloc;
11033                Error_Pragma ("locking policy incompatible with policy#");
11034
11035             --  Set new policy, but always preserve System_Location since we
11036             --  like the error message with the run time name.
11037
11038             else
11039                Locking_Policy := LP;
11040
11041                if Locking_Policy_Sloc /= System_Location then
11042                   Locking_Policy_Sloc := Loc;
11043                end if;
11044             end if;
11045          end;
11046
11047          ----------------
11048          -- Long_Float --
11049          ----------------
11050
11051          --  pragma Long_Float (D_Float | G_Float);
11052
11053          when Pragma_Long_Float => Long_Float : declare
11054          begin
11055             GNAT_Pragma;
11056             Check_Valid_Configuration_Pragma;
11057             Check_Arg_Count (1);
11058             Check_No_Identifier (Arg1);
11059             Check_Arg_Is_One_Of (Arg1, Name_D_Float, Name_G_Float);
11060
11061             if not OpenVMS_On_Target then
11062                Error_Pragma ("?pragma% ignored (applies only to Open'V'M'S)");
11063             end if;
11064
11065             --  D_Float case
11066
11067             if Chars (Get_Pragma_Arg (Arg1)) = Name_D_Float then
11068                if Opt.Float_Format_Long = 'G' then
11069                   Error_Pragma_Arg
11070                     ("G_Float previously specified", Arg1);
11071
11072                elsif Current_Sem_Unit /= Main_Unit
11073                  and then Opt.Float_Format_Long /= 'D'
11074                then
11075                   Error_Pragma_Arg
11076                     ("main unit not compiled with pragma Long_Float (D_Float)",
11077                      "\pragma% must be used consistently for whole partition",
11078                      Arg1);
11079
11080                else
11081                   Opt.Float_Format_Long := 'D';
11082                end if;
11083
11084             --  G_Float case (this is the default, does not need overriding)
11085
11086             else
11087                if Opt.Float_Format_Long = 'D' then
11088                   Error_Pragma ("D_Float previously specified");
11089
11090                elsif Current_Sem_Unit /= Main_Unit
11091                  and then Opt.Float_Format_Long /= 'G'
11092                then
11093                   Error_Pragma_Arg
11094                     ("main unit not compiled with pragma Long_Float (G_Float)",
11095                      "\pragma% must be used consistently for whole partition",
11096                      Arg1);
11097
11098                else
11099                   Opt.Float_Format_Long := 'G';
11100                end if;
11101             end if;
11102
11103             Set_Standard_Fpt_Formats;
11104          end Long_Float;
11105
11106          -----------------------
11107          -- Machine_Attribute --
11108          -----------------------
11109
11110          --  pragma Machine_Attribute (
11111          --       [Entity         =>] LOCAL_NAME,
11112          --       [Attribute_Name =>] static_string_EXPRESSION
11113          --    [, [Info           =>] static_EXPRESSION] );
11114
11115          when Pragma_Machine_Attribute => Machine_Attribute : declare
11116             Def_Id : Entity_Id;
11117
11118          begin
11119             GNAT_Pragma;
11120             Check_Arg_Order ((Name_Entity, Name_Attribute_Name, Name_Info));
11121
11122             if Arg_Count = 3 then
11123                Check_Optional_Identifier (Arg3, Name_Info);
11124                Check_Arg_Is_Static_Expression (Arg3);
11125             else
11126                Check_Arg_Count (2);
11127             end if;
11128
11129             Check_Optional_Identifier (Arg1, Name_Entity);
11130             Check_Optional_Identifier (Arg2, Name_Attribute_Name);
11131             Check_Arg_Is_Local_Name (Arg1);
11132             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
11133             Def_Id := Entity (Get_Pragma_Arg (Arg1));
11134
11135             if Is_Access_Type (Def_Id) then
11136                Def_Id := Designated_Type (Def_Id);
11137             end if;
11138
11139             if Rep_Item_Too_Early (Def_Id, N) then
11140                return;
11141             end if;
11142
11143             Def_Id := Underlying_Type (Def_Id);
11144
11145             --  The only processing required is to link this item on to the
11146             --  list of rep items for the given entity. This is accomplished
11147             --  by the call to Rep_Item_Too_Late (when no error is detected
11148             --  and False is returned).
11149
11150             if Rep_Item_Too_Late (Def_Id, N) then
11151                return;
11152             else
11153                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
11154             end if;
11155          end Machine_Attribute;
11156
11157          ----------
11158          -- Main --
11159          ----------
11160
11161          --  pragma Main
11162          --   (MAIN_OPTION [, MAIN_OPTION]);
11163
11164          --  MAIN_OPTION ::=
11165          --    [STACK_SIZE              =>] static_integer_EXPRESSION
11166          --  | [TASK_STACK_SIZE_DEFAULT =>] static_integer_EXPRESSION
11167          --  | [TIME_SLICING_ENABLED    =>] static_boolean_EXPRESSION
11168
11169          when Pragma_Main => Main : declare
11170             Args  : Args_List (1 .. 3);
11171             Names : constant Name_List (1 .. 3) := (
11172                       Name_Stack_Size,
11173                       Name_Task_Stack_Size_Default,
11174                       Name_Time_Slicing_Enabled);
11175
11176             Nod : Node_Id;
11177
11178          begin
11179             GNAT_Pragma;
11180             Gather_Associations (Names, Args);
11181
11182             for J in 1 .. 2 loop
11183                if Present (Args (J)) then
11184                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
11185                end if;
11186             end loop;
11187
11188             if Present (Args (3)) then
11189                Check_Arg_Is_Static_Expression (Args (3), Standard_Boolean);
11190             end if;
11191
11192             Nod := Next (N);
11193             while Present (Nod) loop
11194                if Nkind (Nod) = N_Pragma
11195                  and then Pragma_Name (Nod) = Name_Main
11196                then
11197                   Error_Msg_Name_1 := Pname;
11198                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
11199                end if;
11200
11201                Next (Nod);
11202             end loop;
11203          end Main;
11204
11205          ------------------
11206          -- Main_Storage --
11207          ------------------
11208
11209          --  pragma Main_Storage
11210          --   (MAIN_STORAGE_OPTION [, MAIN_STORAGE_OPTION]);
11211
11212          --  MAIN_STORAGE_OPTION ::=
11213          --    [WORKING_STORAGE =>] static_SIMPLE_EXPRESSION
11214          --  | [TOP_GUARD =>] static_SIMPLE_EXPRESSION
11215
11216          when Pragma_Main_Storage => Main_Storage : declare
11217             Args  : Args_List (1 .. 2);
11218             Names : constant Name_List (1 .. 2) := (
11219                       Name_Working_Storage,
11220                       Name_Top_Guard);
11221
11222             Nod : Node_Id;
11223
11224          begin
11225             GNAT_Pragma;
11226             Gather_Associations (Names, Args);
11227
11228             for J in 1 .. 2 loop
11229                if Present (Args (J)) then
11230                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
11231                end if;
11232             end loop;
11233
11234             Check_In_Main_Program;
11235
11236             Nod := Next (N);
11237             while Present (Nod) loop
11238                if Nkind (Nod) = N_Pragma
11239                  and then Pragma_Name (Nod) = Name_Main_Storage
11240                then
11241                   Error_Msg_Name_1 := Pname;
11242                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
11243                end if;
11244
11245                Next (Nod);
11246             end loop;
11247          end Main_Storage;
11248
11249          -----------------
11250          -- Memory_Size --
11251          -----------------
11252
11253          --  pragma Memory_Size (NUMERIC_LITERAL)
11254
11255          when Pragma_Memory_Size =>
11256             GNAT_Pragma;
11257
11258             --  Memory size is simply ignored
11259
11260             Check_No_Identifiers;
11261             Check_Arg_Count (1);
11262             Check_Arg_Is_Integer_Literal (Arg1);
11263
11264          -------------
11265          -- No_Body --
11266          -------------
11267
11268          --  pragma No_Body;
11269
11270          --  The only correct use of this pragma is on its own in a file, in
11271          --  which case it is specially processed (see Gnat1drv.Check_Bad_Body
11272          --  and Frontend, which use Sinput.L.Source_File_Is_Pragma_No_Body to
11273          --  check for a file containing nothing but a No_Body pragma). If we
11274          --  attempt to process it during normal semantics processing, it means
11275          --  it was misplaced.
11276
11277          when Pragma_No_Body =>
11278             GNAT_Pragma;
11279             Pragma_Misplaced;
11280
11281          ---------------
11282          -- No_Return --
11283          ---------------
11284
11285          --  pragma No_Return (procedure_LOCAL_NAME {, procedure_Local_Name});
11286
11287          when Pragma_No_Return => No_Return : declare
11288             Id    : Node_Id;
11289             E     : Entity_Id;
11290             Found : Boolean;
11291             Arg   : Node_Id;
11292
11293          begin
11294             Ada_2005_Pragma;
11295             Check_At_Least_N_Arguments (1);
11296
11297             --  Loop through arguments of pragma
11298
11299             Arg := Arg1;
11300             while Present (Arg) loop
11301                Check_Arg_Is_Local_Name (Arg);
11302                Id := Get_Pragma_Arg (Arg);
11303                Analyze (Id);
11304
11305                if not Is_Entity_Name (Id) then
11306                   Error_Pragma_Arg ("entity name required", Arg);
11307                end if;
11308
11309                if Etype (Id) = Any_Type then
11310                   raise Pragma_Exit;
11311                end if;
11312
11313                --  Loop to find matching procedures
11314
11315                E := Entity (Id);
11316                Found := False;
11317                while Present (E)
11318                  and then Scope (E) = Current_Scope
11319                loop
11320                   if Ekind_In (E, E_Procedure, E_Generic_Procedure) then
11321                      Set_No_Return (E);
11322
11323                      --  Set flag on any alias as well
11324
11325                      if Is_Overloadable (E) and then Present (Alias (E)) then
11326                         Set_No_Return (Alias (E));
11327                      end if;
11328
11329                      Found := True;
11330                   end if;
11331
11332                   exit when From_Aspect_Specification (N);
11333                   E := Homonym (E);
11334                end loop;
11335
11336                if not Found then
11337                   Error_Pragma_Arg ("no procedure & found for pragma%", Arg);
11338                end if;
11339
11340                Next (Arg);
11341             end loop;
11342          end No_Return;
11343
11344          -----------------
11345          -- No_Run_Time --
11346          -----------------
11347
11348          --  pragma No_Run_Time;
11349
11350          --  Note: this pragma is retained for backwards compatibility. See
11351          --  body of Rtsfind for full details on its handling.
11352
11353          when Pragma_No_Run_Time =>
11354             GNAT_Pragma;
11355             Check_Valid_Configuration_Pragma;
11356             Check_Arg_Count (0);
11357
11358             No_Run_Time_Mode           := True;
11359             Configurable_Run_Time_Mode := True;
11360
11361             --  Set Duration to 32 bits if word size is 32
11362
11363             if Ttypes.System_Word_Size = 32 then
11364                Duration_32_Bits_On_Target := True;
11365             end if;
11366
11367             --  Set appropriate restrictions
11368
11369             Set_Restriction (No_Finalization, N);
11370             Set_Restriction (No_Exception_Handlers, N);
11371             Set_Restriction (Max_Tasks, N, 0);
11372             Set_Restriction (No_Tasking, N);
11373
11374          ------------------------
11375          -- No_Strict_Aliasing --
11376          ------------------------
11377
11378          --  pragma No_Strict_Aliasing [([Entity =>] type_LOCAL_NAME)];
11379
11380          when Pragma_No_Strict_Aliasing => No_Strict_Aliasing : declare
11381             E_Id : Entity_Id;
11382
11383          begin
11384             GNAT_Pragma;
11385             Check_At_Most_N_Arguments (1);
11386
11387             if Arg_Count = 0 then
11388                Check_Valid_Configuration_Pragma;
11389                Opt.No_Strict_Aliasing := True;
11390
11391             else
11392                Check_Optional_Identifier (Arg2, Name_Entity);
11393                Check_Arg_Is_Local_Name (Arg1);
11394                E_Id := Entity (Get_Pragma_Arg (Arg1));
11395
11396                if E_Id = Any_Type then
11397                   return;
11398                elsif No (E_Id) or else not Is_Access_Type (E_Id) then
11399                   Error_Pragma_Arg ("pragma% requires access type", Arg1);
11400                end if;
11401
11402                Set_No_Strict_Aliasing (Implementation_Base_Type (E_Id));
11403             end if;
11404          end No_Strict_Aliasing;
11405
11406          -----------------------
11407          -- Normalize_Scalars --
11408          -----------------------
11409
11410          --  pragma Normalize_Scalars;
11411
11412          when Pragma_Normalize_Scalars =>
11413             Check_Ada_83_Warning;
11414             Check_Arg_Count (0);
11415             Check_Valid_Configuration_Pragma;
11416
11417             --  Normalize_Scalars creates false positives in CodePeer, and
11418             --  incorrect negative results in Alfa mode, so ignore this pragma
11419             --  in these modes.
11420
11421             if not (CodePeer_Mode or Alfa_Mode) then
11422                Normalize_Scalars := True;
11423                Init_Or_Norm_Scalars := True;
11424             end if;
11425
11426          -----------------
11427          -- Obsolescent --
11428          -----------------
11429
11430          --  pragma Obsolescent;
11431
11432          --  pragma Obsolescent (
11433          --    [Message =>] static_string_EXPRESSION
11434          --  [,[Version =>] Ada_05]]);
11435
11436          --  pragma Obsolescent (
11437          --    [Entity  =>] NAME
11438          --  [,[Message =>] static_string_EXPRESSION
11439          --  [,[Version =>] Ada_05]] );
11440
11441          when Pragma_Obsolescent => Obsolescent : declare
11442             Ename : Node_Id;
11443             Decl  : Node_Id;
11444
11445             procedure Set_Obsolescent (E : Entity_Id);
11446             --  Given an entity Ent, mark it as obsolescent if appropriate
11447
11448             ---------------------
11449             -- Set_Obsolescent --
11450             ---------------------
11451
11452             procedure Set_Obsolescent (E : Entity_Id) is
11453                Active : Boolean;
11454                Ent    : Entity_Id;
11455                S      : String_Id;
11456
11457             begin
11458                Active := True;
11459                Ent    := E;
11460
11461                --  Entity name was given
11462
11463                if Present (Ename) then
11464
11465                   --  If entity name matches, we are fine. Save entity in
11466                   --  pragma argument, for ASIS use.
11467
11468                   if Chars (Ename) = Chars (Ent) then
11469                      Set_Entity (Ename, Ent);
11470                      Generate_Reference (Ent, Ename);
11471
11472                   --  If entity name does not match, only possibility is an
11473                   --  enumeration literal from an enumeration type declaration.
11474
11475                   elsif Ekind (Ent) /= E_Enumeration_Type then
11476                      Error_Pragma
11477                        ("pragma % entity name does not match declaration");
11478
11479                   else
11480                      Ent := First_Literal (E);
11481                      loop
11482                         if No (Ent) then
11483                            Error_Pragma
11484                              ("pragma % entity name does not match any " &
11485                               "enumeration literal");
11486
11487                         elsif Chars (Ent) = Chars (Ename) then
11488                            Set_Entity (Ename, Ent);
11489                            Generate_Reference (Ent, Ename);
11490                            exit;
11491
11492                         else
11493                            Ent := Next_Literal (Ent);
11494                         end if;
11495                      end loop;
11496                   end if;
11497                end if;
11498
11499                --  Ent points to entity to be marked
11500
11501                if Arg_Count >= 1 then
11502
11503                   --  Deal with static string argument
11504
11505                   Check_Arg_Is_Static_Expression (Arg1, Standard_String);
11506                   S := Strval (Get_Pragma_Arg (Arg1));
11507
11508                   for J in 1 .. String_Length (S) loop
11509                      if not In_Character_Range (Get_String_Char (S, J)) then
11510                         Error_Pragma_Arg
11511                           ("pragma% argument does not allow wide characters",
11512                            Arg1);
11513                      end if;
11514                   end loop;
11515
11516                   Obsolescent_Warnings.Append
11517                     ((Ent => Ent, Msg => Strval (Get_Pragma_Arg (Arg1))));
11518
11519                   --  Check for Ada_05 parameter
11520
11521                   if Arg_Count /= 1 then
11522                      Check_Arg_Count (2);
11523
11524                      declare
11525                         Argx : constant Node_Id := Get_Pragma_Arg (Arg2);
11526
11527                      begin
11528                         Check_Arg_Is_Identifier (Argx);
11529
11530                         if Chars (Argx) /= Name_Ada_05 then
11531                            Error_Msg_Name_2 := Name_Ada_05;
11532                            Error_Pragma_Arg
11533                              ("only allowed argument for pragma% is %", Argx);
11534                         end if;
11535
11536                         if Ada_Version_Explicit < Ada_2005
11537                           or else not Warn_On_Ada_2005_Compatibility
11538                         then
11539                            Active := False;
11540                         end if;
11541                      end;
11542                   end if;
11543                end if;
11544
11545                --  Set flag if pragma active
11546
11547                if Active then
11548                   Set_Is_Obsolescent (Ent);
11549                end if;
11550
11551                return;
11552             end Set_Obsolescent;
11553
11554          --  Start of processing for pragma Obsolescent
11555
11556          begin
11557             GNAT_Pragma;
11558
11559             Check_At_Most_N_Arguments (3);
11560
11561             --  See if first argument specifies an entity name
11562
11563             if Arg_Count >= 1
11564               and then
11565                 (Chars (Arg1) = Name_Entity
11566                    or else
11567                      Nkind_In (Get_Pragma_Arg (Arg1), N_Character_Literal,
11568                                                       N_Identifier,
11569                                                       N_Operator_Symbol))
11570             then
11571                Ename := Get_Pragma_Arg (Arg1);
11572
11573                --  Eliminate first argument, so we can share processing
11574
11575                Arg1 := Arg2;
11576                Arg2 := Arg3;
11577                Arg_Count := Arg_Count - 1;
11578
11579             --  No Entity name argument given
11580
11581             else
11582                Ename := Empty;
11583             end if;
11584
11585             if Arg_Count >= 1 then
11586                Check_Optional_Identifier (Arg1, Name_Message);
11587
11588                if Arg_Count = 2 then
11589                   Check_Optional_Identifier (Arg2, Name_Version);
11590                end if;
11591             end if;
11592
11593             --  Get immediately preceding declaration
11594
11595             Decl := Prev (N);
11596             while Present (Decl) and then Nkind (Decl) = N_Pragma loop
11597                Prev (Decl);
11598             end loop;
11599
11600             --  Cases where we do not follow anything other than another pragma
11601
11602             if No (Decl) then
11603
11604                --  First case: library level compilation unit declaration with
11605                --  the pragma immediately following the declaration.
11606
11607                if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
11608                   Set_Obsolescent
11609                     (Defining_Entity (Unit (Parent (Parent (N)))));
11610                   return;
11611
11612                --  Case 2: library unit placement for package
11613
11614                else
11615                   declare
11616                      Ent : constant Entity_Id := Find_Lib_Unit_Name;
11617                   begin
11618                      if Is_Package_Or_Generic_Package (Ent) then
11619                         Set_Obsolescent (Ent);
11620                         return;
11621                      end if;
11622                   end;
11623                end if;
11624
11625             --  Cases where we must follow a declaration
11626
11627             else
11628                if         Nkind (Decl) not in N_Declaration
11629                  and then Nkind (Decl) not in N_Later_Decl_Item
11630                  and then Nkind (Decl) not in N_Generic_Declaration
11631                  and then Nkind (Decl) not in N_Renaming_Declaration
11632                then
11633                   Error_Pragma
11634                     ("pragma% misplaced, "
11635                      & "must immediately follow a declaration");
11636
11637                else
11638                   Set_Obsolescent (Defining_Entity (Decl));
11639                   return;
11640                end if;
11641             end if;
11642          end Obsolescent;
11643
11644          --------------
11645          -- Optimize --
11646          --------------
11647
11648          --  pragma Optimize (Time | Space | Off);
11649
11650          --  The actual check for optimize is done in Gigi. Note that this
11651          --  pragma does not actually change the optimization setting, it
11652          --  simply checks that it is consistent with the pragma.
11653
11654          when Pragma_Optimize =>
11655             Check_No_Identifiers;
11656             Check_Arg_Count (1);
11657             Check_Arg_Is_One_Of (Arg1, Name_Time, Name_Space, Name_Off);
11658
11659          ------------------------
11660          -- Optimize_Alignment --
11661          ------------------------
11662
11663          --  pragma Optimize_Alignment (Time | Space | Off);
11664
11665          when Pragma_Optimize_Alignment => Optimize_Alignment : begin
11666             GNAT_Pragma;
11667             Check_No_Identifiers;
11668             Check_Arg_Count (1);
11669             Check_Valid_Configuration_Pragma;
11670
11671             declare
11672                Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
11673             begin
11674                case Nam is
11675                   when Name_Time =>
11676                      Opt.Optimize_Alignment := 'T';
11677                   when Name_Space =>
11678                      Opt.Optimize_Alignment := 'S';
11679                   when Name_Off =>
11680                      Opt.Optimize_Alignment := 'O';
11681                   when others =>
11682                      Error_Pragma_Arg ("invalid argument for pragma%", Arg1);
11683                end case;
11684             end;
11685
11686             --  Set indication that mode is set locally. If we are in fact in a
11687             --  configuration pragma file, this setting is harmless since the
11688             --  switch will get reset anyway at the start of each unit.
11689
11690             Optimize_Alignment_Local := True;
11691          end Optimize_Alignment;
11692
11693          -------------
11694          -- Ordered --
11695          -------------
11696
11697          --  pragma Ordered (first_enumeration_subtype_LOCAL_NAME);
11698
11699          when Pragma_Ordered => Ordered : declare
11700             Assoc   : constant Node_Id := Arg1;
11701             Type_Id : Node_Id;
11702             Typ     : Entity_Id;
11703
11704          begin
11705             GNAT_Pragma;
11706             Check_No_Identifiers;
11707             Check_Arg_Count (1);
11708             Check_Arg_Is_Local_Name (Arg1);
11709
11710             Type_Id := Get_Pragma_Arg (Assoc);
11711             Find_Type (Type_Id);
11712             Typ := Entity (Type_Id);
11713
11714             if Typ = Any_Type then
11715                return;
11716             else
11717                Typ := Underlying_Type (Typ);
11718             end if;
11719
11720             if not Is_Enumeration_Type (Typ) then
11721                Error_Pragma ("pragma% must specify enumeration type");
11722             end if;
11723
11724             Check_First_Subtype (Arg1);
11725             Set_Has_Pragma_Ordered (Base_Type (Typ));
11726          end Ordered;
11727
11728          ----------
11729          -- Pack --
11730          ----------
11731
11732          --  pragma Pack (first_subtype_LOCAL_NAME);
11733
11734          when Pragma_Pack => Pack : declare
11735             Assoc   : constant Node_Id := Arg1;
11736             Type_Id : Node_Id;
11737             Typ     : Entity_Id;
11738             Ctyp    : Entity_Id;
11739             Ignore  : Boolean := False;
11740
11741          begin
11742             Check_No_Identifiers;
11743             Check_Arg_Count (1);
11744             Check_Arg_Is_Local_Name (Arg1);
11745
11746             Type_Id := Get_Pragma_Arg (Assoc);
11747             Find_Type (Type_Id);
11748             Typ := Entity (Type_Id);
11749
11750             if Typ = Any_Type
11751               or else Rep_Item_Too_Early (Typ, N)
11752             then
11753                return;
11754             else
11755                Typ := Underlying_Type (Typ);
11756             end if;
11757
11758             if not Is_Array_Type (Typ) and then not Is_Record_Type (Typ) then
11759                Error_Pragma ("pragma% must specify array or record type");
11760             end if;
11761
11762             Check_First_Subtype (Arg1);
11763             Check_Duplicate_Pragma (Typ);
11764
11765             --  Array type
11766
11767             if Is_Array_Type (Typ) then
11768                Ctyp := Component_Type (Typ);
11769
11770                --  Ignore pack that does nothing
11771
11772                if Known_Static_Esize (Ctyp)
11773                  and then Known_Static_RM_Size (Ctyp)
11774                  and then Esize (Ctyp) = RM_Size (Ctyp)
11775                  and then Addressable (Esize (Ctyp))
11776                then
11777                   Ignore := True;
11778                end if;
11779
11780                --  Process OK pragma Pack. Note that if there is a separate
11781                --  component clause present, the Pack will be cancelled. This
11782                --  processing is in Freeze.
11783
11784                if not Rep_Item_Too_Late (Typ, N) then
11785
11786                   --  In the context of static code analysis, we do not need
11787                   --  complex front-end expansions related to pragma Pack,
11788                   --  so disable handling of pragma Pack in these cases.
11789
11790                   if CodePeer_Mode or Alfa_Mode then
11791                      null;
11792
11793                   --  Don't attempt any packing for VM targets. We possibly
11794                   --  could deal with some cases of array bit-packing, but we
11795                   --  don't bother, since this is not a typical kind of
11796                   --  representation in the VM context anyway (and would not
11797                   --  for example work nicely with the debugger).
11798
11799                   elsif VM_Target /= No_VM then
11800                      if not GNAT_Mode then
11801                         Error_Pragma
11802                           ("?pragma% ignored in this configuration");
11803                      end if;
11804
11805                   --  Normal case where we do the pack action
11806
11807                   else
11808                      if not Ignore then
11809                         Set_Is_Packed            (Base_Type (Typ));
11810                         Set_Has_Non_Standard_Rep (Base_Type (Typ));
11811                      end if;
11812
11813                      Set_Has_Pragma_Pack (Base_Type (Typ));
11814                   end if;
11815                end if;
11816
11817             --  For record types, the pack is always effective
11818
11819             else pragma Assert (Is_Record_Type (Typ));
11820                if not Rep_Item_Too_Late (Typ, N) then
11821
11822                   --  Ignore pack request with warning in VM mode (skip warning
11823                   --  if we are compiling GNAT run time library).
11824
11825                   if VM_Target /= No_VM then
11826                      if not GNAT_Mode then
11827                         Error_Pragma
11828                           ("?pragma% ignored in this configuration");
11829                      end if;
11830
11831                   --  Normal case of pack request active
11832
11833                   else
11834                      Set_Is_Packed            (Base_Type (Typ));
11835                      Set_Has_Pragma_Pack      (Base_Type (Typ));
11836                      Set_Has_Non_Standard_Rep (Base_Type (Typ));
11837                   end if;
11838                end if;
11839             end if;
11840          end Pack;
11841
11842          ----------
11843          -- Page --
11844          ----------
11845
11846          --  pragma Page;
11847
11848          --  There is nothing to do here, since we did all the processing for
11849          --  this pragma in Par.Prag (so that it works properly even in syntax
11850          --  only mode).
11851
11852          when Pragma_Page =>
11853             null;
11854
11855          -------------
11856          -- Passive --
11857          -------------
11858
11859          --  pragma Passive [(PASSIVE_FORM)];
11860
11861          --  PASSIVE_FORM ::= Semaphore | No
11862
11863          when Pragma_Passive =>
11864             GNAT_Pragma;
11865
11866             if Nkind (Parent (N)) /= N_Task_Definition then
11867                Error_Pragma ("pragma% must be within task definition");
11868             end if;
11869
11870             if Arg_Count /= 0 then
11871                Check_Arg_Count (1);
11872                Check_Arg_Is_One_Of (Arg1, Name_Semaphore, Name_No);
11873             end if;
11874
11875          ----------------------------------
11876          -- Preelaborable_Initialization --
11877          ----------------------------------
11878
11879          --  pragma Preelaborable_Initialization (DIRECT_NAME);
11880
11881          when Pragma_Preelaborable_Initialization => Preelab_Init : declare
11882             Ent : Entity_Id;
11883
11884          begin
11885             Ada_2005_Pragma;
11886             Check_Arg_Count (1);
11887             Check_No_Identifiers;
11888             Check_Arg_Is_Identifier (Arg1);
11889             Check_Arg_Is_Local_Name (Arg1);
11890             Check_First_Subtype (Arg1);
11891             Ent := Entity (Get_Pragma_Arg (Arg1));
11892
11893             if not (Is_Private_Type (Ent)
11894                       or else
11895                     Is_Protected_Type (Ent)
11896                       or else
11897                     (Is_Generic_Type (Ent) and then Is_Derived_Type (Ent)))
11898             then
11899                Error_Pragma_Arg
11900                  ("pragma % can only be applied to private, formal derived or "
11901                   & "protected type",
11902                   Arg1);
11903             end if;
11904
11905             --  Give an error if the pragma is applied to a protected type that
11906             --  does not qualify (due to having entries, or due to components
11907             --  that do not qualify).
11908
11909             if Is_Protected_Type (Ent)
11910               and then not Has_Preelaborable_Initialization (Ent)
11911             then
11912                Error_Msg_N
11913                  ("protected type & does not have preelaborable " &
11914                   "initialization", Ent);
11915
11916             --  Otherwise mark the type as definitely having preelaborable
11917             --  initialization.
11918
11919             else
11920                Set_Known_To_Have_Preelab_Init (Ent);
11921             end if;
11922
11923             if Has_Pragma_Preelab_Init (Ent)
11924               and then Warn_On_Redundant_Constructs
11925             then
11926                Error_Pragma ("?duplicate pragma%!");
11927             else
11928                Set_Has_Pragma_Preelab_Init (Ent);
11929             end if;
11930          end Preelab_Init;
11931
11932          --------------------
11933          -- Persistent_BSS --
11934          --------------------
11935
11936          --  pragma Persistent_BSS [(object_NAME)];
11937
11938          when Pragma_Persistent_BSS => Persistent_BSS :  declare
11939             Decl : Node_Id;
11940             Ent  : Entity_Id;
11941             Prag : Node_Id;
11942
11943          begin
11944             GNAT_Pragma;
11945             Check_At_Most_N_Arguments (1);
11946
11947             --  Case of application to specific object (one argument)
11948
11949             if Arg_Count = 1 then
11950                Check_Arg_Is_Library_Level_Local_Name (Arg1);
11951
11952                if not Is_Entity_Name (Get_Pragma_Arg (Arg1))
11953                  or else not
11954                   Ekind_In (Entity (Get_Pragma_Arg (Arg1)), E_Variable,
11955                                                             E_Constant)
11956                then
11957                   Error_Pragma_Arg ("pragma% only applies to objects", Arg1);
11958                end if;
11959
11960                Ent := Entity (Get_Pragma_Arg (Arg1));
11961                Decl := Parent (Ent);
11962
11963                if Rep_Item_Too_Late (Ent, N) then
11964                   return;
11965                end if;
11966
11967                if Present (Expression (Decl)) then
11968                   Error_Pragma_Arg
11969                     ("object for pragma% cannot have initialization", Arg1);
11970                end if;
11971
11972                if not Is_Potentially_Persistent_Type (Etype (Ent)) then
11973                   Error_Pragma_Arg
11974                     ("object type for pragma% is not potentially persistent",
11975                      Arg1);
11976                end if;
11977
11978                Check_Duplicate_Pragma (Ent);
11979
11980                Prag :=
11981                  Make_Linker_Section_Pragma
11982                    (Ent, Sloc (N), ".persistent.bss");
11983                Insert_After (N, Prag);
11984                Analyze (Prag);
11985
11986             --  Case of use as configuration pragma with no arguments
11987
11988             else
11989                Check_Valid_Configuration_Pragma;
11990                Persistent_BSS_Mode := True;
11991             end if;
11992          end Persistent_BSS;
11993
11994          -------------
11995          -- Polling --
11996          -------------
11997
11998          --  pragma Polling (ON | OFF);
11999
12000          when Pragma_Polling =>
12001             GNAT_Pragma;
12002             Check_Arg_Count (1);
12003             Check_No_Identifiers;
12004             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
12005             Polling_Required := (Chars (Get_Pragma_Arg (Arg1)) = Name_On);
12006
12007          -------------------
12008          -- Postcondition --
12009          -------------------
12010
12011          --  pragma Postcondition ([Check   =>] Boolean_EXPRESSION
12012          --                      [,[Message =>] String_EXPRESSION]);
12013
12014          when Pragma_Postcondition => Postcondition : declare
12015             In_Body : Boolean;
12016             pragma Warnings (Off, In_Body);
12017
12018          begin
12019             GNAT_Pragma;
12020             Check_At_Least_N_Arguments (1);
12021             Check_At_Most_N_Arguments (2);
12022             Check_Optional_Identifier (Arg1, Name_Check);
12023
12024             --  All we need to do here is call the common check procedure,
12025             --  the remainder of the processing is found in Sem_Ch6/Sem_Ch7.
12026
12027             Check_Precondition_Postcondition (In_Body);
12028          end Postcondition;
12029
12030          ------------------
12031          -- Precondition --
12032          ------------------
12033
12034          --  pragma Precondition ([Check   =>] Boolean_EXPRESSION
12035          --                     [,[Message =>] String_EXPRESSION]);
12036
12037          when Pragma_Precondition => Precondition : declare
12038             In_Body : Boolean;
12039
12040          begin
12041             GNAT_Pragma;
12042             Check_At_Least_N_Arguments (1);
12043             Check_At_Most_N_Arguments (2);
12044             Check_Optional_Identifier (Arg1, Name_Check);
12045             Check_Precondition_Postcondition (In_Body);
12046
12047             --  If in spec, nothing more to do. If in body, then we convert the
12048             --  pragma to pragma Check (Precondition, cond [, msg]). Note we do
12049             --  this whether or not precondition checks are enabled. That works
12050             --  fine since pragma Check will do this check, and will also
12051             --  analyze the condition itself in the proper context.
12052
12053             if In_Body then
12054                Rewrite (N,
12055                  Make_Pragma (Loc,
12056                    Chars => Name_Check,
12057                    Pragma_Argument_Associations => New_List (
12058                      Make_Pragma_Argument_Association (Loc,
12059                        Expression => Make_Identifier (Loc, Name_Precondition)),
12060
12061                      Make_Pragma_Argument_Association (Sloc (Arg1),
12062                        Expression => Relocate_Node (Get_Pragma_Arg (Arg1))))));
12063
12064                if Arg_Count = 2 then
12065                   Append_To (Pragma_Argument_Associations (N),
12066                     Make_Pragma_Argument_Association (Sloc (Arg2),
12067                       Expression => Relocate_Node (Get_Pragma_Arg (Arg2))));
12068                end if;
12069
12070                Analyze (N);
12071             end if;
12072          end Precondition;
12073
12074          ---------------
12075          -- Predicate --
12076          ---------------
12077
12078          --  pragma Predicate
12079          --    ([Entity =>] type_LOCAL_NAME,
12080          --     [Check  =>] EXPRESSION);
12081
12082          when Pragma_Predicate => Predicate : declare
12083             Type_Id : Node_Id;
12084             Typ     : Entity_Id;
12085
12086             Discard : Boolean;
12087             pragma Unreferenced (Discard);
12088
12089          begin
12090             GNAT_Pragma;
12091             Check_Arg_Count (2);
12092             Check_Optional_Identifier (Arg1, Name_Entity);
12093             Check_Optional_Identifier (Arg2, Name_Check);
12094
12095             Check_Arg_Is_Local_Name (Arg1);
12096
12097             Type_Id := Get_Pragma_Arg (Arg1);
12098             Find_Type (Type_Id);
12099             Typ := Entity (Type_Id);
12100
12101             if Typ = Any_Type then
12102                return;
12103             end if;
12104
12105             --  The remaining processing is simply to link the pragma on to
12106             --  the rep item chain, for processing when the type is frozen.
12107             --  This is accomplished by a call to Rep_Item_Too_Late. We also
12108             --  mark the type as having predicates.
12109
12110             Set_Has_Predicates (Typ);
12111             Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
12112          end Predicate;
12113
12114          ------------------
12115          -- Preelaborate --
12116          ------------------
12117
12118          --  pragma Preelaborate [(library_unit_NAME)];
12119
12120          --  Set the flag Is_Preelaborated of program unit name entity
12121
12122          when Pragma_Preelaborate => Preelaborate : declare
12123             Pa  : constant Node_Id   := Parent (N);
12124             Pk  : constant Node_Kind := Nkind (Pa);
12125             Ent : Entity_Id;
12126
12127          begin
12128             Check_Ada_83_Warning;
12129             Check_Valid_Library_Unit_Pragma;
12130
12131             if Nkind (N) = N_Null_Statement then
12132                return;
12133             end if;
12134
12135             Ent := Find_Lib_Unit_Name;
12136             Check_Duplicate_Pragma (Ent);
12137
12138             --  This filters out pragmas inside generic parent then
12139             --  show up inside instantiation
12140
12141             if Present (Ent)
12142               and then not (Pk = N_Package_Specification
12143                              and then Present (Generic_Parent (Pa)))
12144             then
12145                if not Debug_Flag_U then
12146                   Set_Is_Preelaborated (Ent);
12147                   Set_Suppress_Elaboration_Warnings (Ent);
12148                end if;
12149             end if;
12150          end Preelaborate;
12151
12152          ---------------------
12153          -- Preelaborate_05 --
12154          ---------------------
12155
12156          --  pragma Preelaborate_05 [(library_unit_NAME)];
12157
12158          --  This pragma is useable only in GNAT_Mode, where it is used like
12159          --  pragma Preelaborate but it is only effective in Ada 2005 mode
12160          --  (otherwise it is ignored). This is used to implement AI-362 which
12161          --  recategorizes some run-time packages in Ada 2005 mode.
12162
12163          when Pragma_Preelaborate_05 => Preelaborate_05 : declare
12164             Ent : Entity_Id;
12165
12166          begin
12167             GNAT_Pragma;
12168             Check_Valid_Library_Unit_Pragma;
12169
12170             if not GNAT_Mode then
12171                Error_Pragma ("pragma% only available in GNAT mode");
12172             end if;
12173
12174             if Nkind (N) = N_Null_Statement then
12175                return;
12176             end if;
12177
12178             --  This is one of the few cases where we need to test the value of
12179             --  Ada_Version_Explicit rather than Ada_Version (which is always
12180             --  set to Ada_2012 in a predefined unit), we need to know the
12181             --  explicit version set to know if this pragma is active.
12182
12183             if Ada_Version_Explicit >= Ada_2005 then
12184                Ent := Find_Lib_Unit_Name;
12185                Set_Is_Preelaborated (Ent);
12186                Set_Suppress_Elaboration_Warnings (Ent);
12187             end if;
12188          end Preelaborate_05;
12189
12190          --------------
12191          -- Priority --
12192          --------------
12193
12194          --  pragma Priority (EXPRESSION);
12195
12196          when Pragma_Priority => Priority : declare
12197             P   : constant Node_Id := Parent (N);
12198             Arg : Node_Id;
12199
12200          begin
12201             Check_No_Identifiers;
12202             Check_Arg_Count (1);
12203
12204             --  Subprogram case
12205
12206             if Nkind (P) = N_Subprogram_Body then
12207                Check_In_Main_Program;
12208
12209                Arg := Get_Pragma_Arg (Arg1);
12210                Analyze_And_Resolve (Arg, Standard_Integer);
12211
12212                --  Must be static
12213
12214                if not Is_Static_Expression (Arg) then
12215                   Flag_Non_Static_Expr
12216                     ("main subprogram priority is not static!", Arg);
12217                   raise Pragma_Exit;
12218
12219                --  If constraint error, then we already signalled an error
12220
12221                elsif Raises_Constraint_Error (Arg) then
12222                   null;
12223
12224                --  Otherwise check in range
12225
12226                else
12227                   declare
12228                      Val : constant Uint := Expr_Value (Arg);
12229
12230                   begin
12231                      if Val < 0
12232                        or else Val > Expr_Value (Expression
12233                                        (Parent (RTE (RE_Max_Priority))))
12234                      then
12235                         Error_Pragma_Arg
12236                           ("main subprogram priority is out of range", Arg1);
12237                      end if;
12238                   end;
12239                end if;
12240
12241                Set_Main_Priority
12242                     (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
12243
12244                --  Load an arbitrary entity from System.Tasking to make sure
12245                --  this package is implicitly with'ed, since we need to have
12246                --  the tasking run-time active for the pragma Priority to have
12247                --  any effect.
12248
12249                declare
12250                   Discard : Entity_Id;
12251                   pragma Warnings (Off, Discard);
12252                begin
12253                   Discard := RTE (RE_Task_List);
12254                end;
12255
12256             --  Task or Protected, must be of type Integer
12257
12258             elsif Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
12259                Arg := Get_Pragma_Arg (Arg1);
12260
12261                --  The expression must be analyzed in the special manner
12262                --  described in "Handling of Default and Per-Object
12263                --  Expressions" in sem.ads.
12264
12265                Preanalyze_Spec_Expression (Arg, Standard_Integer);
12266
12267                if not Is_Static_Expression (Arg) then
12268                   Check_Restriction (Static_Priorities, Arg);
12269                end if;
12270
12271             --  Anything else is incorrect
12272
12273             else
12274                Pragma_Misplaced;
12275             end if;
12276
12277             if Has_Pragma_Priority (P) then
12278                Error_Pragma ("duplicate pragma% not allowed");
12279             else
12280                Set_Has_Pragma_Priority (P, True);
12281
12282                if Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
12283                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
12284                   --  exp_ch9 should use this ???
12285                end if;
12286             end if;
12287          end Priority;
12288
12289          -----------------------------------
12290          -- Priority_Specific_Dispatching --
12291          -----------------------------------
12292
12293          --  pragma Priority_Specific_Dispatching (
12294          --    policy_IDENTIFIER,
12295          --    first_priority_EXPRESSION,
12296          --    last_priority_EXPRESSION);
12297
12298          when Pragma_Priority_Specific_Dispatching =>
12299          Priority_Specific_Dispatching : declare
12300             Prio_Id : constant Entity_Id := RTE (RE_Any_Priority);
12301             --  This is the entity System.Any_Priority;
12302
12303             DP          : Character;
12304             Lower_Bound : Node_Id;
12305             Upper_Bound : Node_Id;
12306             Lower_Val   : Uint;
12307             Upper_Val   : Uint;
12308
12309          begin
12310             Ada_2005_Pragma;
12311             Check_Arg_Count (3);
12312             Check_No_Identifiers;
12313             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
12314             Check_Valid_Configuration_Pragma;
12315             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
12316             DP := Fold_Upper (Name_Buffer (1));
12317
12318             Lower_Bound := Get_Pragma_Arg (Arg2);
12319             Check_Arg_Is_Static_Expression (Lower_Bound, Standard_Integer);
12320             Lower_Val := Expr_Value (Lower_Bound);
12321
12322             Upper_Bound := Get_Pragma_Arg (Arg3);
12323             Check_Arg_Is_Static_Expression (Upper_Bound, Standard_Integer);
12324             Upper_Val := Expr_Value (Upper_Bound);
12325
12326             --  It is not allowed to use Task_Dispatching_Policy and
12327             --  Priority_Specific_Dispatching in the same partition.
12328
12329             if Task_Dispatching_Policy /= ' ' then
12330                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
12331                Error_Pragma
12332                  ("pragma% incompatible with Task_Dispatching_Policy#");
12333
12334             --  Check lower bound in range
12335
12336             elsif Lower_Val < Expr_Value (Type_Low_Bound (Prio_Id))
12337                     or else
12338                   Lower_Val > Expr_Value (Type_High_Bound (Prio_Id))
12339             then
12340                Error_Pragma_Arg
12341                  ("first_priority is out of range", Arg2);
12342
12343             --  Check upper bound in range
12344
12345             elsif Upper_Val < Expr_Value (Type_Low_Bound (Prio_Id))
12346                     or else
12347                   Upper_Val > Expr_Value (Type_High_Bound (Prio_Id))
12348             then
12349                Error_Pragma_Arg
12350                  ("last_priority is out of range", Arg3);
12351
12352             --  Check that the priority range is valid
12353
12354             elsif Lower_Val > Upper_Val then
12355                Error_Pragma
12356                  ("last_priority_expression must be greater than" &
12357                   " or equal to first_priority_expression");
12358
12359             --  Store the new policy, but always preserve System_Location since
12360             --  we like the error message with the run-time name.
12361
12362             else
12363                --  Check overlapping in the priority ranges specified in other
12364                --  Priority_Specific_Dispatching pragmas within the same
12365                --  partition. We can only check those we know about!
12366
12367                for J in
12368                   Specific_Dispatching.First .. Specific_Dispatching.Last
12369                loop
12370                   if Specific_Dispatching.Table (J).First_Priority in
12371                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
12372                   or else Specific_Dispatching.Table (J).Last_Priority in
12373                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
12374                   then
12375                      Error_Msg_Sloc :=
12376                        Specific_Dispatching.Table (J).Pragma_Loc;
12377                         Error_Pragma
12378                           ("priority range overlaps with "
12379                            & "Priority_Specific_Dispatching#");
12380                   end if;
12381                end loop;
12382
12383                --  The use of Priority_Specific_Dispatching is incompatible
12384                --  with Task_Dispatching_Policy.
12385
12386                if Task_Dispatching_Policy /= ' ' then
12387                   Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
12388                      Error_Pragma
12389                        ("Priority_Specific_Dispatching incompatible "
12390                         & "with Task_Dispatching_Policy#");
12391                end if;
12392
12393                --  The use of Priority_Specific_Dispatching forces ceiling
12394                --  locking policy.
12395
12396                if Locking_Policy /= ' ' and then Locking_Policy /= 'C' then
12397                   Error_Msg_Sloc := Locking_Policy_Sloc;
12398                      Error_Pragma
12399                        ("Priority_Specific_Dispatching incompatible "
12400                         & "with Locking_Policy#");
12401
12402                --  Set the Ceiling_Locking policy, but preserve System_Location
12403                --  since we like the error message with the run time name.
12404
12405                else
12406                   Locking_Policy := 'C';
12407
12408                   if Locking_Policy_Sloc /= System_Location then
12409                      Locking_Policy_Sloc := Loc;
12410                   end if;
12411                end if;
12412
12413                --  Add entry in the table
12414
12415                Specific_Dispatching.Append
12416                     ((Dispatching_Policy => DP,
12417                       First_Priority     => UI_To_Int (Lower_Val),
12418                       Last_Priority      => UI_To_Int (Upper_Val),
12419                       Pragma_Loc         => Loc));
12420             end if;
12421          end Priority_Specific_Dispatching;
12422
12423          -------------
12424          -- Profile --
12425          -------------
12426
12427          --  pragma Profile (profile_IDENTIFIER);
12428
12429          --  profile_IDENTIFIER => Restricted | Ravenscar
12430
12431          when Pragma_Profile =>
12432             Ada_2005_Pragma;
12433             Check_Arg_Count (1);
12434             Check_Valid_Configuration_Pragma;
12435             Check_No_Identifiers;
12436
12437             declare
12438                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
12439
12440             begin
12441                if Chars (Argx) = Name_Ravenscar then
12442                   Set_Ravenscar_Profile (N);
12443
12444                elsif Chars (Argx) = Name_Restricted then
12445                   Set_Profile_Restrictions
12446                     (Restricted,
12447                      N, Warn => Treat_Restrictions_As_Warnings);
12448
12449                elsif Chars (Argx) = Name_No_Implementation_Extensions then
12450                   Set_Profile_Restrictions
12451                     (No_Implementation_Extensions,
12452                      N, Warn => Treat_Restrictions_As_Warnings);
12453
12454                else
12455                   Error_Pragma_Arg ("& is not a valid profile", Argx);
12456                end if;
12457             end;
12458
12459          ----------------------
12460          -- Profile_Warnings --
12461          ----------------------
12462
12463          --  pragma Profile_Warnings (profile_IDENTIFIER);
12464
12465          --  profile_IDENTIFIER => Restricted | Ravenscar
12466
12467          when Pragma_Profile_Warnings =>
12468             GNAT_Pragma;
12469             Check_Arg_Count (1);
12470             Check_Valid_Configuration_Pragma;
12471             Check_No_Identifiers;
12472
12473             declare
12474                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
12475
12476             begin
12477                if Chars (Argx) = Name_Ravenscar then
12478                   Set_Profile_Restrictions (Ravenscar, N, Warn => True);
12479
12480                elsif Chars (Argx) = Name_Restricted then
12481                   Set_Profile_Restrictions (Restricted, N, Warn => True);
12482
12483                elsif Chars (Argx) = Name_No_Implementation_Extensions then
12484                   Set_Profile_Restrictions
12485                     (No_Implementation_Extensions, N, Warn => True);
12486
12487                else
12488                   Error_Pragma_Arg ("& is not a valid profile", Argx);
12489                end if;
12490             end;
12491
12492          --------------------------
12493          -- Propagate_Exceptions --
12494          --------------------------
12495
12496          --  pragma Propagate_Exceptions;
12497
12498          --  Note: this pragma is obsolete and has no effect
12499
12500          when Pragma_Propagate_Exceptions =>
12501             GNAT_Pragma;
12502             Check_Arg_Count (0);
12503
12504             if In_Extended_Main_Source_Unit (N) then
12505                Propagate_Exceptions := True;
12506             end if;
12507
12508          ------------------
12509          -- Psect_Object --
12510          ------------------
12511
12512          --  pragma Psect_Object (
12513          --        [Internal =>] LOCAL_NAME,
12514          --     [, [External =>] EXTERNAL_SYMBOL]
12515          --     [, [Size     =>] EXTERNAL_SYMBOL]);
12516
12517          when Pragma_Psect_Object | Pragma_Common_Object =>
12518          Psect_Object : declare
12519             Args  : Args_List (1 .. 3);
12520             Names : constant Name_List (1 .. 3) := (
12521                       Name_Internal,
12522                       Name_External,
12523                       Name_Size);
12524
12525             Internal : Node_Id renames Args (1);
12526             External : Node_Id renames Args (2);
12527             Size     : Node_Id renames Args (3);
12528
12529             Def_Id : Entity_Id;
12530
12531             procedure Check_Too_Long (Arg : Node_Id);
12532             --  Posts message if the argument is an identifier with more
12533             --  than 31 characters, or a string literal with more than
12534             --  31 characters, and we are operating under VMS
12535
12536             --------------------
12537             -- Check_Too_Long --
12538             --------------------
12539
12540             procedure Check_Too_Long (Arg : Node_Id) is
12541                X : constant Node_Id := Original_Node (Arg);
12542
12543             begin
12544                if not Nkind_In (X, N_String_Literal, N_Identifier) then
12545                   Error_Pragma_Arg
12546                     ("inappropriate argument for pragma %", Arg);
12547                end if;
12548
12549                if OpenVMS_On_Target then
12550                   if (Nkind (X) = N_String_Literal
12551                        and then String_Length (Strval (X)) > 31)
12552                     or else
12553                      (Nkind (X) = N_Identifier
12554                        and then Length_Of_Name (Chars (X)) > 31)
12555                   then
12556                      Error_Pragma_Arg
12557                        ("argument for pragma % is longer than 31 characters",
12558                         Arg);
12559                   end if;
12560                end if;
12561             end Check_Too_Long;
12562
12563          --  Start of processing for Common_Object/Psect_Object
12564
12565          begin
12566             GNAT_Pragma;
12567             Gather_Associations (Names, Args);
12568             Process_Extended_Import_Export_Internal_Arg (Internal);
12569
12570             Def_Id := Entity (Internal);
12571
12572             if not Ekind_In (Def_Id, E_Constant, E_Variable) then
12573                Error_Pragma_Arg
12574                  ("pragma% must designate an object", Internal);
12575             end if;
12576
12577             Check_Too_Long (Internal);
12578
12579             if Is_Imported (Def_Id) or else Is_Exported (Def_Id) then
12580                Error_Pragma_Arg
12581                  ("cannot use pragma% for imported/exported object",
12582                   Internal);
12583             end if;
12584
12585             if Is_Concurrent_Type (Etype (Internal)) then
12586                Error_Pragma_Arg
12587                  ("cannot specify pragma % for task/protected object",
12588                   Internal);
12589             end if;
12590
12591             if Has_Rep_Pragma (Def_Id, Name_Common_Object)
12592                  or else
12593                Has_Rep_Pragma (Def_Id, Name_Psect_Object)
12594             then
12595                Error_Msg_N ("?duplicate Common/Psect_Object pragma", N);
12596             end if;
12597
12598             if Ekind (Def_Id) = E_Constant then
12599                Error_Pragma_Arg
12600                  ("cannot specify pragma % for a constant", Internal);
12601             end if;
12602
12603             if Is_Record_Type (Etype (Internal)) then
12604                declare
12605                   Ent  : Entity_Id;
12606                   Decl : Entity_Id;
12607
12608                begin
12609                   Ent := First_Entity (Etype (Internal));
12610                   while Present (Ent) loop
12611                      Decl := Declaration_Node (Ent);
12612
12613                      if Ekind (Ent) = E_Component
12614                        and then Nkind (Decl) = N_Component_Declaration
12615                        and then Present (Expression (Decl))
12616                        and then Warn_On_Export_Import
12617                      then
12618                         Error_Msg_N
12619                           ("?object for pragma % has defaults", Internal);
12620                         exit;
12621
12622                      else
12623                         Next_Entity (Ent);
12624                      end if;
12625                   end loop;
12626                end;
12627             end if;
12628
12629             if Present (Size) then
12630                Check_Too_Long (Size);
12631             end if;
12632
12633             if Present (External) then
12634                Check_Arg_Is_External_Name (External);
12635                Check_Too_Long (External);
12636             end if;
12637
12638             --  If all error tests pass, link pragma on to the rep item chain
12639
12640             Record_Rep_Item (Def_Id, N);
12641          end Psect_Object;
12642
12643          ----------
12644          -- Pure --
12645          ----------
12646
12647          --  pragma Pure [(library_unit_NAME)];
12648
12649          when Pragma_Pure => Pure : declare
12650             Ent : Entity_Id;
12651
12652          begin
12653             Check_Ada_83_Warning;
12654             Check_Valid_Library_Unit_Pragma;
12655
12656             if Nkind (N) = N_Null_Statement then
12657                return;
12658             end if;
12659
12660             Ent := Find_Lib_Unit_Name;
12661             Set_Is_Pure (Ent);
12662             Set_Has_Pragma_Pure (Ent);
12663             Set_Suppress_Elaboration_Warnings (Ent);
12664          end Pure;
12665
12666          -------------
12667          -- Pure_05 --
12668          -------------
12669
12670          --  pragma Pure_05 [(library_unit_NAME)];
12671
12672          --  This pragma is useable only in GNAT_Mode, where it is used like
12673          --  pragma Pure but it is only effective in Ada 2005 mode (otherwise
12674          --  it is ignored). It may be used after a pragma Preelaborate, in
12675          --  which case it overrides the effect of the pragma Preelaborate.
12676          --  This is used to implement AI-362 which recategorizes some run-time
12677          --  packages in Ada 2005 mode.
12678
12679          when Pragma_Pure_05 => Pure_05 : declare
12680             Ent : Entity_Id;
12681
12682          begin
12683             GNAT_Pragma;
12684             Check_Valid_Library_Unit_Pragma;
12685
12686             if not GNAT_Mode then
12687                Error_Pragma ("pragma% only available in GNAT mode");
12688             end if;
12689
12690             if Nkind (N) = N_Null_Statement then
12691                return;
12692             end if;
12693
12694             --  This is one of the few cases where we need to test the value of
12695             --  Ada_Version_Explicit rather than Ada_Version (which is always
12696             --  set to Ada_2012 in a predefined unit), we need to know the
12697             --  explicit version set to know if this pragma is active.
12698
12699             if Ada_Version_Explicit >= Ada_2005 then
12700                Ent := Find_Lib_Unit_Name;
12701                Set_Is_Preelaborated (Ent, False);
12702                Set_Is_Pure (Ent);
12703                Set_Suppress_Elaboration_Warnings (Ent);
12704             end if;
12705          end Pure_05;
12706
12707          -------------
12708          -- Pure_12 --
12709          -------------
12710
12711          --  pragma Pure_12 [(library_unit_NAME)];
12712
12713          --  This pragma is useable only in GNAT_Mode, where it is used like
12714          --  pragma Pure but it is only effective in Ada 2012 mode (otherwise
12715          --  it is ignored). It may be used after a pragma Preelaborate, in
12716          --  which case it overrides the effect of the pragma Preelaborate.
12717          --  This is used to implement AI05-0212 which recategorizes some
12718          --  run-time packages in Ada 2012 mode.
12719
12720          when Pragma_Pure_12 => Pure_12 : declare
12721             Ent : Entity_Id;
12722
12723          begin
12724             GNAT_Pragma;
12725             Check_Valid_Library_Unit_Pragma;
12726
12727             if not GNAT_Mode then
12728                Error_Pragma ("pragma% only available in GNAT mode");
12729             end if;
12730
12731             if Nkind (N) = N_Null_Statement then
12732                return;
12733             end if;
12734
12735             --  This is one of the few cases where we need to test the value of
12736             --  Ada_Version_Explicit rather than Ada_Version (which is always
12737             --  set to Ada_2012 in a predefined unit), we need to know the
12738             --  explicit version set to know if this pragma is active.
12739
12740             if Ada_Version_Explicit >= Ada_2012 then
12741                Ent := Find_Lib_Unit_Name;
12742                Set_Is_Preelaborated (Ent, False);
12743                Set_Is_Pure (Ent);
12744                Set_Suppress_Elaboration_Warnings (Ent);
12745             end if;
12746          end Pure_12;
12747
12748          -------------------
12749          -- Pure_Function --
12750          -------------------
12751
12752          --  pragma Pure_Function ([Entity =>] function_LOCAL_NAME);
12753
12754          when Pragma_Pure_Function => Pure_Function : declare
12755             E_Id      : Node_Id;
12756             E         : Entity_Id;
12757             Def_Id    : Entity_Id;
12758             Effective : Boolean := False;
12759
12760          begin
12761             GNAT_Pragma;
12762             Check_Arg_Count (1);
12763             Check_Optional_Identifier (Arg1, Name_Entity);
12764             Check_Arg_Is_Local_Name (Arg1);
12765             E_Id := Get_Pragma_Arg (Arg1);
12766
12767             if Error_Posted (E_Id) then
12768                return;
12769             end if;
12770
12771             --  Loop through homonyms (overloadings) of referenced entity
12772
12773             E := Entity (E_Id);
12774
12775             if Present (E) then
12776                loop
12777                   Def_Id := Get_Base_Subprogram (E);
12778
12779                   if not Ekind_In (Def_Id, E_Function,
12780                                            E_Generic_Function,
12781                                            E_Operator)
12782                   then
12783                      Error_Pragma_Arg
12784                        ("pragma% requires a function name", Arg1);
12785                   end if;
12786
12787                   Set_Is_Pure (Def_Id);
12788
12789                   if not Has_Pragma_Pure_Function (Def_Id) then
12790                      Set_Has_Pragma_Pure_Function (Def_Id);
12791                      Effective := True;
12792                   end if;
12793
12794                   exit when From_Aspect_Specification (N);
12795                   E := Homonym (E);
12796                   exit when No (E) or else Scope (E) /= Current_Scope;
12797                end loop;
12798
12799                if not Effective
12800                  and then Warn_On_Redundant_Constructs
12801                then
12802                   Error_Msg_NE
12803                     ("pragma Pure_Function on& is redundant?",
12804                      N, Entity (E_Id));
12805                end if;
12806             end if;
12807          end Pure_Function;
12808
12809          --------------------
12810          -- Queuing_Policy --
12811          --------------------
12812
12813          --  pragma Queuing_Policy (policy_IDENTIFIER);
12814
12815          when Pragma_Queuing_Policy => declare
12816             QP : Character;
12817
12818          begin
12819             Check_Ada_83_Warning;
12820             Check_Arg_Count (1);
12821             Check_No_Identifiers;
12822             Check_Arg_Is_Queuing_Policy (Arg1);
12823             Check_Valid_Configuration_Pragma;
12824             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
12825             QP := Fold_Upper (Name_Buffer (1));
12826
12827             if Queuing_Policy /= ' '
12828               and then Queuing_Policy /= QP
12829             then
12830                Error_Msg_Sloc := Queuing_Policy_Sloc;
12831                Error_Pragma ("queuing policy incompatible with policy#");
12832
12833             --  Set new policy, but always preserve System_Location since we
12834             --  like the error message with the run time name.
12835
12836             else
12837                Queuing_Policy := QP;
12838
12839                if Queuing_Policy_Sloc /= System_Location then
12840                   Queuing_Policy_Sloc := Loc;
12841                end if;
12842             end if;
12843          end;
12844
12845          -----------------------
12846          -- Relative_Deadline --
12847          -----------------------
12848
12849          --  pragma Relative_Deadline (time_span_EXPRESSION);
12850
12851          when Pragma_Relative_Deadline => Relative_Deadline : declare
12852             P   : constant Node_Id := Parent (N);
12853             Arg : Node_Id;
12854
12855          begin
12856             Ada_2005_Pragma;
12857             Check_No_Identifiers;
12858             Check_Arg_Count (1);
12859
12860             Arg := Get_Pragma_Arg (Arg1);
12861
12862             --  The expression must be analyzed in the special manner described
12863             --  in "Handling of Default and Per-Object Expressions" in sem.ads.
12864
12865             Preanalyze_Spec_Expression (Arg, RTE (RE_Time_Span));
12866
12867             --  Subprogram case
12868
12869             if Nkind (P) = N_Subprogram_Body then
12870                Check_In_Main_Program;
12871
12872             --  Tasks
12873
12874             elsif Nkind (P) = N_Task_Definition then
12875                null;
12876
12877             --  Anything else is incorrect
12878
12879             else
12880                Pragma_Misplaced;
12881             end if;
12882
12883             if Has_Relative_Deadline_Pragma (P) then
12884                Error_Pragma ("duplicate pragma% not allowed");
12885             else
12886                Set_Has_Relative_Deadline_Pragma (P, True);
12887
12888                if Nkind (P) = N_Task_Definition then
12889                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
12890                end if;
12891             end if;
12892          end Relative_Deadline;
12893
12894          ------------------------
12895          -- Remote_Access_Type --
12896          ------------------------
12897
12898          --  pragma Remote_Access_Type ([Entity =>] formal_type_LOCAL_NAME);
12899
12900          when Pragma_Remote_Access_Type => Remote_Access_Type : declare
12901             E : Entity_Id;
12902
12903          begin
12904             GNAT_Pragma;
12905             Check_Arg_Count (1);
12906             Check_Optional_Identifier (Arg1, Name_Entity);
12907             Check_Arg_Is_Local_Name (Arg1);
12908
12909             E := Entity (Get_Pragma_Arg (Arg1));
12910
12911             if Nkind (Parent (E)) = N_Formal_Type_Declaration
12912               and then Ekind (E) = E_General_Access_Type
12913               and then Is_Class_Wide_Type (Directly_Designated_Type (E))
12914               and then Scope (Root_Type (Directly_Designated_Type (E)))
12915                          = Scope (E)
12916               and then Is_Valid_Remote_Object_Type
12917                          (Root_Type (Directly_Designated_Type (E)))
12918             then
12919                Set_Is_Remote_Types (E);
12920
12921             else
12922                Error_Pragma_Arg
12923                  ("pragma% applies only to formal access to classwide types",
12924                   Arg1);
12925             end if;
12926          end Remote_Access_Type;
12927
12928          ---------------------------
12929          -- Remote_Call_Interface --
12930          ---------------------------
12931
12932          --  pragma Remote_Call_Interface [(library_unit_NAME)];
12933
12934          when Pragma_Remote_Call_Interface => Remote_Call_Interface : declare
12935             Cunit_Node : Node_Id;
12936             Cunit_Ent  : Entity_Id;
12937             K          : Node_Kind;
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             K          := Nkind (Unit (Cunit_Node));
12949             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12950
12951             if K = N_Package_Declaration
12952               or else K = N_Generic_Package_Declaration
12953               or else K = N_Subprogram_Declaration
12954               or else K = N_Generic_Subprogram_Declaration
12955               or else (K = N_Subprogram_Body
12956                          and then Acts_As_Spec (Unit (Cunit_Node)))
12957             then
12958                null;
12959             else
12960                Error_Pragma (
12961                  "pragma% must apply to package or subprogram declaration");
12962             end if;
12963
12964             Set_Is_Remote_Call_Interface (Cunit_Ent);
12965          end Remote_Call_Interface;
12966
12967          ------------------
12968          -- Remote_Types --
12969          ------------------
12970
12971          --  pragma Remote_Types [(library_unit_NAME)];
12972
12973          when Pragma_Remote_Types => Remote_Types : declare
12974             Cunit_Node : Node_Id;
12975             Cunit_Ent  : Entity_Id;
12976
12977          begin
12978             Check_Ada_83_Warning;
12979             Check_Valid_Library_Unit_Pragma;
12980
12981             if Nkind (N) = N_Null_Statement then
12982                return;
12983             end if;
12984
12985             Cunit_Node := Cunit (Current_Sem_Unit);
12986             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12987
12988             if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
12989                                                 N_Generic_Package_Declaration)
12990             then
12991                Error_Pragma
12992                  ("pragma% can only apply to a package declaration");
12993             end if;
12994
12995             Set_Is_Remote_Types (Cunit_Ent);
12996          end Remote_Types;
12997
12998          ---------------
12999          -- Ravenscar --
13000          ---------------
13001
13002          --  pragma Ravenscar;
13003
13004          when Pragma_Ravenscar =>
13005             GNAT_Pragma;
13006             Check_Arg_Count (0);
13007             Check_Valid_Configuration_Pragma;
13008             Set_Ravenscar_Profile (N);
13009
13010             if Warn_On_Obsolescent_Feature then
13011                Error_Msg_N ("pragma Ravenscar is an obsolescent feature?", N);
13012                Error_Msg_N ("|use pragma Profile (Ravenscar) instead", N);
13013             end if;
13014
13015          -------------------------
13016          -- Restricted_Run_Time --
13017          -------------------------
13018
13019          --  pragma Restricted_Run_Time;
13020
13021          when Pragma_Restricted_Run_Time =>
13022             GNAT_Pragma;
13023             Check_Arg_Count (0);
13024             Check_Valid_Configuration_Pragma;
13025             Set_Profile_Restrictions
13026               (Restricted, N, Warn => Treat_Restrictions_As_Warnings);
13027
13028             if Warn_On_Obsolescent_Feature then
13029                Error_Msg_N
13030                  ("pragma Restricted_Run_Time is an obsolescent feature?", N);
13031                Error_Msg_N ("|use pragma Profile (Restricted) instead", N);
13032             end if;
13033
13034          ------------------
13035          -- Restrictions --
13036          ------------------
13037
13038          --  pragma Restrictions (RESTRICTION {, RESTRICTION});
13039
13040          --  RESTRICTION ::=
13041          --    restriction_IDENTIFIER
13042          --  | restriction_parameter_IDENTIFIER => EXPRESSION
13043
13044          when Pragma_Restrictions =>
13045             Process_Restrictions_Or_Restriction_Warnings
13046               (Warn => Treat_Restrictions_As_Warnings);
13047
13048          --------------------------
13049          -- Restriction_Warnings --
13050          --------------------------
13051
13052          --  pragma Restriction_Warnings (RESTRICTION {, RESTRICTION});
13053
13054          --  RESTRICTION ::=
13055          --    restriction_IDENTIFIER
13056          --  | restriction_parameter_IDENTIFIER => EXPRESSION
13057
13058          when Pragma_Restriction_Warnings =>
13059             GNAT_Pragma;
13060             Process_Restrictions_Or_Restriction_Warnings (Warn => True);
13061
13062          ----------------
13063          -- Reviewable --
13064          ----------------
13065
13066          --  pragma Reviewable;
13067
13068          when Pragma_Reviewable =>
13069             Check_Ada_83_Warning;
13070             Check_Arg_Count (0);
13071
13072             --  Call dummy debugging function rv. This is done to assist front
13073             --  end debugging. By placing a Reviewable pragma in the source
13074             --  program, a breakpoint on rv catches this place in the source,
13075             --  allowing convenient stepping to the point of interest.
13076
13077             rv;
13078
13079          --------------------------
13080          -- Short_Circuit_And_Or --
13081          --------------------------
13082
13083          when Pragma_Short_Circuit_And_Or =>
13084             GNAT_Pragma;
13085             Check_Arg_Count (0);
13086             Check_Valid_Configuration_Pragma;
13087             Short_Circuit_And_Or := True;
13088
13089          -------------------
13090          -- Share_Generic --
13091          -------------------
13092
13093          --  pragma Share_Generic (NAME {, NAME});
13094
13095          when Pragma_Share_Generic =>
13096             GNAT_Pragma;
13097             Process_Generic_List;
13098
13099          ------------
13100          -- Shared --
13101          ------------
13102
13103          --  pragma Shared (LOCAL_NAME);
13104
13105          when Pragma_Shared =>
13106             GNAT_Pragma;
13107             Process_Atomic_Shared_Volatile;
13108
13109          --------------------
13110          -- Shared_Passive --
13111          --------------------
13112
13113          --  pragma Shared_Passive [(library_unit_NAME)];
13114
13115          --  Set the flag Is_Shared_Passive of program unit name entity
13116
13117          when Pragma_Shared_Passive => Shared_Passive : declare
13118             Cunit_Node : Node_Id;
13119             Cunit_Ent  : Entity_Id;
13120
13121          begin
13122             Check_Ada_83_Warning;
13123             Check_Valid_Library_Unit_Pragma;
13124
13125             if Nkind (N) = N_Null_Statement then
13126                return;
13127             end if;
13128
13129             Cunit_Node := Cunit (Current_Sem_Unit);
13130             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
13131
13132             if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
13133                                                 N_Generic_Package_Declaration)
13134             then
13135                Error_Pragma
13136                  ("pragma% can only apply to a package declaration");
13137             end if;
13138
13139             Set_Is_Shared_Passive (Cunit_Ent);
13140          end Shared_Passive;
13141
13142          -----------------------
13143          -- Short_Descriptors --
13144          -----------------------
13145
13146          --  pragma Short_Descriptors;
13147
13148          when Pragma_Short_Descriptors =>
13149             GNAT_Pragma;
13150             Check_Arg_Count (0);
13151             Check_Valid_Configuration_Pragma;
13152             Short_Descriptors := True;
13153
13154          ------------------------------
13155          -- Simple_Storage_Pool_Type --
13156          ------------------------------
13157
13158          --  pragma Simple_Storage_Pool_Type (type_LOCAL_NAME);
13159
13160          when Pragma_Simple_Storage_Pool_Type =>
13161          Simple_Storage_Pool_Type : declare
13162             Type_Id : Node_Id;
13163             Typ     : Entity_Id;
13164
13165          begin
13166             GNAT_Pragma;
13167             Check_Arg_Count (1);
13168             Check_Arg_Is_Library_Level_Local_Name (Arg1);
13169
13170             Type_Id := Get_Pragma_Arg (Arg1);
13171             Find_Type (Type_Id);
13172             Typ := Entity (Type_Id);
13173
13174             if Typ = Any_Type then
13175                return;
13176             end if;
13177
13178             --  We require the pragma to apply to a type declared in a package
13179             --  declaration, but not (immediately) within a package body.
13180
13181             if Ekind (Current_Scope) /= E_Package
13182               or else In_Package_Body (Current_Scope)
13183             then
13184                Error_Pragma
13185                  ("pragma% can only apply to type declared immediately " &
13186                   "within a package declaration");
13187             end if;
13188
13189             --  A simple storage pool type must be an immutably limited record
13190             --  or private type. If the pragma is given for a private type,
13191             --  the full type is similarly restricted (which is checked later
13192             --  in Freeze_Entity).
13193
13194             if Is_Record_Type (Typ)
13195               and then not Is_Immutably_Limited_Type (Typ)
13196             then
13197                Error_Pragma
13198                  ("pragma% can only apply to explicitly limited record type");
13199
13200             elsif Is_Private_Type (Typ) and then not Is_Limited_Type (Typ) then
13201                Error_Pragma
13202                  ("pragma% can only apply to a private type that is limited");
13203
13204             elsif not Is_Record_Type (Typ)
13205               and then not Is_Private_Type (Typ)
13206             then
13207                Error_Pragma
13208                  ("pragma% can only apply to limited record or private type");
13209             end if;
13210
13211             Record_Rep_Item (Typ, N);
13212          end Simple_Storage_Pool_Type;
13213
13214          ----------------------
13215          -- Source_File_Name --
13216          ----------------------
13217
13218          --  There are five forms for this pragma:
13219
13220          --  pragma Source_File_Name (
13221          --    [UNIT_NAME      =>] unit_NAME,
13222          --     BODY_FILE_NAME =>  STRING_LITERAL
13223          --    [, [INDEX =>] INTEGER_LITERAL]);
13224
13225          --  pragma Source_File_Name (
13226          --    [UNIT_NAME      =>] unit_NAME,
13227          --     SPEC_FILE_NAME =>  STRING_LITERAL
13228          --    [, [INDEX =>] INTEGER_LITERAL]);
13229
13230          --  pragma Source_File_Name (
13231          --     BODY_FILE_NAME  => STRING_LITERAL
13232          --  [, DOT_REPLACEMENT => STRING_LITERAL]
13233          --  [, CASING          => CASING_SPEC]);
13234
13235          --  pragma Source_File_Name (
13236          --     SPEC_FILE_NAME  => STRING_LITERAL
13237          --  [, DOT_REPLACEMENT => STRING_LITERAL]
13238          --  [, CASING          => CASING_SPEC]);
13239
13240          --  pragma Source_File_Name (
13241          --     SUBUNIT_FILE_NAME  => STRING_LITERAL
13242          --  [, DOT_REPLACEMENT    => STRING_LITERAL]
13243          --  [, CASING             => CASING_SPEC]);
13244
13245          --  CASING_SPEC ::= Uppercase | Lowercase | Mixedcase
13246
13247          --  Pragma Source_File_Name_Project (SFNP) is equivalent to pragma
13248          --  Source_File_Name (SFN), however their usage is exclusive: SFN can
13249          --  only be used when no project file is used, while SFNP can only be
13250          --  used when a project file is used.
13251
13252          --  No processing here. Processing was completed during parsing, since
13253          --  we need to have file names set as early as possible. Units are
13254          --  loaded well before semantic processing starts.
13255
13256          --  The only processing we defer to this point is the check for
13257          --  correct placement.
13258
13259          when Pragma_Source_File_Name =>
13260             GNAT_Pragma;
13261             Check_Valid_Configuration_Pragma;
13262
13263          ------------------------------
13264          -- Source_File_Name_Project --
13265          ------------------------------
13266
13267          --  See Source_File_Name for syntax
13268
13269          --  No processing here. Processing was completed during parsing, since
13270          --  we need to have file names set as early as possible. Units are
13271          --  loaded well before semantic processing starts.
13272
13273          --  The only processing we defer to this point is the check for
13274          --  correct placement.
13275
13276          when Pragma_Source_File_Name_Project =>
13277             GNAT_Pragma;
13278             Check_Valid_Configuration_Pragma;
13279
13280             --  Check that a pragma Source_File_Name_Project is used only in a
13281             --  configuration pragmas file.
13282
13283             --  Pragmas Source_File_Name_Project should only be generated by
13284             --  the Project Manager in configuration pragmas files.
13285
13286             --  This is really an ugly test. It seems to depend on some
13287             --  accidental and undocumented property. At the very least it
13288             --  needs to be documented, but it would be better to have a
13289             --  clean way of testing if we are in a configuration file???
13290
13291             if Present (Parent (N)) then
13292                Error_Pragma
13293                  ("pragma% can only appear in a configuration pragmas file");
13294             end if;
13295
13296          ----------------------
13297          -- Source_Reference --
13298          ----------------------
13299
13300          --  pragma Source_Reference (INTEGER_LITERAL [, STRING_LITERAL]);
13301
13302          --  Nothing to do, all processing completed in Par.Prag, since we need
13303          --  the information for possible parser messages that are output.
13304
13305          when Pragma_Source_Reference =>
13306             GNAT_Pragma;
13307
13308          --------------------------------
13309          -- Static_Elaboration_Desired --
13310          --------------------------------
13311
13312          --  pragma Static_Elaboration_Desired (DIRECT_NAME);
13313
13314          when Pragma_Static_Elaboration_Desired =>
13315             GNAT_Pragma;
13316             Check_At_Most_N_Arguments (1);
13317
13318             if Is_Compilation_Unit (Current_Scope)
13319               and then Ekind (Current_Scope) = E_Package
13320             then
13321                Set_Static_Elaboration_Desired (Current_Scope, True);
13322             else
13323                Error_Pragma ("pragma% must apply to a library-level package");
13324             end if;
13325
13326          ------------------
13327          -- Storage_Size --
13328          ------------------
13329
13330          --  pragma Storage_Size (EXPRESSION);
13331
13332          when Pragma_Storage_Size => Storage_Size : declare
13333             P   : constant Node_Id := Parent (N);
13334             Arg : Node_Id;
13335
13336          begin
13337             Check_No_Identifiers;
13338             Check_Arg_Count (1);
13339
13340             --  The expression must be analyzed in the special manner described
13341             --  in "Handling of Default Expressions" in sem.ads.
13342
13343             Arg := Get_Pragma_Arg (Arg1);
13344             Preanalyze_Spec_Expression (Arg, Any_Integer);
13345
13346             if not Is_Static_Expression (Arg) then
13347                Check_Restriction (Static_Storage_Size, Arg);
13348             end if;
13349
13350             if Nkind (P) /= N_Task_Definition then
13351                Pragma_Misplaced;
13352                return;
13353
13354             else
13355                if Has_Storage_Size_Pragma (P) then
13356                   Error_Pragma ("duplicate pragma% not allowed");
13357                else
13358                   Set_Has_Storage_Size_Pragma (P, True);
13359                end if;
13360
13361                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
13362                --  ???  exp_ch9 should use this!
13363             end if;
13364          end Storage_Size;
13365
13366          ------------------
13367          -- Storage_Unit --
13368          ------------------
13369
13370          --  pragma Storage_Unit (NUMERIC_LITERAL);
13371
13372          --  Only permitted argument is System'Storage_Unit value
13373
13374          when Pragma_Storage_Unit =>
13375             Check_No_Identifiers;
13376             Check_Arg_Count (1);
13377             Check_Arg_Is_Integer_Literal (Arg1);
13378
13379             if Intval (Get_Pragma_Arg (Arg1)) /=
13380               UI_From_Int (Ttypes.System_Storage_Unit)
13381             then
13382                Error_Msg_Uint_1 := UI_From_Int (Ttypes.System_Storage_Unit);
13383                Error_Pragma_Arg
13384                  ("the only allowed argument for pragma% is ^", Arg1);
13385             end if;
13386
13387          --------------------
13388          -- Stream_Convert --
13389          --------------------
13390
13391          --  pragma Stream_Convert (
13392          --    [Entity =>] type_LOCAL_NAME,
13393          --    [Read   =>] function_NAME,
13394          --    [Write  =>] function NAME);
13395
13396          when Pragma_Stream_Convert => Stream_Convert : declare
13397
13398             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id);
13399             --  Check that the given argument is the name of a local function
13400             --  of one argument that is not overloaded earlier in the current
13401             --  local scope. A check is also made that the argument is a
13402             --  function with one parameter.
13403
13404             --------------------------------------
13405             -- Check_OK_Stream_Convert_Function --
13406             --------------------------------------
13407
13408             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id) is
13409                Ent : Entity_Id;
13410
13411             begin
13412                Check_Arg_Is_Local_Name (Arg);
13413                Ent := Entity (Get_Pragma_Arg (Arg));
13414
13415                if Has_Homonym (Ent) then
13416                   Error_Pragma_Arg
13417                     ("argument for pragma% may not be overloaded", Arg);
13418                end if;
13419
13420                if Ekind (Ent) /= E_Function
13421                  or else No (First_Formal (Ent))
13422                  or else Present (Next_Formal (First_Formal (Ent)))
13423                then
13424                   Error_Pragma_Arg
13425                     ("argument for pragma% must be" &
13426                      " function of one argument", Arg);
13427                end if;
13428             end Check_OK_Stream_Convert_Function;
13429
13430          --  Start of processing for Stream_Convert
13431
13432          begin
13433             GNAT_Pragma;
13434             Check_Arg_Order ((Name_Entity, Name_Read, Name_Write));
13435             Check_Arg_Count (3);
13436             Check_Optional_Identifier (Arg1, Name_Entity);
13437             Check_Optional_Identifier (Arg2, Name_Read);
13438             Check_Optional_Identifier (Arg3, Name_Write);
13439             Check_Arg_Is_Local_Name (Arg1);
13440             Check_OK_Stream_Convert_Function (Arg2);
13441             Check_OK_Stream_Convert_Function (Arg3);
13442
13443             declare
13444                Typ   : constant Entity_Id :=
13445                          Underlying_Type (Entity (Get_Pragma_Arg (Arg1)));
13446                Read  : constant Entity_Id := Entity (Get_Pragma_Arg (Arg2));
13447                Write : constant Entity_Id := Entity (Get_Pragma_Arg (Arg3));
13448
13449             begin
13450                Check_First_Subtype (Arg1);
13451
13452                --  Check for too early or too late. Note that we don't enforce
13453                --  the rule about primitive operations in this case, since, as
13454                --  is the case for explicit stream attributes themselves, these
13455                --  restrictions are not appropriate. Note that the chaining of
13456                --  the pragma by Rep_Item_Too_Late is actually the critical
13457                --  processing done for this pragma.
13458
13459                if Rep_Item_Too_Early (Typ, N)
13460                     or else
13461                   Rep_Item_Too_Late (Typ, N, FOnly => True)
13462                then
13463                   return;
13464                end if;
13465
13466                --  Return if previous error
13467
13468                if Etype (Typ) = Any_Type
13469                     or else
13470                   Etype (Read) = Any_Type
13471                     or else
13472                   Etype (Write) = Any_Type
13473                then
13474                   return;
13475                end if;
13476
13477                --  Error checks
13478
13479                if Underlying_Type (Etype (Read)) /= Typ then
13480                   Error_Pragma_Arg
13481                     ("incorrect return type for function&", Arg2);
13482                end if;
13483
13484                if Underlying_Type (Etype (First_Formal (Write))) /= Typ then
13485                   Error_Pragma_Arg
13486                     ("incorrect parameter type for function&", Arg3);
13487                end if;
13488
13489                if Underlying_Type (Etype (First_Formal (Read))) /=
13490                   Underlying_Type (Etype (Write))
13491                then
13492                   Error_Pragma_Arg
13493                     ("result type of & does not match Read parameter type",
13494                      Arg3);
13495                end if;
13496             end;
13497          end Stream_Convert;
13498
13499          -------------------------
13500          -- Style_Checks (GNAT) --
13501          -------------------------
13502
13503          --  pragma Style_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
13504
13505          --  This is processed by the parser since some of the style checks
13506          --  take place during source scanning and parsing. This means that
13507          --  we don't need to issue error messages here.
13508
13509          when Pragma_Style_Checks => Style_Checks : declare
13510             A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
13511             S  : String_Id;
13512             C  : Char_Code;
13513
13514          begin
13515             GNAT_Pragma;
13516             Check_No_Identifiers;
13517
13518             --  Two argument form
13519
13520             if Arg_Count = 2 then
13521                Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
13522
13523                declare
13524                   E_Id : Node_Id;
13525                   E    : Entity_Id;
13526
13527                begin
13528                   E_Id := Get_Pragma_Arg (Arg2);
13529                   Analyze (E_Id);
13530
13531                   if not Is_Entity_Name (E_Id) then
13532                      Error_Pragma_Arg
13533                        ("second argument of pragma% must be entity name",
13534                         Arg2);
13535                   end if;
13536
13537                   E := Entity (E_Id);
13538
13539                   if E = Any_Id then
13540                      return;
13541                   else
13542                      loop
13543                         Set_Suppress_Style_Checks (E,
13544                           (Chars (Get_Pragma_Arg (Arg1)) = Name_Off));
13545                         exit when No (Homonym (E));
13546                         E := Homonym (E);
13547                      end loop;
13548                   end if;
13549                end;
13550
13551             --  One argument form
13552
13553             else
13554                Check_Arg_Count (1);
13555
13556                if Nkind (A) = N_String_Literal then
13557                   S   := Strval (A);
13558
13559                   declare
13560                      Slen    : constant Natural := Natural (String_Length (S));
13561                      Options : String (1 .. Slen);
13562                      J       : Natural;
13563
13564                   begin
13565                      J := 1;
13566                      loop
13567                         C := Get_String_Char (S, Int (J));
13568                         exit when not In_Character_Range (C);
13569                         Options (J) := Get_Character (C);
13570
13571                         --  If at end of string, set options. As per discussion
13572                         --  above, no need to check for errors, since we issued
13573                         --  them in the parser.
13574
13575                         if J = Slen then
13576                            Set_Style_Check_Options (Options);
13577                            exit;
13578                         end if;
13579
13580                         J := J + 1;
13581                      end loop;
13582                   end;
13583
13584                elsif Nkind (A) = N_Identifier then
13585                   if Chars (A) = Name_All_Checks then
13586                      if GNAT_Mode then
13587                         Set_GNAT_Style_Check_Options;
13588                      else
13589                         Set_Default_Style_Check_Options;
13590                      end if;
13591
13592                   elsif Chars (A) = Name_On then
13593                      Style_Check := True;
13594
13595                   elsif Chars (A) = Name_Off then
13596                      Style_Check := False;
13597                   end if;
13598                end if;
13599             end if;
13600          end Style_Checks;
13601
13602          --------------
13603          -- Subtitle --
13604          --------------
13605
13606          --  pragma Subtitle ([Subtitle =>] STRING_LITERAL);
13607
13608          when Pragma_Subtitle =>
13609             GNAT_Pragma;
13610             Check_Arg_Count (1);
13611             Check_Optional_Identifier (Arg1, Name_Subtitle);
13612             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
13613             Store_Note (N);
13614
13615          --------------
13616          -- Suppress --
13617          --------------
13618
13619          --  pragma Suppress (IDENTIFIER [, [On =>] NAME]);
13620
13621          when Pragma_Suppress =>
13622             Process_Suppress_Unsuppress (True);
13623
13624          ------------------
13625          -- Suppress_All --
13626          ------------------
13627
13628          --  pragma Suppress_All;
13629
13630          --  The only check made here is that the pragma has no arguments.
13631          --  There are no placement rules, and the processing required (setting
13632          --  the Has_Pragma_Suppress_All flag in the compilation unit node was
13633          --  taken care of by the parser). Process_Compilation_Unit_Pragmas
13634          --  then creates and inserts a pragma Suppress (All_Checks).
13635
13636          when Pragma_Suppress_All =>
13637             GNAT_Pragma;
13638             Check_Arg_Count (0);
13639
13640          -------------------------
13641          -- Suppress_Debug_Info --
13642          -------------------------
13643
13644          --  pragma Suppress_Debug_Info ([Entity =>] LOCAL_NAME);
13645
13646          when Pragma_Suppress_Debug_Info =>
13647             GNAT_Pragma;
13648             Check_Arg_Count (1);
13649             Check_Optional_Identifier (Arg1, Name_Entity);
13650             Check_Arg_Is_Local_Name (Arg1);
13651             Set_Debug_Info_Off (Entity (Get_Pragma_Arg (Arg1)));
13652
13653          ----------------------------------
13654          -- Suppress_Exception_Locations --
13655          ----------------------------------
13656
13657          --  pragma Suppress_Exception_Locations;
13658
13659          when Pragma_Suppress_Exception_Locations =>
13660             GNAT_Pragma;
13661             Check_Arg_Count (0);
13662             Check_Valid_Configuration_Pragma;
13663             Exception_Locations_Suppressed := True;
13664
13665          -----------------------------
13666          -- Suppress_Initialization --
13667          -----------------------------
13668
13669          --  pragma Suppress_Initialization ([Entity =>] type_Name);
13670
13671          when Pragma_Suppress_Initialization => Suppress_Init : declare
13672             E_Id : Node_Id;
13673             E    : Entity_Id;
13674
13675          begin
13676             GNAT_Pragma;
13677             Check_Arg_Count (1);
13678             Check_Optional_Identifier (Arg1, Name_Entity);
13679             Check_Arg_Is_Local_Name (Arg1);
13680
13681             E_Id := Get_Pragma_Arg (Arg1);
13682
13683             if Etype (E_Id) = Any_Type then
13684                return;
13685             end if;
13686
13687             E := Entity (E_Id);
13688
13689             if not Is_Type (E) then
13690                Error_Pragma_Arg ("pragma% requires type or subtype", Arg1);
13691             end if;
13692
13693             if Rep_Item_Too_Early (E, N)
13694                  or else
13695                Rep_Item_Too_Late (E, N, FOnly => True)
13696             then
13697                return;
13698             end if;
13699
13700             --  For incomplete/private type, set flag on full view
13701
13702             if Is_Incomplete_Or_Private_Type (E) then
13703                if No (Full_View (Base_Type (E))) then
13704                   Error_Pragma_Arg
13705                     ("argument of pragma% cannot be an incomplete type", Arg1);
13706                else
13707                   Set_Suppress_Initialization (Full_View (Base_Type (E)));
13708                end if;
13709
13710             --  For first subtype, set flag on base type
13711
13712             elsif Is_First_Subtype (E) then
13713                Set_Suppress_Initialization (Base_Type (E));
13714
13715             --  For other than first subtype, set flag on subtype itself
13716
13717             else
13718                Set_Suppress_Initialization (E);
13719             end if;
13720          end Suppress_Init;
13721
13722          -----------------
13723          -- System_Name --
13724          -----------------
13725
13726          --  pragma System_Name (DIRECT_NAME);
13727
13728          --  Syntax check: one argument, which must be the identifier GNAT or
13729          --  the identifier GCC, no other identifiers are acceptable.
13730
13731          when Pragma_System_Name =>
13732             GNAT_Pragma;
13733             Check_No_Identifiers;
13734             Check_Arg_Count (1);
13735             Check_Arg_Is_One_Of (Arg1, Name_Gcc, Name_Gnat);
13736
13737          -----------------------------
13738          -- Task_Dispatching_Policy --
13739          -----------------------------
13740
13741          --  pragma Task_Dispatching_Policy (policy_IDENTIFIER);
13742
13743          when Pragma_Task_Dispatching_Policy => declare
13744             DP : Character;
13745
13746          begin
13747             Check_Ada_83_Warning;
13748             Check_Arg_Count (1);
13749             Check_No_Identifiers;
13750             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
13751             Check_Valid_Configuration_Pragma;
13752             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
13753             DP := Fold_Upper (Name_Buffer (1));
13754
13755             if Task_Dispatching_Policy /= ' '
13756               and then Task_Dispatching_Policy /= DP
13757             then
13758                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
13759                Error_Pragma
13760                  ("task dispatching policy incompatible with policy#");
13761
13762             --  Set new policy, but always preserve System_Location since we
13763             --  like the error message with the run time name.
13764
13765             else
13766                Task_Dispatching_Policy := DP;
13767
13768                if Task_Dispatching_Policy_Sloc /= System_Location then
13769                   Task_Dispatching_Policy_Sloc := Loc;
13770                end if;
13771             end if;
13772          end;
13773
13774          ---------------
13775          -- Task_Info --
13776          ---------------
13777
13778          --  pragma Task_Info (EXPRESSION);
13779
13780          when Pragma_Task_Info => Task_Info : declare
13781             P : constant Node_Id := Parent (N);
13782
13783          begin
13784             GNAT_Pragma;
13785
13786             if Nkind (P) /= N_Task_Definition then
13787                Error_Pragma ("pragma% must appear in task definition");
13788             end if;
13789
13790             Check_No_Identifiers;
13791             Check_Arg_Count (1);
13792
13793             Analyze_And_Resolve
13794               (Get_Pragma_Arg (Arg1), RTE (RE_Task_Info_Type));
13795
13796             if Etype (Get_Pragma_Arg (Arg1)) = Any_Type then
13797                return;
13798             end if;
13799
13800             if Has_Task_Info_Pragma (P) then
13801                Error_Pragma ("duplicate pragma% not allowed");
13802             else
13803                Set_Has_Task_Info_Pragma (P, True);
13804             end if;
13805          end Task_Info;
13806
13807          ---------------
13808          -- Task_Name --
13809          ---------------
13810
13811          --  pragma Task_Name (string_EXPRESSION);
13812
13813          when Pragma_Task_Name => Task_Name : declare
13814             P   : constant Node_Id := Parent (N);
13815             Arg : Node_Id;
13816
13817          begin
13818             Check_No_Identifiers;
13819             Check_Arg_Count (1);
13820
13821             Arg := Get_Pragma_Arg (Arg1);
13822
13823             --  The expression is used in the call to Create_Task, and must be
13824             --  expanded there, not in the context of the current spec. It must
13825             --  however be analyzed to capture global references, in case it
13826             --  appears in a generic context.
13827
13828             Preanalyze_And_Resolve (Arg, Standard_String);
13829
13830             if Nkind (P) /= N_Task_Definition then
13831                Pragma_Misplaced;
13832             end if;
13833
13834             if Has_Task_Name_Pragma (P) then
13835                Error_Pragma ("duplicate pragma% not allowed");
13836             else
13837                Set_Has_Task_Name_Pragma (P, True);
13838                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
13839             end if;
13840          end Task_Name;
13841
13842          ------------------
13843          -- Task_Storage --
13844          ------------------
13845
13846          --  pragma Task_Storage (
13847          --     [Task_Type =>] LOCAL_NAME,
13848          --     [Top_Guard =>] static_integer_EXPRESSION);
13849
13850          when Pragma_Task_Storage => Task_Storage : declare
13851             Args  : Args_List (1 .. 2);
13852             Names : constant Name_List (1 .. 2) := (
13853                       Name_Task_Type,
13854                       Name_Top_Guard);
13855
13856             Task_Type : Node_Id renames Args (1);
13857             Top_Guard : Node_Id renames Args (2);
13858
13859             Ent : Entity_Id;
13860
13861          begin
13862             GNAT_Pragma;
13863             Gather_Associations (Names, Args);
13864
13865             if No (Task_Type) then
13866                Error_Pragma
13867                  ("missing task_type argument for pragma%");
13868             end if;
13869
13870             Check_Arg_Is_Local_Name (Task_Type);
13871
13872             Ent := Entity (Task_Type);
13873
13874             if not Is_Task_Type (Ent) then
13875                Error_Pragma_Arg
13876                  ("argument for pragma% must be task type", Task_Type);
13877             end if;
13878
13879             if No (Top_Guard) then
13880                Error_Pragma_Arg
13881                  ("pragma% takes two arguments", Task_Type);
13882             else
13883                Check_Arg_Is_Static_Expression (Top_Guard, Any_Integer);
13884             end if;
13885
13886             Check_First_Subtype (Task_Type);
13887
13888             if Rep_Item_Too_Late (Ent, N) then
13889                raise Pragma_Exit;
13890             end if;
13891          end Task_Storage;
13892
13893          ---------------
13894          -- Test_Case --
13895          ---------------
13896
13897          --  pragma Test_Case ([Name     =>] Static_String_EXPRESSION
13898          --                   ,[Mode     =>] MODE_TYPE
13899          --                  [, Requires =>  Boolean_EXPRESSION]
13900          --                  [, Ensures  =>  Boolean_EXPRESSION]);
13901
13902          --  MODE_TYPE ::= Nominal | Robustness
13903
13904          when Pragma_Test_Case => Test_Case : declare
13905          begin
13906             GNAT_Pragma;
13907             Check_At_Least_N_Arguments (2);
13908             Check_At_Most_N_Arguments (4);
13909             Check_Arg_Order
13910                  ((Name_Name, Name_Mode, Name_Requires, Name_Ensures));
13911
13912             Check_Optional_Identifier (Arg1, Name_Name);
13913             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
13914
13915             --  In ASIS mode, for a pragma generated from a source aspect, also
13916             --  analyze the original aspect expression.
13917
13918             if ASIS_Mode
13919               and then Present (Corresponding_Aspect (N))
13920             then
13921                Check_Expr_Is_Static_Expression
13922                  (Original_Node (Get_Pragma_Arg (Arg1)), Standard_String);
13923             end if;
13924
13925             Check_Optional_Identifier (Arg2, Name_Mode);
13926             Check_Arg_Is_One_Of (Arg2, Name_Nominal, Name_Robustness);
13927
13928             if Arg_Count = 4 then
13929                Check_Identifier (Arg3, Name_Requires);
13930                Check_Identifier (Arg4, Name_Ensures);
13931
13932             elsif Arg_Count = 3 then
13933                Check_Identifier_Is_One_Of (Arg3, Name_Requires, Name_Ensures);
13934             end if;
13935
13936             Check_Test_Case;
13937          end Test_Case;
13938
13939          --------------------------
13940          -- Thread_Local_Storage --
13941          --------------------------
13942
13943          --  pragma Thread_Local_Storage ([Entity =>] LOCAL_NAME);
13944
13945          when Pragma_Thread_Local_Storage => Thread_Local_Storage : declare
13946             Id : Node_Id;
13947             E  : Entity_Id;
13948
13949          begin
13950             GNAT_Pragma;
13951             Check_Arg_Count (1);
13952             Check_Optional_Identifier (Arg1, Name_Entity);
13953             Check_Arg_Is_Library_Level_Local_Name (Arg1);
13954
13955             Id := Get_Pragma_Arg (Arg1);
13956             Analyze (Id);
13957
13958             if not Is_Entity_Name (Id)
13959               or else Ekind (Entity (Id)) /= E_Variable
13960             then
13961                Error_Pragma_Arg ("local variable name required", Arg1);
13962             end if;
13963
13964             E := Entity (Id);
13965
13966             if Rep_Item_Too_Early (E, N)
13967               or else Rep_Item_Too_Late (E, N)
13968             then
13969                raise Pragma_Exit;
13970             end if;
13971
13972             Set_Has_Pragma_Thread_Local_Storage (E);
13973             Set_Has_Gigi_Rep_Item (E);
13974          end Thread_Local_Storage;
13975
13976          ----------------
13977          -- Time_Slice --
13978          ----------------
13979
13980          --  pragma Time_Slice (static_duration_EXPRESSION);
13981
13982          when Pragma_Time_Slice => Time_Slice : declare
13983             Val : Ureal;
13984             Nod : Node_Id;
13985
13986          begin
13987             GNAT_Pragma;
13988             Check_Arg_Count (1);
13989             Check_No_Identifiers;
13990             Check_In_Main_Program;
13991             Check_Arg_Is_Static_Expression (Arg1, Standard_Duration);
13992
13993             if not Error_Posted (Arg1) then
13994                Nod := Next (N);
13995                while Present (Nod) loop
13996                   if Nkind (Nod) = N_Pragma
13997                     and then Pragma_Name (Nod) = Name_Time_Slice
13998                   then
13999                      Error_Msg_Name_1 := Pname;
14000                      Error_Msg_N ("duplicate pragma% not permitted", Nod);
14001                   end if;
14002
14003                   Next (Nod);
14004                end loop;
14005             end if;
14006
14007             --  Process only if in main unit
14008
14009             if Get_Source_Unit (Loc) = Main_Unit then
14010                Opt.Time_Slice_Set := True;
14011                Val := Expr_Value_R (Get_Pragma_Arg (Arg1));
14012
14013                if Val <= Ureal_0 then
14014                   Opt.Time_Slice_Value := 0;
14015
14016                elsif Val > UR_From_Uint (UI_From_Int (1000)) then
14017                   Opt.Time_Slice_Value := 1_000_000_000;
14018
14019                else
14020                   Opt.Time_Slice_Value :=
14021                     UI_To_Int (UR_To_Uint (Val * UI_From_Int (1_000_000)));
14022                end if;
14023             end if;
14024          end Time_Slice;
14025
14026          -----------
14027          -- Title --
14028          -----------
14029
14030          --  pragma Title (TITLING_OPTION [, TITLING OPTION]);
14031
14032          --   TITLING_OPTION ::=
14033          --     [Title =>] STRING_LITERAL
14034          --   | [Subtitle =>] STRING_LITERAL
14035
14036          when Pragma_Title => Title : declare
14037             Args  : Args_List (1 .. 2);
14038             Names : constant Name_List (1 .. 2) := (
14039                       Name_Title,
14040                       Name_Subtitle);
14041
14042          begin
14043             GNAT_Pragma;
14044             Gather_Associations (Names, Args);
14045             Store_Note (N);
14046
14047             for J in 1 .. 2 loop
14048                if Present (Args (J)) then
14049                   Check_Arg_Is_Static_Expression (Args (J), Standard_String);
14050                end if;
14051             end loop;
14052          end Title;
14053
14054          ---------------------
14055          -- Unchecked_Union --
14056          ---------------------
14057
14058          --  pragma Unchecked_Union (first_subtype_LOCAL_NAME)
14059
14060          when Pragma_Unchecked_Union => Unchecked_Union : declare
14061             Assoc   : constant Node_Id := Arg1;
14062             Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
14063             Typ     : Entity_Id;
14064             Discr   : Entity_Id;
14065             Tdef    : Node_Id;
14066             Clist   : Node_Id;
14067             Vpart   : Node_Id;
14068             Comp    : Node_Id;
14069             Variant : Node_Id;
14070
14071          begin
14072             Ada_2005_Pragma;
14073             Check_No_Identifiers;
14074             Check_Arg_Count (1);
14075             Check_Arg_Is_Local_Name (Arg1);
14076
14077             Find_Type (Type_Id);
14078             Typ := Entity (Type_Id);
14079
14080             if Typ = Any_Type
14081               or else Rep_Item_Too_Early (Typ, N)
14082             then
14083                return;
14084             else
14085                Typ := Underlying_Type (Typ);
14086             end if;
14087
14088             if Rep_Item_Too_Late (Typ, N) then
14089                return;
14090             end if;
14091
14092             Check_First_Subtype (Arg1);
14093
14094             --  Note remaining cases are references to a type in the current
14095             --  declarative part. If we find an error, we post the error on
14096             --  the relevant type declaration at an appropriate point.
14097
14098             if not Is_Record_Type (Typ) then
14099                Error_Msg_N ("Unchecked_Union must be record type", Typ);
14100                return;
14101
14102             elsif Is_Tagged_Type (Typ) then
14103                Error_Msg_N ("Unchecked_Union must not be tagged", Typ);
14104                return;
14105
14106             elsif not Has_Discriminants (Typ) then
14107                Error_Msg_N
14108                 ("Unchecked_Union must have one discriminant", Typ);
14109                return;
14110
14111             --  Note: in previous versions of GNAT we used to check for limited
14112             --  types and give an error, but in fact the standard does allow
14113             --  Unchecked_Union on limited types, so this check was removed.
14114
14115             --  Proceed with basic error checks completed
14116
14117             else
14118                Discr := First_Discriminant (Typ);
14119                while Present (Discr) loop
14120                   if No (Discriminant_Default_Value (Discr)) then
14121                      Error_Msg_N
14122                        ("Unchecked_Union discriminant must have default value",
14123                         Discr);
14124                   end if;
14125
14126                   Next_Discriminant (Discr);
14127                end loop;
14128
14129                Tdef  := Type_Definition (Declaration_Node (Typ));
14130                Clist := Component_List (Tdef);
14131
14132                Comp := First (Component_Items (Clist));
14133                while Present (Comp) loop
14134                   Check_Component (Comp, Typ);
14135                   Next (Comp);
14136                end loop;
14137
14138                if No (Clist) or else No (Variant_Part (Clist)) then
14139                   Error_Msg_N
14140                     ("Unchecked_Union must have variant part",
14141                      Tdef);
14142                   return;
14143                end if;
14144
14145                Vpart := Variant_Part (Clist);
14146
14147                Variant := First (Variants (Vpart));
14148                while Present (Variant) loop
14149                   Check_Variant (Variant, Typ);
14150                   Next (Variant);
14151                end loop;
14152             end if;
14153
14154             Set_Is_Unchecked_Union  (Typ);
14155             Set_Convention (Typ, Convention_C);
14156             Set_Has_Unchecked_Union (Base_Type (Typ));
14157             Set_Is_Unchecked_Union  (Base_Type (Typ));
14158          end Unchecked_Union;
14159
14160          ------------------------
14161          -- Unimplemented_Unit --
14162          ------------------------
14163
14164          --  pragma Unimplemented_Unit;
14165
14166          --  Note: this only gives an error if we are generating code, or if
14167          --  we are in a generic library unit (where the pragma appears in the
14168          --  body, not in the spec).
14169
14170          when Pragma_Unimplemented_Unit => Unimplemented_Unit : declare
14171             Cunitent : constant Entity_Id :=
14172                          Cunit_Entity (Get_Source_Unit (Loc));
14173             Ent_Kind : constant Entity_Kind :=
14174                          Ekind (Cunitent);
14175
14176          begin
14177             GNAT_Pragma;
14178             Check_Arg_Count (0);
14179
14180             if Operating_Mode = Generate_Code
14181               or else Ent_Kind = E_Generic_Function
14182               or else Ent_Kind = E_Generic_Procedure
14183               or else Ent_Kind = E_Generic_Package
14184             then
14185                Get_Name_String (Chars (Cunitent));
14186                Set_Casing (Mixed_Case);
14187                Write_Str (Name_Buffer (1 .. Name_Len));
14188                Write_Str (" is not supported in this configuration");
14189                Write_Eol;
14190                raise Unrecoverable_Error;
14191             end if;
14192          end Unimplemented_Unit;
14193
14194          ------------------------
14195          -- Universal_Aliasing --
14196          ------------------------
14197
14198          --  pragma Universal_Aliasing [([Entity =>] type_LOCAL_NAME)];
14199
14200          when Pragma_Universal_Aliasing => Universal_Alias : declare
14201             E_Id : Entity_Id;
14202
14203          begin
14204             GNAT_Pragma;
14205             Check_Arg_Count (1);
14206             Check_Optional_Identifier (Arg2, Name_Entity);
14207             Check_Arg_Is_Local_Name (Arg1);
14208             E_Id := Entity (Get_Pragma_Arg (Arg1));
14209
14210             if E_Id = Any_Type then
14211                return;
14212             elsif No (E_Id) or else not Is_Type (E_Id) then
14213                Error_Pragma_Arg ("pragma% requires type", Arg1);
14214             end if;
14215
14216             Set_Universal_Aliasing (Implementation_Base_Type (E_Id));
14217          end Universal_Alias;
14218
14219          --------------------
14220          -- Universal_Data --
14221          --------------------
14222
14223          --  pragma Universal_Data [(library_unit_NAME)];
14224
14225          when Pragma_Universal_Data =>
14226             GNAT_Pragma;
14227
14228             --  If this is a configuration pragma, then set the universal
14229             --  addressing option, otherwise confirm that the pragma satisfies
14230             --  the requirements of library unit pragma placement and leave it
14231             --  to the GNAAMP back end to detect the pragma (avoids transitive
14232             --  setting of the option due to withed units).
14233
14234             if Is_Configuration_Pragma then
14235                Universal_Addressing_On_AAMP := True;
14236             else
14237                Check_Valid_Library_Unit_Pragma;
14238             end if;
14239
14240             if not AAMP_On_Target then
14241                Error_Pragma ("?pragma% ignored (applies only to AAMP)");
14242             end if;
14243
14244          ----------------
14245          -- Unmodified --
14246          ----------------
14247
14248          --  pragma Unmodified (local_Name {, local_Name});
14249
14250          when Pragma_Unmodified => Unmodified : declare
14251             Arg_Node : Node_Id;
14252             Arg_Expr : Node_Id;
14253             Arg_Ent  : Entity_Id;
14254
14255          begin
14256             GNAT_Pragma;
14257             Check_At_Least_N_Arguments (1);
14258
14259             --  Loop through arguments
14260
14261             Arg_Node := Arg1;
14262             while Present (Arg_Node) loop
14263                Check_No_Identifier (Arg_Node);
14264
14265                --  Note: the analyze call done by Check_Arg_Is_Local_Name will
14266                --  in fact generate reference, so that the entity will have a
14267                --  reference, which will inhibit any warnings about it not
14268                --  being referenced, and also properly show up in the ali file
14269                --  as a reference. But this reference is recorded before the
14270                --  Has_Pragma_Unreferenced flag is set, so that no warning is
14271                --  generated for this reference.
14272
14273                Check_Arg_Is_Local_Name (Arg_Node);
14274                Arg_Expr := Get_Pragma_Arg (Arg_Node);
14275
14276                if Is_Entity_Name (Arg_Expr) then
14277                   Arg_Ent := Entity (Arg_Expr);
14278
14279                   if not Is_Assignable (Arg_Ent) then
14280                      Error_Pragma_Arg
14281                        ("pragma% can only be applied to a variable",
14282                         Arg_Expr);
14283                   else
14284                      Set_Has_Pragma_Unmodified (Arg_Ent);
14285                   end if;
14286                end if;
14287
14288                Next (Arg_Node);
14289             end loop;
14290          end Unmodified;
14291
14292          ------------------
14293          -- Unreferenced --
14294          ------------------
14295
14296          --  pragma Unreferenced (local_Name {, local_Name});
14297
14298          --    or when used in a context clause:
14299
14300          --  pragma Unreferenced (library_unit_NAME {, library_unit_NAME}
14301
14302          when Pragma_Unreferenced => Unreferenced : declare
14303             Arg_Node : Node_Id;
14304             Arg_Expr : Node_Id;
14305             Arg_Ent  : Entity_Id;
14306             Citem    : Node_Id;
14307
14308          begin
14309             GNAT_Pragma;
14310             Check_At_Least_N_Arguments (1);
14311
14312             --  Check case of appearing within context clause
14313
14314             if Is_In_Context_Clause then
14315
14316                --  The arguments must all be units mentioned in a with clause
14317                --  in the same context clause. Note we already checked (in
14318                --  Par.Prag) that the arguments are either identifiers or
14319                --  selected components.
14320
14321                Arg_Node := Arg1;
14322                while Present (Arg_Node) loop
14323                   Citem := First (List_Containing (N));
14324                   while Citem /= N loop
14325                      if Nkind (Citem) = N_With_Clause
14326                        and then
14327                          Same_Name (Name (Citem), Get_Pragma_Arg (Arg_Node))
14328                      then
14329                         Set_Has_Pragma_Unreferenced
14330                           (Cunit_Entity
14331                              (Get_Source_Unit
14332                                 (Library_Unit (Citem))));
14333                         Set_Unit_Name
14334                           (Get_Pragma_Arg (Arg_Node), Name (Citem));
14335                         exit;
14336                      end if;
14337
14338                      Next (Citem);
14339                   end loop;
14340
14341                   if Citem = N then
14342                      Error_Pragma_Arg
14343                        ("argument of pragma% is not withed unit", Arg_Node);
14344                   end if;
14345
14346                   Next (Arg_Node);
14347                end loop;
14348
14349             --  Case of not in list of context items
14350
14351             else
14352                Arg_Node := Arg1;
14353                while Present (Arg_Node) loop
14354                   Check_No_Identifier (Arg_Node);
14355
14356                   --  Note: the analyze call done by Check_Arg_Is_Local_Name
14357                   --  will in fact generate reference, so that the entity will
14358                   --  have a reference, which will inhibit any warnings about
14359                   --  it not being referenced, and also properly show up in the
14360                   --  ali file as a reference. But this reference is recorded
14361                   --  before the Has_Pragma_Unreferenced flag is set, so that
14362                   --  no warning is generated for this reference.
14363
14364                   Check_Arg_Is_Local_Name (Arg_Node);
14365                   Arg_Expr := Get_Pragma_Arg (Arg_Node);
14366
14367                   if Is_Entity_Name (Arg_Expr) then
14368                      Arg_Ent := Entity (Arg_Expr);
14369
14370                      --  If the entity is overloaded, the pragma applies to the
14371                      --  most recent overloading, as documented. In this case,
14372                      --  name resolution does not generate a reference, so it
14373                      --  must be done here explicitly.
14374
14375                      if Is_Overloaded (Arg_Expr) then
14376                         Generate_Reference (Arg_Ent, N);
14377                      end if;
14378
14379                      Set_Has_Pragma_Unreferenced (Arg_Ent);
14380                   end if;
14381
14382                   Next (Arg_Node);
14383                end loop;
14384             end if;
14385          end Unreferenced;
14386
14387          --------------------------
14388          -- Unreferenced_Objects --
14389          --------------------------
14390
14391          --  pragma Unreferenced_Objects (local_Name {, local_Name});
14392
14393          when Pragma_Unreferenced_Objects => Unreferenced_Objects : declare
14394             Arg_Node : Node_Id;
14395             Arg_Expr : Node_Id;
14396
14397          begin
14398             GNAT_Pragma;
14399             Check_At_Least_N_Arguments (1);
14400
14401             Arg_Node := Arg1;
14402             while Present (Arg_Node) loop
14403                Check_No_Identifier (Arg_Node);
14404                Check_Arg_Is_Local_Name (Arg_Node);
14405                Arg_Expr := Get_Pragma_Arg (Arg_Node);
14406
14407                if not Is_Entity_Name (Arg_Expr)
14408                  or else not Is_Type (Entity (Arg_Expr))
14409                then
14410                   Error_Pragma_Arg
14411                     ("argument for pragma% must be type or subtype", Arg_Node);
14412                end if;
14413
14414                Set_Has_Pragma_Unreferenced_Objects (Entity (Arg_Expr));
14415                Next (Arg_Node);
14416             end loop;
14417          end Unreferenced_Objects;
14418
14419          ------------------------------
14420          -- Unreserve_All_Interrupts --
14421          ------------------------------
14422
14423          --  pragma Unreserve_All_Interrupts;
14424
14425          when Pragma_Unreserve_All_Interrupts =>
14426             GNAT_Pragma;
14427             Check_Arg_Count (0);
14428
14429             if In_Extended_Main_Code_Unit (Main_Unit_Entity) then
14430                Unreserve_All_Interrupts := True;
14431             end if;
14432
14433          ----------------
14434          -- Unsuppress --
14435          ----------------
14436
14437          --  pragma Unsuppress (IDENTIFIER [, [On =>] NAME]);
14438
14439          when Pragma_Unsuppress =>
14440             Ada_2005_Pragma;
14441             Process_Suppress_Unsuppress (False);
14442
14443          -------------------
14444          -- Use_VADS_Size --
14445          -------------------
14446
14447          --  pragma Use_VADS_Size;
14448
14449          when Pragma_Use_VADS_Size =>
14450             GNAT_Pragma;
14451             Check_Arg_Count (0);
14452             Check_Valid_Configuration_Pragma;
14453             Use_VADS_Size := True;
14454
14455          ---------------------
14456          -- Validity_Checks --
14457          ---------------------
14458
14459          --  pragma Validity_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
14460
14461          when Pragma_Validity_Checks => Validity_Checks : declare
14462             A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
14463             S  : String_Id;
14464             C  : Char_Code;
14465
14466          begin
14467             GNAT_Pragma;
14468             Check_Arg_Count (1);
14469             Check_No_Identifiers;
14470
14471             if Nkind (A) = N_String_Literal then
14472                S   := Strval (A);
14473
14474                declare
14475                   Slen    : constant Natural := Natural (String_Length (S));
14476                   Options : String (1 .. Slen);
14477                   J       : Natural;
14478
14479                begin
14480                   J := 1;
14481                   loop
14482                      C := Get_String_Char (S, Int (J));
14483                      exit when not In_Character_Range (C);
14484                      Options (J) := Get_Character (C);
14485
14486                      if J = Slen then
14487                         Set_Validity_Check_Options (Options);
14488                         exit;
14489                      else
14490                         J := J + 1;
14491                      end if;
14492                   end loop;
14493                end;
14494
14495             elsif Nkind (A) = N_Identifier then
14496                if Chars (A) = Name_All_Checks then
14497                   Set_Validity_Check_Options ("a");
14498                elsif Chars (A) = Name_On then
14499                   Validity_Checks_On := True;
14500                elsif Chars (A) = Name_Off then
14501                   Validity_Checks_On := False;
14502                end if;
14503             end if;
14504          end Validity_Checks;
14505
14506          --------------
14507          -- Volatile --
14508          --------------
14509
14510          --  pragma Volatile (LOCAL_NAME);
14511
14512          when Pragma_Volatile =>
14513             Process_Atomic_Shared_Volatile;
14514
14515          -------------------------
14516          -- Volatile_Components --
14517          -------------------------
14518
14519          --  pragma Volatile_Components (array_LOCAL_NAME);
14520
14521          --  Volatile is handled by the same circuit as Atomic_Components
14522
14523          --------------
14524          -- Warnings --
14525          --------------
14526
14527          --  pragma Warnings (On | Off);
14528          --  pragma Warnings (On | Off, LOCAL_NAME);
14529          --  pragma Warnings (static_string_EXPRESSION);
14530          --  pragma Warnings (On | Off, STRING_LITERAL);
14531
14532          when Pragma_Warnings => Warnings : begin
14533             GNAT_Pragma;
14534             Check_At_Least_N_Arguments (1);
14535             Check_No_Identifiers;
14536
14537             --  If debug flag -gnatd.i is set, pragma is ignored
14538
14539             if Debug_Flag_Dot_I then
14540                return;
14541             end if;
14542
14543             --  Process various forms of the pragma
14544
14545             declare
14546                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
14547
14548             begin
14549                --  One argument case
14550
14551                if Arg_Count = 1 then
14552
14553                   --  On/Off one argument case was processed by parser
14554
14555                   if Nkind (Argx) = N_Identifier
14556                     and then
14557                       (Chars (Argx) = Name_On
14558                          or else
14559                        Chars (Argx) = Name_Off)
14560                   then
14561                      null;
14562
14563                   --  One argument case must be ON/OFF or static string expr
14564
14565                   elsif not Is_Static_String_Expression (Arg1) then
14566                      Error_Pragma_Arg
14567                        ("argument of pragma% must be On/Off or " &
14568                         "static string expression", Arg1);
14569
14570                   --  One argument string expression case
14571
14572                   else
14573                      declare
14574                         Lit : constant Node_Id   := Expr_Value_S (Argx);
14575                         Str : constant String_Id := Strval (Lit);
14576                         Len : constant Nat       := String_Length (Str);
14577                         C   : Char_Code;
14578                         J   : Nat;
14579                         OK  : Boolean;
14580                         Chr : Character;
14581
14582                      begin
14583                         J := 1;
14584                         while J <= Len loop
14585                            C := Get_String_Char (Str, J);
14586                            OK := In_Character_Range (C);
14587
14588                            if OK then
14589                               Chr := Get_Character (C);
14590
14591                               --  Dot case
14592
14593                               if J < Len and then Chr = '.' then
14594                                  J := J + 1;
14595                                  C := Get_String_Char (Str, J);
14596                                  Chr := Get_Character (C);
14597
14598                                  if not Set_Dot_Warning_Switch (Chr) then
14599                                     Error_Pragma_Arg
14600                                       ("invalid warning switch character " &
14601                                        '.' & Chr, Arg1);
14602                                  end if;
14603
14604                               --  Non-Dot case
14605
14606                               else
14607                                  OK := Set_Warning_Switch (Chr);
14608                               end if;
14609                            end if;
14610
14611                            if not OK then
14612                               Error_Pragma_Arg
14613                                 ("invalid warning switch character " & Chr,
14614                                  Arg1);
14615                            end if;
14616
14617                            J := J + 1;
14618                         end loop;
14619                      end;
14620                   end if;
14621
14622                --  Two or more arguments (must be two)
14623
14624                else
14625                   Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
14626                   Check_At_Most_N_Arguments (2);
14627
14628                   declare
14629                      E_Id : Node_Id;
14630                      E    : Entity_Id;
14631                      Err  : Boolean;
14632
14633                   begin
14634                      E_Id := Get_Pragma_Arg (Arg2);
14635                      Analyze (E_Id);
14636
14637                      --  In the expansion of an inlined body, a reference to
14638                      --  the formal may be wrapped in a conversion if the
14639                      --  actual is a conversion. Retrieve the real entity name.
14640
14641                      if (In_Instance_Body or In_Inlined_Body)
14642                        and then Nkind (E_Id) = N_Unchecked_Type_Conversion
14643                      then
14644                         E_Id := Expression (E_Id);
14645                      end if;
14646
14647                      --  Entity name case
14648
14649                      if Is_Entity_Name (E_Id) then
14650                         E := Entity (E_Id);
14651
14652                         if E = Any_Id then
14653                            return;
14654                         else
14655                            loop
14656                               Set_Warnings_Off
14657                                 (E, (Chars (Get_Pragma_Arg (Arg1)) =
14658                                                               Name_Off));
14659
14660                               if Chars (Get_Pragma_Arg (Arg1)) = Name_Off
14661                                 and then Warn_On_Warnings_Off
14662                               then
14663                                  Warnings_Off_Pragmas.Append ((N, E));
14664                               end if;
14665
14666                               if Is_Enumeration_Type (E) then
14667                                  declare
14668                                     Lit : Entity_Id;
14669                                  begin
14670                                     Lit := First_Literal (E);
14671                                     while Present (Lit) loop
14672                                        Set_Warnings_Off (Lit);
14673                                        Next_Literal (Lit);
14674                                     end loop;
14675                                  end;
14676                               end if;
14677
14678                               exit when No (Homonym (E));
14679                               E := Homonym (E);
14680                            end loop;
14681                         end if;
14682
14683                      --  Error if not entity or static string literal case
14684
14685                      elsif not Is_Static_String_Expression (Arg2) then
14686                         Error_Pragma_Arg
14687                           ("second argument of pragma% must be entity " &
14688                            "name or static string expression", Arg2);
14689
14690                      --  String literal case
14691
14692                      else
14693                         String_To_Name_Buffer
14694                           (Strval (Expr_Value_S (Get_Pragma_Arg (Arg2))));
14695
14696                         --  Note on configuration pragma case: If this is a
14697                         --  configuration pragma, then for an OFF pragma, we
14698                         --  just set Config True in the call, which is all
14699                         --  that needs to be done. For the case of ON, this
14700                         --  is normally an error, unless it is canceling the
14701                         --  effect of a previous OFF pragma in the same file.
14702                         --  In any other case, an error will be signalled (ON
14703                         --  with no matching OFF).
14704
14705                         --  Note: We set Used if we are inside a generic to
14706                         --  disable the test that the non-config case actually
14707                         --  cancels a warning. That's because we can't be sure
14708                         --  there isn't an instantiation in some other unit
14709                         --  where a warning is suppressed.
14710
14711                         --  We could do a little better here by checking if the
14712                         --  generic unit we are inside is public, but for now
14713                         --  we don't bother with that refinement.
14714
14715                         if Chars (Argx) = Name_Off then
14716                            Set_Specific_Warning_Off
14717                              (Loc, Name_Buffer (1 .. Name_Len),
14718                               Config => Is_Configuration_Pragma,
14719                               Used   => Inside_A_Generic or else In_Instance);
14720
14721                         elsif Chars (Argx) = Name_On then
14722                            Set_Specific_Warning_On
14723                              (Loc, Name_Buffer (1 .. Name_Len), Err);
14724
14725                            if Err then
14726                               Error_Msg
14727                                 ("?pragma Warnings On with no " &
14728                                  "matching Warnings Off",
14729                                  Loc);
14730                            end if;
14731                         end if;
14732                      end if;
14733                   end;
14734                end if;
14735             end;
14736          end Warnings;
14737
14738          -------------------
14739          -- Weak_External --
14740          -------------------
14741
14742          --  pragma Weak_External ([Entity =>] LOCAL_NAME);
14743
14744          when Pragma_Weak_External => Weak_External : declare
14745             Ent : Entity_Id;
14746
14747          begin
14748             GNAT_Pragma;
14749             Check_Arg_Count (1);
14750             Check_Optional_Identifier (Arg1, Name_Entity);
14751             Check_Arg_Is_Library_Level_Local_Name (Arg1);
14752             Ent := Entity (Get_Pragma_Arg (Arg1));
14753
14754             if Rep_Item_Too_Early (Ent, N) then
14755                return;
14756             else
14757                Ent := Underlying_Type (Ent);
14758             end if;
14759
14760             --  The only processing required is to link this item on to the
14761             --  list of rep items for the given entity. This is accomplished
14762             --  by the call to Rep_Item_Too_Late (when no error is detected
14763             --  and False is returned).
14764
14765             if Rep_Item_Too_Late (Ent, N) then
14766                return;
14767             else
14768                Set_Has_Gigi_Rep_Item (Ent);
14769             end if;
14770          end Weak_External;
14771
14772          -----------------------------
14773          -- Wide_Character_Encoding --
14774          -----------------------------
14775
14776          --  pragma Wide_Character_Encoding (IDENTIFIER);
14777
14778          when Pragma_Wide_Character_Encoding =>
14779             GNAT_Pragma;
14780
14781             --  Nothing to do, handled in parser. Note that we do not enforce
14782             --  configuration pragma placement, this pragma can appear at any
14783             --  place in the source, allowing mixed encodings within a single
14784             --  source program.
14785
14786             null;
14787
14788          --------------------
14789          -- Unknown_Pragma --
14790          --------------------
14791
14792          --  Should be impossible, since the case of an unknown pragma is
14793          --  separately processed before the case statement is entered.
14794
14795          when Unknown_Pragma =>
14796             raise Program_Error;
14797       end case;
14798
14799       --  AI05-0144: detect dangerous order dependence. Disabled for now,
14800       --  until AI is formally approved.
14801
14802       --  Check_Order_Dependence;
14803
14804    exception
14805       when Pragma_Exit => null;
14806    end Analyze_Pragma;
14807
14808    -----------------------------
14809    -- Analyze_TC_In_Decl_Part --
14810    -----------------------------
14811
14812    procedure Analyze_TC_In_Decl_Part (N : Node_Id; S : Entity_Id) is
14813    begin
14814       --  Install formals and push subprogram spec onto scope stack so that we
14815       --  can see the formals from the pragma.
14816
14817       Install_Formals (S);
14818       Push_Scope (S);
14819
14820       --  Preanalyze the boolean expressions, we treat these as spec
14821       --  expressions (i.e. similar to a default expression).
14822
14823       Preanalyze_TC_Args (N,
14824                           Get_Requires_From_Test_Case_Pragma (N),
14825                           Get_Ensures_From_Test_Case_Pragma (N));
14826
14827       --  Remove the subprogram from the scope stack now that the pre-analysis
14828       --  of the expressions in the test-case is done.
14829
14830       End_Scope;
14831    end Analyze_TC_In_Decl_Part;
14832
14833    --------------------
14834    -- Check_Disabled --
14835    --------------------
14836
14837    function Check_Disabled (Nam : Name_Id) return Boolean is
14838       PP : Node_Id;
14839
14840    begin
14841       --  Loop through entries in check policy list
14842
14843       PP := Opt.Check_Policy_List;
14844       loop
14845          --  If there are no specific entries that matched, then nothing is
14846          --  disabled, so return False.
14847
14848          if No (PP) then
14849             return False;
14850
14851          --  Here we have an entry see if it matches
14852
14853          else
14854             declare
14855                PPA : constant List_Id := Pragma_Argument_Associations (PP);
14856             begin
14857                if Nam = Chars (Get_Pragma_Arg (First (PPA))) then
14858                   return Chars (Get_Pragma_Arg (Last (PPA))) = Name_Disable;
14859                else
14860                   PP := Next_Pragma (PP);
14861                end if;
14862             end;
14863          end if;
14864       end loop;
14865    end Check_Disabled;
14866
14867    -------------------
14868    -- Check_Enabled --
14869    -------------------
14870
14871    function Check_Enabled (Nam : Name_Id) return Boolean is
14872       PP : Node_Id;
14873
14874    begin
14875       --  Loop through entries in check policy list
14876
14877       PP := Opt.Check_Policy_List;
14878       loop
14879          --  If there are no specific entries that matched, then we let the
14880          --  setting of assertions govern. Note that this provides the needed
14881          --  compatibility with the RM for the cases of assertion, invariant,
14882          --  precondition, predicate, and postcondition.
14883
14884          if No (PP) then
14885             return Assertions_Enabled;
14886
14887          --  Here we have an entry see if it matches
14888
14889          else
14890             declare
14891                PPA : constant List_Id := Pragma_Argument_Associations (PP);
14892
14893             begin
14894                if Nam = Chars (Get_Pragma_Arg (First (PPA))) then
14895                   case (Chars (Get_Pragma_Arg (Last (PPA)))) is
14896                      when Name_On | Name_Check =>
14897                         return True;
14898                      when Name_Off | Name_Ignore =>
14899                         return False;
14900                      when others =>
14901                         raise Program_Error;
14902                   end case;
14903
14904                else
14905                   PP := Next_Pragma (PP);
14906                end if;
14907             end;
14908          end if;
14909       end loop;
14910    end Check_Enabled;
14911
14912    ---------------------------------
14913    -- Delay_Config_Pragma_Analyze --
14914    ---------------------------------
14915
14916    function Delay_Config_Pragma_Analyze (N : Node_Id) return Boolean is
14917    begin
14918       return Pragma_Name (N) = Name_Interrupt_State
14919                or else
14920              Pragma_Name (N) = Name_Priority_Specific_Dispatching;
14921    end Delay_Config_Pragma_Analyze;
14922
14923    -------------------------
14924    -- Get_Base_Subprogram --
14925    -------------------------
14926
14927    function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id is
14928       Result : Entity_Id;
14929
14930    begin
14931       --  Follow subprogram renaming chain
14932
14933       Result := Def_Id;
14934       while Is_Subprogram (Result)
14935         and then
14936           Nkind (Parent (Declaration_Node (Result))) =
14937                                          N_Subprogram_Renaming_Declaration
14938         and then Present (Alias (Result))
14939       loop
14940          Result := Alias (Result);
14941       end loop;
14942
14943       return Result;
14944    end Get_Base_Subprogram;
14945
14946    ----------------
14947    -- Initialize --
14948    ----------------
14949
14950    procedure Initialize is
14951    begin
14952       Externals.Init;
14953    end Initialize;
14954
14955    -----------------------------
14956    -- Is_Config_Static_String --
14957    -----------------------------
14958
14959    function Is_Config_Static_String (Arg : Node_Id) return Boolean is
14960
14961       function Add_Config_Static_String (Arg : Node_Id) return Boolean;
14962       --  This is an internal recursive function that is just like the outer
14963       --  function except that it adds the string to the name buffer rather
14964       --  than placing the string in the name buffer.
14965
14966       ------------------------------
14967       -- Add_Config_Static_String --
14968       ------------------------------
14969
14970       function Add_Config_Static_String (Arg : Node_Id) return Boolean is
14971          N : Node_Id;
14972          C : Char_Code;
14973
14974       begin
14975          N := Arg;
14976
14977          if Nkind (N) = N_Op_Concat then
14978             if Add_Config_Static_String (Left_Opnd (N)) then
14979                N := Right_Opnd (N);
14980             else
14981                return False;
14982             end if;
14983          end if;
14984
14985          if Nkind (N) /= N_String_Literal then
14986             Error_Msg_N ("string literal expected for pragma argument", N);
14987             return False;
14988
14989          else
14990             for J in 1 .. String_Length (Strval (N)) loop
14991                C := Get_String_Char (Strval (N), J);
14992
14993                if not In_Character_Range (C) then
14994                   Error_Msg
14995                     ("string literal contains invalid wide character",
14996                      Sloc (N) + 1 + Source_Ptr (J));
14997                   return False;
14998                end if;
14999
15000                Add_Char_To_Name_Buffer (Get_Character (C));
15001             end loop;
15002          end if;
15003
15004          return True;
15005       end Add_Config_Static_String;
15006
15007    --  Start of processing for Is_Config_Static_String
15008
15009    begin
15010
15011       Name_Len := 0;
15012       return Add_Config_Static_String (Arg);
15013    end Is_Config_Static_String;
15014
15015    -----------------------------------------
15016    -- Is_Non_Significant_Pragma_Reference --
15017    -----------------------------------------
15018
15019    --  This function makes use of the following static table which indicates
15020    --  whether appearance of some name in a given pragma is to be considered
15021    --  as a reference for the purposes of warnings about unreferenced objects.
15022
15023    --  -1  indicates that references in any argument position are significant
15024    --  0   indicates that appearance in any argument is not significant
15025    --  +n  indicates that appearance as argument n is significant, but all
15026    --      other arguments are not significant
15027    --  99  special processing required (e.g. for pragma Check)
15028
15029    Sig_Flags : constant array (Pragma_Id) of Int :=
15030      (Pragma_AST_Entry                      => -1,
15031       Pragma_Abort_Defer                    => -1,
15032       Pragma_Ada_83                         => -1,
15033       Pragma_Ada_95                         => -1,
15034       Pragma_Ada_05                         => -1,
15035       Pragma_Ada_2005                       => -1,
15036       Pragma_Ada_12                         => -1,
15037       Pragma_Ada_2012                       => -1,
15038       Pragma_All_Calls_Remote               => -1,
15039       Pragma_Annotate                       => -1,
15040       Pragma_Assert                         => -1,
15041       Pragma_Assertion_Policy               =>  0,
15042       Pragma_Assume_No_Invalid_Values       =>  0,
15043       Pragma_Asynchronous                   => -1,
15044       Pragma_Atomic                         =>  0,
15045       Pragma_Atomic_Components              =>  0,
15046       Pragma_Attach_Handler                 => -1,
15047       Pragma_Check                          => 99,
15048       Pragma_Check_Name                     =>  0,
15049       Pragma_Check_Policy                   =>  0,
15050       Pragma_CIL_Constructor                => -1,
15051       Pragma_CPP_Class                      =>  0,
15052       Pragma_CPP_Constructor                =>  0,
15053       Pragma_CPP_Virtual                    =>  0,
15054       Pragma_CPP_Vtable                     =>  0,
15055       Pragma_CPU                            => -1,
15056       Pragma_C_Pass_By_Copy                 =>  0,
15057       Pragma_Comment                        =>  0,
15058       Pragma_Common_Object                  => -1,
15059       Pragma_Compile_Time_Error             => -1,
15060       Pragma_Compile_Time_Warning           => -1,
15061       Pragma_Compiler_Unit                  =>  0,
15062       Pragma_Complete_Representation        =>  0,
15063       Pragma_Complex_Representation         =>  0,
15064       Pragma_Component_Alignment            => -1,
15065       Pragma_Controlled                     =>  0,
15066       Pragma_Convention                     =>  0,
15067       Pragma_Convention_Identifier          =>  0,
15068       Pragma_Debug                          => -1,
15069       Pragma_Debug_Policy                   =>  0,
15070       Pragma_Detect_Blocking                => -1,
15071       Pragma_Default_Storage_Pool           => -1,
15072       Pragma_Disable_Atomic_Synchronization => -1,
15073       Pragma_Discard_Names                  =>  0,
15074       Pragma_Dispatching_Domain             => -1,
15075       Pragma_Elaborate                      => -1,
15076       Pragma_Elaborate_All                  => -1,
15077       Pragma_Elaborate_Body                 => -1,
15078       Pragma_Elaboration_Checks             => -1,
15079       Pragma_Eliminate                      => -1,
15080       Pragma_Enable_Atomic_Synchronization  => -1,
15081       Pragma_Export                         => -1,
15082       Pragma_Export_Exception               => -1,
15083       Pragma_Export_Function                => -1,
15084       Pragma_Export_Object                  => -1,
15085       Pragma_Export_Procedure               => -1,
15086       Pragma_Export_Value                   => -1,
15087       Pragma_Export_Valued_Procedure        => -1,
15088       Pragma_Extend_System                  => -1,
15089       Pragma_Extensions_Allowed             => -1,
15090       Pragma_External                       => -1,
15091       Pragma_Favor_Top_Level                => -1,
15092       Pragma_External_Name_Casing           => -1,
15093       Pragma_Fast_Math                      => -1,
15094       Pragma_Finalize_Storage_Only          =>  0,
15095       Pragma_Float_Representation           =>  0,
15096       Pragma_Ident                          => -1,
15097       Pragma_Implementation_Defined         => -1,
15098       Pragma_Implemented                    => -1,
15099       Pragma_Implicit_Packing               =>  0,
15100       Pragma_Import                         => +2,
15101       Pragma_Import_Exception               =>  0,
15102       Pragma_Import_Function                =>  0,
15103       Pragma_Import_Object                  =>  0,
15104       Pragma_Import_Procedure               =>  0,
15105       Pragma_Import_Valued_Procedure        =>  0,
15106       Pragma_Independent                    =>  0,
15107       Pragma_Independent_Components         =>  0,
15108       Pragma_Initialize_Scalars             => -1,
15109       Pragma_Inline                         =>  0,
15110       Pragma_Inline_Always                  =>  0,
15111       Pragma_Inline_Generic                 =>  0,
15112       Pragma_Inspection_Point               => -1,
15113       Pragma_Interface                      => +2,
15114       Pragma_Interface_Name                 => +2,
15115       Pragma_Interrupt_Handler              => -1,
15116       Pragma_Interrupt_Priority             => -1,
15117       Pragma_Interrupt_State                => -1,
15118       Pragma_Invariant                      => -1,
15119       Pragma_Java_Constructor               => -1,
15120       Pragma_Java_Interface                 => -1,
15121       Pragma_Keep_Names                     =>  0,
15122       Pragma_License                        => -1,
15123       Pragma_Link_With                      => -1,
15124       Pragma_Linker_Alias                   => -1,
15125       Pragma_Linker_Constructor             => -1,
15126       Pragma_Linker_Destructor              => -1,
15127       Pragma_Linker_Options                 => -1,
15128       Pragma_Linker_Section                 => -1,
15129       Pragma_List                           => -1,
15130       Pragma_Locking_Policy                 => -1,
15131       Pragma_Long_Float                     => -1,
15132       Pragma_Machine_Attribute              => -1,
15133       Pragma_Main                           => -1,
15134       Pragma_Main_Storage                   => -1,
15135       Pragma_Memory_Size                    => -1,
15136       Pragma_No_Return                      =>  0,
15137       Pragma_No_Body                        =>  0,
15138       Pragma_No_Run_Time                    => -1,
15139       Pragma_No_Strict_Aliasing             => -1,
15140       Pragma_Normalize_Scalars              => -1,
15141       Pragma_Obsolescent                    =>  0,
15142       Pragma_Optimize                       => -1,
15143       Pragma_Optimize_Alignment             => -1,
15144       Pragma_Ordered                        =>  0,
15145       Pragma_Pack                           =>  0,
15146       Pragma_Page                           => -1,
15147       Pragma_Passive                        => -1,
15148       Pragma_Preelaborable_Initialization   => -1,
15149       Pragma_Polling                        => -1,
15150       Pragma_Persistent_BSS                 =>  0,
15151       Pragma_Postcondition                  => -1,
15152       Pragma_Precondition                   => -1,
15153       Pragma_Predicate                      => -1,
15154       Pragma_Preelaborate                   => -1,
15155       Pragma_Preelaborate_05                => -1,
15156       Pragma_Priority                       => -1,
15157       Pragma_Priority_Specific_Dispatching  => -1,
15158       Pragma_Profile                        =>  0,
15159       Pragma_Profile_Warnings               =>  0,
15160       Pragma_Propagate_Exceptions           => -1,
15161       Pragma_Psect_Object                   => -1,
15162       Pragma_Pure                           => -1,
15163       Pragma_Pure_05                        => -1,
15164       Pragma_Pure_12                        => -1,
15165       Pragma_Pure_Function                  => -1,
15166       Pragma_Queuing_Policy                 => -1,
15167       Pragma_Ravenscar                      => -1,
15168       Pragma_Relative_Deadline              => -1,
15169       Pragma_Remote_Access_Type             => -1,
15170       Pragma_Remote_Call_Interface          => -1,
15171       Pragma_Remote_Types                   => -1,
15172       Pragma_Restricted_Run_Time            => -1,
15173       Pragma_Restriction_Warnings           => -1,
15174       Pragma_Restrictions                   => -1,
15175       Pragma_Reviewable                     => -1,
15176       Pragma_Short_Circuit_And_Or           => -1,
15177       Pragma_Share_Generic                  => -1,
15178       Pragma_Shared                         => -1,
15179       Pragma_Shared_Passive                 => -1,
15180       Pragma_Short_Descriptors              =>  0,
15181       Pragma_Simple_Storage_Pool_Type       =>  0,
15182       Pragma_Source_File_Name               => -1,
15183       Pragma_Source_File_Name_Project       => -1,
15184       Pragma_Source_Reference               => -1,
15185       Pragma_Storage_Size                   => -1,
15186       Pragma_Storage_Unit                   => -1,
15187       Pragma_Static_Elaboration_Desired     => -1,
15188       Pragma_Stream_Convert                 => -1,
15189       Pragma_Style_Checks                   => -1,
15190       Pragma_Subtitle                       => -1,
15191       Pragma_Suppress                       =>  0,
15192       Pragma_Suppress_Exception_Locations   =>  0,
15193       Pragma_Suppress_All                   => -1,
15194       Pragma_Suppress_Debug_Info            =>  0,
15195       Pragma_Suppress_Initialization        =>  0,
15196       Pragma_System_Name                    => -1,
15197       Pragma_Task_Dispatching_Policy        => -1,
15198       Pragma_Task_Info                      => -1,
15199       Pragma_Task_Name                      => -1,
15200       Pragma_Task_Storage                   =>  0,
15201       Pragma_Test_Case                      => -1,
15202       Pragma_Thread_Local_Storage           =>  0,
15203       Pragma_Time_Slice                     => -1,
15204       Pragma_Title                          => -1,
15205       Pragma_Unchecked_Union                =>  0,
15206       Pragma_Unimplemented_Unit             => -1,
15207       Pragma_Universal_Aliasing             => -1,
15208       Pragma_Universal_Data                 => -1,
15209       Pragma_Unmodified                     => -1,
15210       Pragma_Unreferenced                   => -1,
15211       Pragma_Unreferenced_Objects           => -1,
15212       Pragma_Unreserve_All_Interrupts       => -1,
15213       Pragma_Unsuppress                     =>  0,
15214       Pragma_Use_VADS_Size                  => -1,
15215       Pragma_Validity_Checks                => -1,
15216       Pragma_Volatile                       =>  0,
15217       Pragma_Volatile_Components            =>  0,
15218       Pragma_Warnings                       => -1,
15219       Pragma_Weak_External                  => -1,
15220       Pragma_Wide_Character_Encoding        =>  0,
15221       Unknown_Pragma                        =>  0);
15222
15223    function Is_Non_Significant_Pragma_Reference (N : Node_Id) return Boolean is
15224       Id : Pragma_Id;
15225       P  : Node_Id;
15226       C  : Int;
15227       A  : Node_Id;
15228
15229    begin
15230       P := Parent (N);
15231
15232       if Nkind (P) /= N_Pragma_Argument_Association then
15233          return False;
15234
15235       else
15236          Id := Get_Pragma_Id (Parent (P));
15237          C := Sig_Flags (Id);
15238
15239          case C is
15240             when -1 =>
15241                return False;
15242
15243             when 0 =>
15244                return True;
15245
15246             when 99 =>
15247                case Id is
15248
15249                   --  For pragma Check, the first argument is not significant,
15250                   --  the second and the third (if present) arguments are
15251                   --  significant.
15252
15253                   when Pragma_Check =>
15254                      return
15255                        P = First (Pragma_Argument_Associations (Parent (P)));
15256
15257                   when others =>
15258                      raise Program_Error;
15259                end case;
15260
15261             when others =>
15262                A := First (Pragma_Argument_Associations (Parent (P)));
15263                for J in 1 .. C - 1 loop
15264                   if No (A) then
15265                      return False;
15266                   end if;
15267
15268                   Next (A);
15269                end loop;
15270
15271                return A = P; -- is this wrong way round ???
15272          end case;
15273       end if;
15274    end Is_Non_Significant_Pragma_Reference;
15275
15276    ------------------------------
15277    -- Is_Pragma_String_Literal --
15278    ------------------------------
15279
15280    --  This function returns true if the corresponding pragma argument is a
15281    --  static string expression. These are the only cases in which string
15282    --  literals can appear as pragma arguments. We also allow a string literal
15283    --  as the first argument to pragma Assert (although it will of course
15284    --  always generate a type error).
15285
15286    function Is_Pragma_String_Literal (Par : Node_Id) return Boolean is
15287       Pragn : constant Node_Id := Parent (Par);
15288       Assoc : constant List_Id := Pragma_Argument_Associations (Pragn);
15289       Pname : constant Name_Id := Pragma_Name (Pragn);
15290       Argn  : Natural;
15291       N     : Node_Id;
15292
15293    begin
15294       Argn := 1;
15295       N := First (Assoc);
15296       loop
15297          exit when N = Par;
15298          Argn := Argn + 1;
15299          Next (N);
15300       end loop;
15301
15302       if Pname = Name_Assert then
15303          return True;
15304
15305       elsif Pname = Name_Export then
15306          return Argn > 2;
15307
15308       elsif Pname = Name_Ident then
15309          return Argn = 1;
15310
15311       elsif Pname = Name_Import then
15312          return Argn > 2;
15313
15314       elsif Pname = Name_Interface_Name then
15315          return Argn > 1;
15316
15317       elsif Pname = Name_Linker_Alias then
15318          return Argn = 2;
15319
15320       elsif Pname = Name_Linker_Section then
15321          return Argn = 2;
15322
15323       elsif Pname = Name_Machine_Attribute then
15324          return Argn = 2;
15325
15326       elsif Pname = Name_Source_File_Name then
15327          return True;
15328
15329       elsif Pname = Name_Source_Reference then
15330          return Argn = 2;
15331
15332       elsif Pname = Name_Title then
15333          return True;
15334
15335       elsif Pname = Name_Subtitle then
15336          return True;
15337
15338       else
15339          return False;
15340       end if;
15341    end Is_Pragma_String_Literal;
15342
15343    -----------------------------------------
15344    -- Make_Aspect_For_PPC_In_Gen_Sub_Decl --
15345    -----------------------------------------
15346
15347    procedure Make_Aspect_For_PPC_In_Gen_Sub_Decl (Decl : Node_Id) is
15348       Aspects : constant List_Id := New_List;
15349       Loc     : constant Source_Ptr := Sloc (Decl);
15350       Or_Decl : constant Node_Id := Original_Node (Decl);
15351
15352       Original_Aspects : List_Id;
15353       --  To capture global references, a copy of the created aspects must be
15354       --  inserted in the original tree.
15355
15356       Prag         : Node_Id;
15357       Prag_Arg_Ass : Node_Id;
15358       Prag_Id      : Pragma_Id;
15359
15360    begin
15361       --  Check for any PPC pragmas that appear within Decl
15362
15363       Prag := Next (Decl);
15364       while Nkind (Prag) = N_Pragma loop
15365          Prag_Id := Get_Pragma_Id (Chars (Pragma_Identifier (Prag)));
15366
15367          case Prag_Id is
15368             when Pragma_Postcondition | Pragma_Precondition =>
15369                Prag_Arg_Ass := First (Pragma_Argument_Associations (Prag));
15370
15371                --  Make an aspect from any PPC pragma
15372
15373                Append_To (Aspects,
15374                  Make_Aspect_Specification (Loc,
15375                    Identifier =>
15376                      Make_Identifier (Loc, Chars (Pragma_Identifier (Prag))),
15377                    Expression =>
15378                      Copy_Separate_Tree (Expression (Prag_Arg_Ass))));
15379
15380                --  Generate the analysis information in the pragma expression
15381                --  and then set the pragma node analyzed to avoid any further
15382                --  analysis.
15383
15384                Analyze (Expression (Prag_Arg_Ass));
15385                Set_Analyzed (Prag, True);
15386
15387             when others => null;
15388          end case;
15389
15390          Next (Prag);
15391       end loop;
15392
15393       --  Set all new aspects into the generic declaration node
15394
15395       if Is_Non_Empty_List (Aspects) then
15396
15397          --  Create the list of aspects to be inserted in the original tree
15398
15399          Original_Aspects := Copy_Separate_List (Aspects);
15400
15401          --  Check if Decl already has aspects
15402
15403          --  Attach the new lists of aspects to both the generic copy and the
15404          --  original tree.
15405
15406          if Has_Aspects (Decl) then
15407             Append_List (Aspects, Aspect_Specifications (Decl));
15408             Append_List (Original_Aspects, Aspect_Specifications (Or_Decl));
15409
15410          else
15411             Set_Parent (Aspects, Decl);
15412             Set_Aspect_Specifications (Decl, Aspects);
15413             Set_Parent (Original_Aspects, Or_Decl);
15414             Set_Aspect_Specifications (Or_Decl, Original_Aspects);
15415          end if;
15416       end if;
15417    end Make_Aspect_For_PPC_In_Gen_Sub_Decl;
15418
15419    ------------------------
15420    -- Preanalyze_TC_Args --
15421    ------------------------
15422
15423    procedure Preanalyze_TC_Args (N, Arg_Req, Arg_Ens : Node_Id) is
15424    begin
15425       --  Preanalyze the boolean expressions, we treat these as spec
15426       --  expressions (i.e. similar to a default expression).
15427
15428       if Present (Arg_Req) then
15429          Preanalyze_Spec_Expression
15430            (Get_Pragma_Arg (Arg_Req), Standard_Boolean);
15431
15432          --  In ASIS mode, for a pragma generated from a source aspect, also
15433          --  analyze the original aspect expression.
15434
15435          if ASIS_Mode and then Present (Corresponding_Aspect (N)) then
15436             Preanalyze_Spec_Expression
15437               (Original_Node (Get_Pragma_Arg (Arg_Req)), Standard_Boolean);
15438          end if;
15439       end if;
15440
15441       if Present (Arg_Ens) then
15442          Preanalyze_Spec_Expression
15443            (Get_Pragma_Arg (Arg_Ens), Standard_Boolean);
15444
15445          --  In ASIS mode, for a pragma generated from a source aspect, also
15446          --  analyze the original aspect expression.
15447
15448          if ASIS_Mode and then Present (Corresponding_Aspect (N)) then
15449             Preanalyze_Spec_Expression
15450               (Original_Node (Get_Pragma_Arg (Arg_Ens)), Standard_Boolean);
15451          end if;
15452       end if;
15453    end Preanalyze_TC_Args;
15454
15455    --------------------------------------
15456    -- Process_Compilation_Unit_Pragmas --
15457    --------------------------------------
15458
15459    procedure Process_Compilation_Unit_Pragmas (N : Node_Id) is
15460    begin
15461       --  A special check for pragma Suppress_All, a very strange DEC pragma,
15462       --  strange because it comes at the end of the unit. Rational has the
15463       --  same name for a pragma, but treats it as a program unit pragma, In
15464       --  GNAT we just decide to allow it anywhere at all. If it appeared then
15465       --  the flag Has_Pragma_Suppress_All was set on the compilation unit
15466       --  node, and we insert a pragma Suppress (All_Checks) at the start of
15467       --  the context clause to ensure the correct processing.
15468
15469       if Has_Pragma_Suppress_All (N) then
15470          Prepend_To (Context_Items (N),
15471            Make_Pragma (Sloc (N),
15472              Chars                        => Name_Suppress,
15473              Pragma_Argument_Associations => New_List (
15474                Make_Pragma_Argument_Association (Sloc (N),
15475                  Expression => Make_Identifier (Sloc (N), Name_All_Checks)))));
15476       end if;
15477
15478       --  Nothing else to do at the current time!
15479
15480    end Process_Compilation_Unit_Pragmas;
15481
15482    --------
15483    -- rv --
15484    --------
15485
15486    procedure rv is
15487    begin
15488       null;
15489    end rv;
15490
15491    --------------------------------
15492    -- Set_Encoded_Interface_Name --
15493    --------------------------------
15494
15495    procedure Set_Encoded_Interface_Name (E : Entity_Id; S : Node_Id) is
15496       Str : constant String_Id := Strval (S);
15497       Len : constant Int       := String_Length (Str);
15498       CC  : Char_Code;
15499       C   : Character;
15500       J   : Int;
15501
15502       Hex : constant array (0 .. 15) of Character := "0123456789abcdef";
15503
15504       procedure Encode;
15505       --  Stores encoded value of character code CC. The encoding we use an
15506       --  underscore followed by four lower case hex digits.
15507
15508       ------------
15509       -- Encode --
15510       ------------
15511
15512       procedure Encode is
15513       begin
15514          Store_String_Char (Get_Char_Code ('_'));
15515          Store_String_Char
15516            (Get_Char_Code (Hex (Integer (CC / 2 ** 12))));
15517          Store_String_Char
15518            (Get_Char_Code (Hex (Integer (CC / 2 ** 8 and 16#0F#))));
15519          Store_String_Char
15520            (Get_Char_Code (Hex (Integer (CC / 2 ** 4 and 16#0F#))));
15521          Store_String_Char
15522            (Get_Char_Code (Hex (Integer (CC and 16#0F#))));
15523       end Encode;
15524
15525    --  Start of processing for Set_Encoded_Interface_Name
15526
15527    begin
15528       --  If first character is asterisk, this is a link name, and we leave it
15529       --  completely unmodified. We also ignore null strings (the latter case
15530       --  happens only in error cases) and no encoding should occur for Java or
15531       --  AAMP interface names.
15532
15533       if Len = 0
15534         or else Get_String_Char (Str, 1) = Get_Char_Code ('*')
15535         or else VM_Target /= No_VM
15536         or else AAMP_On_Target
15537       then
15538          Set_Interface_Name (E, S);
15539
15540       else
15541          J := 1;
15542          loop
15543             CC := Get_String_Char (Str, J);
15544
15545             exit when not In_Character_Range (CC);
15546
15547             C := Get_Character (CC);
15548
15549             exit when C /= '_' and then C /= '$'
15550               and then C not in '0' .. '9'
15551               and then C not in 'a' .. 'z'
15552               and then C not in 'A' .. 'Z';
15553
15554             if J = Len then
15555                Set_Interface_Name (E, S);
15556                return;
15557
15558             else
15559                J := J + 1;
15560             end if;
15561          end loop;
15562
15563          --  Here we need to encode. The encoding we use as follows:
15564          --     three underscores  + four hex digits (lower case)
15565
15566          Start_String;
15567
15568          for J in 1 .. String_Length (Str) loop
15569             CC := Get_String_Char (Str, J);
15570
15571             if not In_Character_Range (CC) then
15572                Encode;
15573             else
15574                C := Get_Character (CC);
15575
15576                if C = '_' or else C = '$'
15577                  or else C in '0' .. '9'
15578                  or else C in 'a' .. 'z'
15579                  or else C in 'A' .. 'Z'
15580                then
15581                   Store_String_Char (CC);
15582                else
15583                   Encode;
15584                end if;
15585             end if;
15586          end loop;
15587
15588          Set_Interface_Name (E,
15589            Make_String_Literal (Sloc (S),
15590              Strval => End_String));
15591       end if;
15592    end Set_Encoded_Interface_Name;
15593
15594    -------------------
15595    -- Set_Unit_Name --
15596    -------------------
15597
15598    procedure Set_Unit_Name (N : Node_Id; With_Item : Node_Id) is
15599       Pref : Node_Id;
15600       Scop : Entity_Id;
15601
15602    begin
15603       if Nkind (N) = N_Identifier
15604         and then Nkind (With_Item) = N_Identifier
15605       then
15606          Set_Entity (N, Entity (With_Item));
15607
15608       elsif Nkind (N) = N_Selected_Component then
15609          Change_Selected_Component_To_Expanded_Name (N);
15610          Set_Entity (N, Entity (With_Item));
15611          Set_Entity (Selector_Name (N), Entity (N));
15612
15613          Pref := Prefix (N);
15614          Scop := Scope (Entity (N));
15615          while Nkind (Pref) = N_Selected_Component loop
15616             Change_Selected_Component_To_Expanded_Name (Pref);
15617             Set_Entity (Selector_Name (Pref), Scop);
15618             Set_Entity (Pref, Scop);
15619             Pref := Prefix (Pref);
15620             Scop := Scope (Scop);
15621          end loop;
15622
15623          Set_Entity (Pref, Scop);
15624       end if;
15625    end Set_Unit_Name;
15626
15627 end Sem_Prag;