2015-01-06 Eric Botcazou <ebotcazou@adacore.com>
[official-gcc.git] / gcc / ada / sem_prag.adb
blob74607e576550d98867e596bde6b6cba4b1e03ccf
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-2014, 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 ------------------------------------------------------------------------------
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).
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 Output; use Output;
51 with Par_SCO; use Par_SCO;
52 with Restrict; use Restrict;
53 with Rident; use Rident;
54 with Rtsfind; use Rtsfind;
55 with Sem; use Sem;
56 with Sem_Aux; use Sem_Aux;
57 with Sem_Ch3; use Sem_Ch3;
58 with Sem_Ch6; use Sem_Ch6;
59 with Sem_Ch8; use Sem_Ch8;
60 with Sem_Ch12; use Sem_Ch12;
61 with Sem_Ch13; use Sem_Ch13;
62 with Sem_Disp; use Sem_Disp;
63 with Sem_Dist; use Sem_Dist;
64 with Sem_Elim; use Sem_Elim;
65 with Sem_Eval; use Sem_Eval;
66 with Sem_Intr; use Sem_Intr;
67 with Sem_Mech; use Sem_Mech;
68 with Sem_Res; use Sem_Res;
69 with Sem_Type; use Sem_Type;
70 with Sem_Util; use Sem_Util;
71 with Sem_Warn; use Sem_Warn;
72 with Stand; use Stand;
73 with Sinfo; use Sinfo;
74 with Sinfo.CN; use Sinfo.CN;
75 with Sinput; use Sinput;
76 with Stringt; use Stringt;
77 with Stylesw; use Stylesw;
78 with Table;
79 with Targparm; use Targparm;
80 with Tbuild; use Tbuild;
81 with Ttypes;
82 with Uintp; use Uintp;
83 with Uname; use Uname;
84 with Urealp; use Urealp;
85 with Validsw; use Validsw;
86 with Warnsw; use Warnsw;
88 package body Sem_Prag is
90 ----------------------------------------------
91 -- Common Handling of Import-Export Pragmas --
92 ----------------------------------------------
94 -- In the following section, a number of Import_xxx and Export_xxx pragmas
95 -- are defined by GNAT. These are compatible with the DEC pragmas of the
96 -- same name, and all have the following common form and processing:
98 -- pragma Export_xxx
99 -- [Internal =>] LOCAL_NAME
100 -- [, [External =>] EXTERNAL_SYMBOL]
101 -- [, other optional parameters ]);
103 -- pragma Import_xxx
104 -- [Internal =>] LOCAL_NAME
105 -- [, [External =>] EXTERNAL_SYMBOL]
106 -- [, other optional parameters ]);
108 -- EXTERNAL_SYMBOL ::=
109 -- IDENTIFIER
110 -- | static_string_EXPRESSION
112 -- The internal LOCAL_NAME designates the entity that is imported or
113 -- exported, and must refer to an entity in the current declarative
114 -- part (as required by the rules for LOCAL_NAME).
116 -- The external linker name is designated by the External parameter if
117 -- given, or the Internal parameter if not (if there is no External
118 -- parameter, the External parameter is a copy of the Internal name).
120 -- If the External parameter is given as a string, then this string is
121 -- treated as an external name (exactly as though it had been given as an
122 -- External_Name parameter for a normal Import pragma).
124 -- If the External parameter is given as an identifier (or there is no
125 -- External parameter, so that the Internal identifier is used), then
126 -- the external name is the characters of the identifier, translated
127 -- to all lower case letters.
129 -- Note: the external name specified or implied by any of these special
130 -- Import_xxx or Export_xxx pragmas override an external or link name
131 -- specified in a previous Import or Export pragma.
133 -- Note: these and all other DEC-compatible GNAT pragmas allow full use of
134 -- named notation, following the standard rules for subprogram calls, i.e.
135 -- parameters can be given in any order if named notation is used, and
136 -- positional and named notation can be mixed, subject to the rule that all
137 -- positional parameters must appear first.
139 -- Note: All these pragmas are implemented exactly following the DEC design
140 -- and implementation and are intended to be fully compatible with the use
141 -- of these pragmas in the DEC Ada compiler.
143 --------------------------------------------
144 -- Checking for Duplicated External Names --
145 --------------------------------------------
147 -- It is suspicious if two separate Export pragmas use the same external
148 -- name. The following table is used to diagnose this situation so that
149 -- an appropriate warning can be issued.
151 -- The Node_Id stored is for the N_String_Literal node created to hold
152 -- the value of the external name. The Sloc of this node is used to
153 -- cross-reference the location of the duplication.
155 package Externals is new Table.Table (
156 Table_Component_Type => Node_Id,
157 Table_Index_Type => Int,
158 Table_Low_Bound => 0,
159 Table_Initial => 100,
160 Table_Increment => 100,
161 Table_Name => "Name_Externals");
163 -------------------------------------
164 -- Local Subprograms and Variables --
165 -------------------------------------
167 procedure Add_Item (Item : Entity_Id; To_List : in out Elist_Id);
168 -- Subsidiary routine to the analysis of pragmas Depends, Global and
169 -- Refined_State. Append an entity to a list. If the list is empty, create
170 -- a new list.
172 function Adjust_External_Name_Case (N : Node_Id) return Node_Id;
173 -- This routine is used for possible casing adjustment of an explicit
174 -- external name supplied as a string literal (the node N), according to
175 -- the casing requirement of Opt.External_Name_Casing. If this is set to
176 -- As_Is, then the string literal is returned unchanged, but if it is set
177 -- to Uppercase or Lowercase, then a new string literal with appropriate
178 -- casing is constructed.
180 function Appears_In (List : Elist_Id; Item_Id : Entity_Id) return Boolean;
181 -- Subsidiary to analysis of pragmas Depends, Global and Refined_Depends.
182 -- Query whether a particular item appears in a mixed list of nodes and
183 -- entities. It is assumed that all nodes in the list have entities.
185 function Check_Kind (Nam : Name_Id) return Name_Id;
186 -- This function is used in connection with pragmas Assert, Check,
187 -- and assertion aspects and pragmas, to determine if Check pragmas
188 -- (or corresponding assertion aspects or pragmas) are currently active
189 -- as determined by the presence of -gnata on the command line (which
190 -- sets the default), and the appearance of pragmas Check_Policy and
191 -- Assertion_Policy as configuration pragmas either in a configuration
192 -- pragma file, or at the start of the current unit, or locally given
193 -- Check_Policy and Assertion_Policy pragmas that are currently active.
195 -- The value returned is one of the names Check, Ignore, Disable (On
196 -- returns Check, and Off returns Ignore).
198 -- Note: for assertion kinds Pre'Class, Post'Class, Invariant'Class,
199 -- and Type_Invariant'Class, the name passed is Name_uPre, Name_uPost,
200 -- Name_uInvariant, or Name_uType_Invariant, which corresponds to _Pre,
201 -- _Post, _Invariant, or _Type_Invariant, which are special names used
202 -- in identifiers to represent these attribute references.
204 procedure Check_SPARK_Aspect_For_ASIS (N : Node_Id);
205 -- In ASIS mode we need to analyze the original expression in the aspect
206 -- specification. For Initializes, Global, and related SPARK aspects, the
207 -- expression has a sui-generis syntax which may be a list, an expression,
208 -- or an aggregate.
210 procedure Check_State_And_Constituent_Use
211 (States : Elist_Id;
212 Constits : Elist_Id;
213 Context : Node_Id);
214 -- Subsidiary to the analysis of pragmas [Refined_]Depends, [Refined_]
215 -- Global and Initializes. Determine whether a state from list States and a
216 -- corresponding constituent from list Constits (if any) appear in the same
217 -- context denoted by Context. If this is the case, emit an error.
219 function Find_Related_Subprogram_Or_Body
220 (Prag : Node_Id;
221 Do_Checks : Boolean := False) return Node_Id;
222 -- Subsidiary to the analysis of pragmas Contract_Cases, Depends, Global,
223 -- Refined_Depends, Refined_Global and Refined_Post. Find the declaration
224 -- of the related subprogram [body or stub] subject to pragma Prag. If flag
225 -- Do_Checks is set, the routine reports duplicate pragmas and detects
226 -- improper use of refinement pragmas in stand alone expression functions.
227 -- The returned value depends on the related pragma as follows:
228 -- 1) Pragmas Contract_Cases, Depends and Global yield the corresponding
229 -- N_Subprogram_Declaration node or if the pragma applies to a stand
230 -- alone body, the N_Subprogram_Body node or Empty if illegal.
231 -- 2) Pragmas Refined_Depends, Refined_Global and Refined_Post yield
232 -- N_Subprogram_Body or N_Subprogram_Body_Stub nodes or Empty if
233 -- illegal.
235 function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id;
236 -- If Def_Id refers to a renamed subprogram, then the base subprogram (the
237 -- original one, following the renaming chain) is returned. Otherwise the
238 -- entity is returned unchanged. Should be in Einfo???
240 function Get_SPARK_Mode_Type (N : Name_Id) return SPARK_Mode_Type;
241 -- Subsidiary to the analysis of pragma SPARK_Mode as well as subprogram
242 -- Get_SPARK_Mode_Type. Convert a name into a corresponding value of type
243 -- SPARK_Mode_Type.
245 function Has_Extra_Parentheses (Clause : Node_Id) return Boolean;
246 -- Subsidiary to the analysis of pragmas Depends and Refined_Depends.
247 -- Determine whether dependency clause Clause is surrounded by extra
248 -- parentheses. If this is the case, issue an error message.
250 function Is_Unconstrained_Or_Tagged_Item (Item : Entity_Id) return Boolean;
251 -- Subsidiary to Collect_Subprogram_Inputs_Outputs and the analysis of
252 -- pragma Depends. Determine whether the type of dependency item Item is
253 -- tagged, unconstrained array, unconstrained record or a record with at
254 -- least one unconstrained component.
256 procedure Preanalyze_CTC_Args (N, Arg_Req, Arg_Ens : Node_Id);
257 -- Preanalyze the boolean expressions in the Requires and Ensures arguments
258 -- of a Test_Case pragma if present (possibly Empty). We treat these as
259 -- spec expressions (i.e. similar to a default expression).
261 procedure Record_Possible_Body_Reference
262 (State_Id : Entity_Id;
263 Ref : Node_Id);
264 -- Subsidiary to the analysis of pragmas [Refined_]Depends and [Refined_]
265 -- Global. Given an abstract state denoted by State_Id and a reference Ref
266 -- to it, determine whether the reference appears in a package body that
267 -- will eventually refine the state. If this is the case, record the
268 -- reference for future checks (see Analyze_Refined_State_In_Decls).
270 procedure Resolve_State (N : Node_Id);
271 -- Handle the overloading of state names by functions. When N denotes a
272 -- function, this routine finds the corresponding state and sets the entity
273 -- of N to that of the state.
275 procedure Rewrite_Assertion_Kind (N : Node_Id);
276 -- If N is Pre'Class, Post'Class, Invariant'Class, or Type_Invariant'Class,
277 -- then it is rewritten as an identifier with the corresponding special
278 -- name _Pre, _Post, _Invariant, or _Type_Invariant. Used by pragmas
279 -- Check, Check_Policy.
281 procedure Set_Unit_Name (N : Node_Id; With_Item : Node_Id);
282 -- Place semantic information on the argument of an Elaborate/Elaborate_All
283 -- pragma. Entity name for unit and its parents is taken from item in
284 -- previous with_clause that mentions the unit.
286 Dummy : Integer := 0;
287 pragma Volatile (Dummy);
288 -- Dummy volatile integer used in bodies of ip/rv to prevent optimization
290 procedure ip;
291 pragma No_Inline (ip);
292 -- A dummy procedure called when pragma Inspection_Point is analyzed. This
293 -- is just to help debugging the front end. If a pragma Inspection_Point
294 -- is added to a source program, then breaking on ip will get you to that
295 -- point in the program.
297 procedure rv;
298 pragma No_Inline (rv);
299 -- This is a dummy function called by the processing for pragma Reviewable.
300 -- It is there for assisting front end debugging. By placing a Reviewable
301 -- pragma in the source program, a breakpoint on rv catches this place in
302 -- the source, allowing convenient stepping to the point of interest.
304 --------------
305 -- Add_Item --
306 --------------
308 procedure Add_Item (Item : Entity_Id; To_List : in out Elist_Id) is
309 begin
310 Append_New_Elmt (Item, To => To_List);
311 end Add_Item;
313 -------------------------------
314 -- Adjust_External_Name_Case --
315 -------------------------------
317 function Adjust_External_Name_Case (N : Node_Id) return Node_Id is
318 CC : Char_Code;
320 begin
321 -- Adjust case of literal if required
323 if Opt.External_Name_Exp_Casing = As_Is then
324 return N;
326 else
327 -- Copy existing string
329 Start_String;
331 -- Set proper casing
333 for J in 1 .. String_Length (Strval (N)) loop
334 CC := Get_String_Char (Strval (N), J);
336 if Opt.External_Name_Exp_Casing = Uppercase
337 and then CC >= Get_Char_Code ('a')
338 and then CC <= Get_Char_Code ('z')
339 then
340 Store_String_Char (CC - 32);
342 elsif Opt.External_Name_Exp_Casing = Lowercase
343 and then CC >= Get_Char_Code ('A')
344 and then CC <= Get_Char_Code ('Z')
345 then
346 Store_String_Char (CC + 32);
348 else
349 Store_String_Char (CC);
350 end if;
351 end loop;
353 return
354 Make_String_Literal (Sloc (N),
355 Strval => End_String);
356 end if;
357 end Adjust_External_Name_Case;
359 -----------------------------------------
360 -- Analyze_Contract_Cases_In_Decl_Part --
361 -----------------------------------------
363 procedure Analyze_Contract_Cases_In_Decl_Part (N : Node_Id) is
364 Others_Seen : Boolean := False;
366 procedure Analyze_Contract_Case (CCase : Node_Id);
367 -- Verify the legality of a single contract case
369 ---------------------------
370 -- Analyze_Contract_Case --
371 ---------------------------
373 procedure Analyze_Contract_Case (CCase : Node_Id) is
374 Case_Guard : Node_Id;
375 Conseq : Node_Id;
376 Extra_Guard : Node_Id;
378 begin
379 if Nkind (CCase) = N_Component_Association then
380 Case_Guard := First (Choices (CCase));
381 Conseq := Expression (CCase);
383 -- Each contract case must have exactly one case guard
385 Extra_Guard := Next (Case_Guard);
387 if Present (Extra_Guard) then
388 Error_Msg_N
389 ("contract case must have exactly one case guard",
390 Extra_Guard);
391 end if;
393 -- Check placement of OTHERS if available (SPARK RM 6.1.3(1))
395 if Nkind (Case_Guard) = N_Others_Choice then
396 if Others_Seen then
397 Error_Msg_N
398 ("only one others choice allowed in contract cases",
399 Case_Guard);
400 else
401 Others_Seen := True;
402 end if;
404 elsif Others_Seen then
405 Error_Msg_N
406 ("others must be the last choice in contract cases", N);
407 end if;
409 -- Preanalyze the case guard and consequence
411 if Nkind (Case_Guard) /= N_Others_Choice then
412 Preanalyze_Assert_Expression (Case_Guard, Standard_Boolean);
413 end if;
415 Preanalyze_Assert_Expression (Conseq, Standard_Boolean);
417 -- The contract case is malformed
419 else
420 Error_Msg_N ("wrong syntax in contract case", CCase);
421 end if;
422 end Analyze_Contract_Case;
424 -- Local variables
426 All_Cases : Node_Id;
427 CCase : Node_Id;
428 Subp_Decl : Node_Id;
429 Subp_Id : Entity_Id;
431 Restore_Scope : Boolean := False;
432 -- Gets set True if we do a Push_Scope needing a Pop_Scope on exit
434 -- Start of processing for Analyze_Contract_Cases_In_Decl_Part
436 begin
437 Set_Analyzed (N);
439 Subp_Decl := Find_Related_Subprogram_Or_Body (N);
440 Subp_Id := Defining_Entity (Subp_Decl);
441 All_Cases := Get_Pragma_Arg (First (Pragma_Argument_Associations (N)));
443 -- Single and multiple contract cases must appear in aggregate form. If
444 -- this is not the case, then either the parser of the analysis of the
445 -- pragma failed to produce an aggregate.
447 pragma Assert (Nkind (All_Cases) = N_Aggregate);
449 if No (Component_Associations (All_Cases)) then
450 Error_Msg_N ("wrong syntax for constract cases", N);
452 -- Individual contract cases appear as component associations
454 else
455 -- Ensure that the formal parameters are visible when analyzing all
456 -- clauses. This falls out of the general rule of aspects pertaining
457 -- to subprogram declarations. Skip the installation for subprogram
458 -- bodies because the formals are already visible.
460 if not In_Open_Scopes (Subp_Id) then
461 Restore_Scope := True;
462 Push_Scope (Subp_Id);
463 Install_Formals (Subp_Id);
464 end if;
466 CCase := First (Component_Associations (All_Cases));
467 while Present (CCase) loop
468 Analyze_Contract_Case (CCase);
469 Next (CCase);
470 end loop;
472 if Restore_Scope then
473 End_Scope;
474 end if;
475 end if;
476 end Analyze_Contract_Cases_In_Decl_Part;
478 ----------------------------------
479 -- Analyze_Depends_In_Decl_Part --
480 ----------------------------------
482 procedure Analyze_Depends_In_Decl_Part (N : Node_Id) is
483 Loc : constant Source_Ptr := Sloc (N);
485 All_Inputs_Seen : Elist_Id := No_Elist;
486 -- A list containing the entities of all the inputs processed so far.
487 -- The list is populated with unique entities because the same input
488 -- may appear in multiple input lists.
490 All_Outputs_Seen : Elist_Id := No_Elist;
491 -- A list containing the entities of all the outputs processed so far.
492 -- The list is populated with unique entities because output items are
493 -- unique in a dependence relation.
495 Constits_Seen : Elist_Id := No_Elist;
496 -- A list containing the entities of all constituents processed so far.
497 -- It aids in detecting illegal usage of a state and a corresponding
498 -- constituent in pragma [Refinde_]Depends.
500 Global_Seen : Boolean := False;
501 -- A flag set when pragma Global has been processed
503 Null_Output_Seen : Boolean := False;
504 -- A flag used to track the legality of a null output
506 Result_Seen : Boolean := False;
507 -- A flag set when Subp_Id'Result is processed
509 Spec_Id : Entity_Id;
510 -- The entity of the subprogram subject to pragma [Refined_]Depends
512 States_Seen : Elist_Id := No_Elist;
513 -- A list containing the entities of all states processed so far. It
514 -- helps in detecting illegal usage of a state and a corresponding
515 -- constituent in pragma [Refined_]Depends.
517 Subp_Id : Entity_Id;
518 -- The entity of the subprogram [body or stub] subject to pragma
519 -- [Refined_]Depends.
521 Subp_Inputs : Elist_Id := No_Elist;
522 Subp_Outputs : Elist_Id := No_Elist;
523 -- Two lists containing the full set of inputs and output of the related
524 -- subprograms. Note that these lists contain both nodes and entities.
526 procedure Add_Item_To_Name_Buffer (Item_Id : Entity_Id);
527 -- Subsidiary routine to Check_Role and Check_Usage. Add the item kind
528 -- to the name buffer. The individual kinds are as follows:
529 -- E_Abstract_State - "state"
530 -- E_In_Parameter - "parameter"
531 -- E_In_Out_Parameter - "parameter"
532 -- E_Out_Parameter - "parameter"
533 -- E_Variable - "global"
535 procedure Analyze_Dependency_Clause
536 (Clause : Node_Id;
537 Is_Last : Boolean);
538 -- Verify the legality of a single dependency clause. Flag Is_Last
539 -- denotes whether Clause is the last clause in the relation.
541 procedure Check_Function_Return;
542 -- Verify that Funtion'Result appears as one of the outputs
543 -- (SPARK RM 6.1.5(10)).
545 procedure Check_Role
546 (Item : Node_Id;
547 Item_Id : Entity_Id;
548 Is_Input : Boolean;
549 Self_Ref : Boolean);
550 -- Ensure that an item fulfils its designated input and/or output role
551 -- as specified by pragma Global (if any) or the enclosing context. If
552 -- this is not the case, emit an error. Item and Item_Id denote the
553 -- attributes of an item. Flag Is_Input should be set when item comes
554 -- from an input list. Flag Self_Ref should be set when the item is an
555 -- output and the dependency clause has operator "+".
557 procedure Check_Usage
558 (Subp_Items : Elist_Id;
559 Used_Items : Elist_Id;
560 Is_Input : Boolean);
561 -- Verify that all items from Subp_Items appear in Used_Items. Emit an
562 -- error if this is not the case.
564 procedure Normalize_Clause (Clause : Node_Id);
565 -- Remove a self-dependency "+" from the input list of a clause
567 -----------------------------
568 -- Add_Item_To_Name_Buffer --
569 -----------------------------
571 procedure Add_Item_To_Name_Buffer (Item_Id : Entity_Id) is
572 begin
573 if Ekind (Item_Id) = E_Abstract_State then
574 Add_Str_To_Name_Buffer ("state");
576 elsif Is_Formal (Item_Id) then
577 Add_Str_To_Name_Buffer ("parameter");
579 elsif Ekind (Item_Id) = E_Variable then
580 Add_Str_To_Name_Buffer ("global");
582 -- The routine should not be called with non-SPARK items
584 else
585 raise Program_Error;
586 end if;
587 end Add_Item_To_Name_Buffer;
589 -------------------------------
590 -- Analyze_Dependency_Clause --
591 -------------------------------
593 procedure Analyze_Dependency_Clause
594 (Clause : Node_Id;
595 Is_Last : Boolean)
597 procedure Analyze_Input_List (Inputs : Node_Id);
598 -- Verify the legality of a single input list
600 procedure Analyze_Input_Output
601 (Item : Node_Id;
602 Is_Input : Boolean;
603 Self_Ref : Boolean;
604 Top_Level : Boolean;
605 Seen : in out Elist_Id;
606 Null_Seen : in out Boolean;
607 Non_Null_Seen : in out Boolean);
608 -- Verify the legality of a single input or output item. Flag
609 -- Is_Input should be set whenever Item is an input, False when it
610 -- denotes an output. Flag Self_Ref should be set when the item is an
611 -- output and the dependency clause has a "+". Flag Top_Level should
612 -- be set whenever Item appears immediately within an input or output
613 -- list. Seen is a collection of all abstract states, variables and
614 -- formals processed so far. Flag Null_Seen denotes whether a null
615 -- input or output has been encountered. Flag Non_Null_Seen denotes
616 -- whether a non-null input or output has been encountered.
618 ------------------------
619 -- Analyze_Input_List --
620 ------------------------
622 procedure Analyze_Input_List (Inputs : Node_Id) is
623 Inputs_Seen : Elist_Id := No_Elist;
624 -- A list containing the entities of all inputs that appear in the
625 -- current input list.
627 Non_Null_Input_Seen : Boolean := False;
628 Null_Input_Seen : Boolean := False;
629 -- Flags used to check the legality of an input list
631 Input : Node_Id;
633 begin
634 -- Multiple inputs appear as an aggregate
636 if Nkind (Inputs) = N_Aggregate then
637 if Present (Component_Associations (Inputs)) then
638 SPARK_Msg_N
639 ("nested dependency relations not allowed", Inputs);
641 elsif Present (Expressions (Inputs)) then
642 Input := First (Expressions (Inputs));
643 while Present (Input) loop
644 Analyze_Input_Output
645 (Item => Input,
646 Is_Input => True,
647 Self_Ref => False,
648 Top_Level => False,
649 Seen => Inputs_Seen,
650 Null_Seen => Null_Input_Seen,
651 Non_Null_Seen => Non_Null_Input_Seen);
653 Next (Input);
654 end loop;
656 -- Syntax error, always report
658 else
659 Error_Msg_N ("malformed input dependency list", Inputs);
660 end if;
662 -- Process a solitary input
664 else
665 Analyze_Input_Output
666 (Item => Inputs,
667 Is_Input => True,
668 Self_Ref => False,
669 Top_Level => False,
670 Seen => Inputs_Seen,
671 Null_Seen => Null_Input_Seen,
672 Non_Null_Seen => Non_Null_Input_Seen);
673 end if;
675 -- Detect an illegal dependency clause of the form
677 -- (null =>[+] null)
679 if Null_Output_Seen and then Null_Input_Seen then
680 SPARK_Msg_N
681 ("null dependency clause cannot have a null input list",
682 Inputs);
683 end if;
684 end Analyze_Input_List;
686 --------------------------
687 -- Analyze_Input_Output --
688 --------------------------
690 procedure Analyze_Input_Output
691 (Item : Node_Id;
692 Is_Input : Boolean;
693 Self_Ref : Boolean;
694 Top_Level : Boolean;
695 Seen : in out Elist_Id;
696 Null_Seen : in out Boolean;
697 Non_Null_Seen : in out Boolean)
699 Is_Output : constant Boolean := not Is_Input;
700 Grouped : Node_Id;
701 Item_Id : Entity_Id;
703 begin
704 -- Multiple input or output items appear as an aggregate
706 if Nkind (Item) = N_Aggregate then
707 if not Top_Level then
708 SPARK_Msg_N ("nested grouping of items not allowed", Item);
710 elsif Present (Component_Associations (Item)) then
711 SPARK_Msg_N
712 ("nested dependency relations not allowed", Item);
714 -- Recursively analyze the grouped items
716 elsif Present (Expressions (Item)) then
717 Grouped := First (Expressions (Item));
718 while Present (Grouped) loop
719 Analyze_Input_Output
720 (Item => Grouped,
721 Is_Input => Is_Input,
722 Self_Ref => Self_Ref,
723 Top_Level => False,
724 Seen => Seen,
725 Null_Seen => Null_Seen,
726 Non_Null_Seen => Non_Null_Seen);
728 Next (Grouped);
729 end loop;
731 -- Syntax error, always report
733 else
734 Error_Msg_N ("malformed dependency list", Item);
735 end if;
737 -- Process Function'Result in the context of a dependency clause
739 elsif Is_Attribute_Result (Item) then
740 Non_Null_Seen := True;
742 -- It is sufficent to analyze the prefix of 'Result in order to
743 -- establish legality of the attribute.
745 Analyze (Prefix (Item));
747 -- The prefix of 'Result must denote the function for which
748 -- pragma Depends applies (SPARK RM 6.1.5(11)).
750 if not Is_Entity_Name (Prefix (Item))
751 or else Ekind (Spec_Id) /= E_Function
752 or else Entity (Prefix (Item)) /= Spec_Id
753 then
754 Error_Msg_Name_1 := Name_Result;
755 SPARK_Msg_N
756 ("prefix of attribute % must denote the enclosing "
757 & "function", Item);
759 -- Function'Result is allowed to appear on the output side of a
760 -- dependency clause (SPARK RM 6.1.5(6)).
762 elsif Is_Input then
763 SPARK_Msg_N ("function result cannot act as input", Item);
765 elsif Null_Seen then
766 SPARK_Msg_N
767 ("cannot mix null and non-null dependency items", Item);
769 else
770 Result_Seen := True;
771 end if;
773 -- Detect multiple uses of null in a single dependency list or
774 -- throughout the whole relation. Verify the placement of a null
775 -- output list relative to the other clauses (SPARK RM 6.1.5(12)).
777 elsif Nkind (Item) = N_Null then
778 if Null_Seen then
779 SPARK_Msg_N
780 ("multiple null dependency relations not allowed", Item);
782 elsif Non_Null_Seen then
783 SPARK_Msg_N
784 ("cannot mix null and non-null dependency items", Item);
786 else
787 Null_Seen := True;
789 if Is_Output then
790 if not Is_Last then
791 SPARK_Msg_N
792 ("null output list must be the last clause in a "
793 & "dependency relation", Item);
795 -- Catch a useless dependence of the form:
796 -- null =>+ ...
798 elsif Self_Ref then
799 SPARK_Msg_N
800 ("useless dependence, null depends on itself", Item);
801 end if;
802 end if;
803 end if;
805 -- Default case
807 else
808 Non_Null_Seen := True;
810 if Null_Seen then
811 SPARK_Msg_N ("cannot mix null and non-null items", Item);
812 end if;
814 Analyze (Item);
815 Resolve_State (Item);
817 -- Find the entity of the item. If this is a renaming, climb
818 -- the renaming chain to reach the root object. Renamings of
819 -- non-entire objects do not yield an entity (Empty).
821 Item_Id := Entity_Of (Item);
823 if Present (Item_Id) then
824 if Ekind_In (Item_Id, E_Abstract_State,
825 E_In_Parameter,
826 E_In_Out_Parameter,
827 E_Out_Parameter,
828 E_Variable)
829 then
830 -- Ensure that the item fulfils its role as input and/or
831 -- output as specified by pragma Global or the enclosing
832 -- context.
834 Check_Role (Item, Item_Id, Is_Input, Self_Ref);
836 -- Detect multiple uses of the same state, variable or
837 -- formal parameter. If this is not the case, add the
838 -- item to the list of processed relations.
840 if Contains (Seen, Item_Id) then
841 SPARK_Msg_NE
842 ("duplicate use of item &", Item, Item_Id);
843 else
844 Add_Item (Item_Id, Seen);
845 end if;
847 -- Detect illegal use of an input related to a null
848 -- output. Such input items cannot appear in other
849 -- input lists (SPARK RM 6.1.5(13)).
851 if Is_Input
852 and then Null_Output_Seen
853 and then Contains (All_Inputs_Seen, Item_Id)
854 then
855 SPARK_Msg_N
856 ("input of a null output list cannot appear in "
857 & "multiple input lists", Item);
858 end if;
860 -- Add an input or a self-referential output to the list
861 -- of all processed inputs.
863 if Is_Input or else Self_Ref then
864 Add_Item (Item_Id, All_Inputs_Seen);
865 end if;
867 -- State related checks (SPARK RM 6.1.5(3))
869 if Ekind (Item_Id) = E_Abstract_State then
870 if Has_Visible_Refinement (Item_Id) then
871 SPARK_Msg_NE
872 ("cannot mention state & in global refinement",
873 Item, Item_Id);
874 SPARK_Msg_N
875 ("\use its constituents instead", Item);
876 return;
878 -- If the reference to the abstract state appears in
879 -- an enclosing package body that will eventually
880 -- refine the state, record the reference for future
881 -- checks.
883 else
884 Record_Possible_Body_Reference
885 (State_Id => Item_Id,
886 Ref => Item);
887 end if;
888 end if;
890 -- When the item renames an entire object, replace the
891 -- item with a reference to the object.
893 if Present (Renamed_Object (Entity (Item))) then
894 Rewrite (Item,
895 New_Occurrence_Of (Item_Id, Sloc (Item)));
896 Analyze (Item);
897 end if;
899 -- Add the entity of the current item to the list of
900 -- processed items.
902 if Ekind (Item_Id) = E_Abstract_State then
903 Add_Item (Item_Id, States_Seen);
904 end if;
906 if Ekind_In (Item_Id, E_Abstract_State, E_Variable)
907 and then Present (Encapsulating_State (Item_Id))
908 then
909 Add_Item (Item_Id, Constits_Seen);
910 end if;
912 -- All other input/output items are illegal
913 -- (SPARK RM 6.1.5(1)).
915 else
916 SPARK_Msg_N
917 ("item must denote parameter, variable, or state",
918 Item);
919 end if;
921 -- All other input/output items are illegal
922 -- (SPARK RM 6.1.5(1)). This is a syntax error, always report.
924 else
925 Error_Msg_N
926 ("item must denote parameter, variable, or state", Item);
927 end if;
928 end if;
929 end Analyze_Input_Output;
931 -- Local variables
933 Inputs : Node_Id;
934 Output : Node_Id;
935 Self_Ref : Boolean;
937 Non_Null_Output_Seen : Boolean := False;
938 -- Flag used to check the legality of an output list
940 -- Start of processing for Analyze_Dependency_Clause
942 begin
943 Inputs := Expression (Clause);
944 Self_Ref := False;
946 -- An input list with a self-dependency appears as operator "+" where
947 -- the actuals inputs are the right operand.
949 if Nkind (Inputs) = N_Op_Plus then
950 Inputs := Right_Opnd (Inputs);
951 Self_Ref := True;
952 end if;
954 -- Process the output_list of a dependency_clause
956 Output := First (Choices (Clause));
957 while Present (Output) loop
958 Analyze_Input_Output
959 (Item => Output,
960 Is_Input => False,
961 Self_Ref => Self_Ref,
962 Top_Level => True,
963 Seen => All_Outputs_Seen,
964 Null_Seen => Null_Output_Seen,
965 Non_Null_Seen => Non_Null_Output_Seen);
967 Next (Output);
968 end loop;
970 -- Process the input_list of a dependency_clause
972 Analyze_Input_List (Inputs);
973 end Analyze_Dependency_Clause;
975 ---------------------------
976 -- Check_Function_Return --
977 ---------------------------
979 procedure Check_Function_Return is
980 begin
981 if Ekind (Spec_Id) = E_Function and then not Result_Seen then
982 SPARK_Msg_NE
983 ("result of & must appear in exactly one output list",
984 N, Spec_Id);
985 end if;
986 end Check_Function_Return;
988 ----------------
989 -- Check_Role --
990 ----------------
992 procedure Check_Role
993 (Item : Node_Id;
994 Item_Id : Entity_Id;
995 Is_Input : Boolean;
996 Self_Ref : Boolean)
998 procedure Find_Role
999 (Item_Is_Input : out Boolean;
1000 Item_Is_Output : out Boolean);
1001 -- Find the input/output role of Item_Id. Flags Item_Is_Input and
1002 -- Item_Is_Output are set depending on the role.
1004 procedure Role_Error
1005 (Item_Is_Input : Boolean;
1006 Item_Is_Output : Boolean);
1007 -- Emit an error message concerning the incorrect use of Item in
1008 -- pragma [Refined_]Depends. Flags Item_Is_Input and Item_Is_Output
1009 -- denote whether the item is an input and/or an output.
1011 ---------------
1012 -- Find_Role --
1013 ---------------
1015 procedure Find_Role
1016 (Item_Is_Input : out Boolean;
1017 Item_Is_Output : out Boolean)
1019 begin
1020 Item_Is_Input := False;
1021 Item_Is_Output := False;
1023 -- Abstract state cases
1025 if Ekind (Item_Id) = E_Abstract_State then
1027 -- When pragma Global is present, the mode of the state may be
1028 -- further constrained by setting a more restrictive mode.
1030 if Global_Seen then
1031 if Appears_In (Subp_Inputs, Item_Id) then
1032 Item_Is_Input := True;
1033 end if;
1035 if Appears_In (Subp_Outputs, Item_Id) then
1036 Item_Is_Output := True;
1037 end if;
1039 -- Otherwise the state has a default IN OUT mode
1041 else
1042 Item_Is_Input := True;
1043 Item_Is_Output := True;
1044 end if;
1046 -- Parameter cases
1048 elsif Ekind (Item_Id) = E_In_Parameter then
1049 Item_Is_Input := True;
1051 elsif Ekind (Item_Id) = E_In_Out_Parameter then
1052 Item_Is_Input := True;
1053 Item_Is_Output := True;
1055 elsif Ekind (Item_Id) = E_Out_Parameter then
1056 if Scope (Item_Id) = Spec_Id then
1058 -- An OUT parameter of the related subprogram has mode IN
1059 -- if its type is unconstrained or tagged because array
1060 -- bounds, discriminants or tags can be read.
1062 if Is_Unconstrained_Or_Tagged_Item (Item_Id) then
1063 Item_Is_Input := True;
1064 end if;
1066 Item_Is_Output := True;
1068 -- An OUT parameter of an enclosing subprogram behaves as a
1069 -- read-write variable in which case the mode is IN OUT.
1071 else
1072 Item_Is_Input := True;
1073 Item_Is_Output := True;
1074 end if;
1076 -- Variable cases
1078 else pragma Assert (Ekind (Item_Id) = E_Variable);
1080 -- When pragma Global is present, the mode of the variable may
1081 -- be further constrained by setting a more restrictive mode.
1083 if Global_Seen then
1085 -- A variable has mode IN when its type is unconstrained or
1086 -- tagged because array bounds, discriminants or tags can be
1087 -- read.
1089 if Appears_In (Subp_Inputs, Item_Id)
1090 or else Is_Unconstrained_Or_Tagged_Item (Item_Id)
1091 then
1092 Item_Is_Input := True;
1093 end if;
1095 if Appears_In (Subp_Outputs, Item_Id) then
1096 Item_Is_Output := True;
1097 end if;
1099 -- Otherwise the variable has a default IN OUT mode
1101 else
1102 Item_Is_Input := True;
1103 Item_Is_Output := True;
1104 end if;
1105 end if;
1106 end Find_Role;
1108 ----------------
1109 -- Role_Error --
1110 ----------------
1112 procedure Role_Error
1113 (Item_Is_Input : Boolean;
1114 Item_Is_Output : Boolean)
1116 Error_Msg : Name_Id;
1118 begin
1119 Name_Len := 0;
1121 -- When the item is not part of the input and the output set of
1122 -- the related subprogram, then it appears as extra in pragma
1123 -- [Refined_]Depends.
1125 if not Item_Is_Input and then not Item_Is_Output then
1126 Add_Item_To_Name_Buffer (Item_Id);
1127 Add_Str_To_Name_Buffer
1128 (" & cannot appear in dependence relation");
1130 Error_Msg := Name_Find;
1131 SPARK_Msg_NE (Get_Name_String (Error_Msg), Item, Item_Id);
1133 Error_Msg_Name_1 := Chars (Subp_Id);
1134 SPARK_Msg_NE
1135 ("\& is not part of the input or output set of subprogram %",
1136 Item, Item_Id);
1138 -- The mode of the item and its role in pragma [Refined_]Depends
1139 -- are in conflict. Construct a detailed message explaining the
1140 -- illegality (SPARK RM 6.1.5(5-6)).
1142 else
1143 if Item_Is_Input then
1144 Add_Str_To_Name_Buffer ("read-only");
1145 else
1146 Add_Str_To_Name_Buffer ("write-only");
1147 end if;
1149 Add_Char_To_Name_Buffer (' ');
1150 Add_Item_To_Name_Buffer (Item_Id);
1151 Add_Str_To_Name_Buffer (" & cannot appear as ");
1153 if Item_Is_Input then
1154 Add_Str_To_Name_Buffer ("output");
1155 else
1156 Add_Str_To_Name_Buffer ("input");
1157 end if;
1159 Add_Str_To_Name_Buffer (" in dependence relation");
1160 Error_Msg := Name_Find;
1161 SPARK_Msg_NE (Get_Name_String (Error_Msg), Item, Item_Id);
1162 end if;
1163 end Role_Error;
1165 -- Local variables
1167 Item_Is_Input : Boolean;
1168 Item_Is_Output : Boolean;
1170 -- Start of processing for Check_Role
1172 begin
1173 Find_Role (Item_Is_Input, Item_Is_Output);
1175 -- Input item
1177 if Is_Input then
1178 if not Item_Is_Input then
1179 Role_Error (Item_Is_Input, Item_Is_Output);
1180 end if;
1182 -- Self-referential item
1184 elsif Self_Ref then
1185 if not Item_Is_Input or else not Item_Is_Output then
1186 Role_Error (Item_Is_Input, Item_Is_Output);
1187 end if;
1189 -- Output item
1191 elsif not Item_Is_Output then
1192 Role_Error (Item_Is_Input, Item_Is_Output);
1193 end if;
1194 end Check_Role;
1196 -----------------
1197 -- Check_Usage --
1198 -----------------
1200 procedure Check_Usage
1201 (Subp_Items : Elist_Id;
1202 Used_Items : Elist_Id;
1203 Is_Input : Boolean)
1205 procedure Usage_Error (Item : Node_Id; Item_Id : Entity_Id);
1206 -- Emit an error concerning the illegal usage of an item
1208 -----------------
1209 -- Usage_Error --
1210 -----------------
1212 procedure Usage_Error (Item : Node_Id; Item_Id : Entity_Id) is
1213 Error_Msg : Name_Id;
1215 begin
1216 -- Input case
1218 if Is_Input then
1220 -- Unconstrained and tagged items are not part of the explicit
1221 -- input set of the related subprogram, they do not have to be
1222 -- present in a dependence relation and should not be flagged
1223 -- (SPARK RM 6.1.5(8)).
1225 if not Is_Unconstrained_Or_Tagged_Item (Item_Id) then
1226 Name_Len := 0;
1228 Add_Item_To_Name_Buffer (Item_Id);
1229 Add_Str_To_Name_Buffer
1230 (" & must appear in at least one input dependence list");
1232 Error_Msg := Name_Find;
1233 SPARK_Msg_NE (Get_Name_String (Error_Msg), Item, Item_Id);
1234 end if;
1236 -- Output case (SPARK RM 6.1.5(10))
1238 else
1239 Name_Len := 0;
1241 Add_Item_To_Name_Buffer (Item_Id);
1242 Add_Str_To_Name_Buffer
1243 (" & must appear in exactly one output dependence list");
1245 Error_Msg := Name_Find;
1246 SPARK_Msg_NE (Get_Name_String (Error_Msg), Item, Item_Id);
1247 end if;
1248 end Usage_Error;
1250 -- Local variables
1252 Elmt : Elmt_Id;
1253 Item : Node_Id;
1254 Item_Id : Entity_Id;
1256 -- Start of processing for Check_Usage
1258 begin
1259 if No (Subp_Items) then
1260 return;
1261 end if;
1263 -- Each input or output of the subprogram must appear in a dependency
1264 -- relation.
1266 Elmt := First_Elmt (Subp_Items);
1267 while Present (Elmt) loop
1268 Item := Node (Elmt);
1270 if Nkind (Item) = N_Defining_Identifier then
1271 Item_Id := Item;
1272 else
1273 Item_Id := Entity_Of (Item);
1274 end if;
1276 -- The item does not appear in a dependency
1278 if Present (Item_Id)
1279 and then not Contains (Used_Items, Item_Id)
1280 then
1281 if Is_Formal (Item_Id) then
1282 Usage_Error (Item, Item_Id);
1284 -- States and global variables are not used properly only when
1285 -- the subprogram is subject to pragma Global.
1287 elsif Global_Seen then
1288 Usage_Error (Item, Item_Id);
1289 end if;
1290 end if;
1292 Next_Elmt (Elmt);
1293 end loop;
1294 end Check_Usage;
1296 ----------------------
1297 -- Normalize_Clause --
1298 ----------------------
1300 procedure Normalize_Clause (Clause : Node_Id) is
1301 procedure Create_Or_Modify_Clause
1302 (Output : Node_Id;
1303 Outputs : Node_Id;
1304 Inputs : Node_Id;
1305 After : Node_Id;
1306 In_Place : Boolean;
1307 Multiple : Boolean);
1308 -- Create a brand new clause to represent the self-reference or
1309 -- modify the input and/or output lists of an existing clause. Output
1310 -- denotes a self-referencial output. Outputs is the output list of a
1311 -- clause. Inputs is the input list of a clause. After denotes the
1312 -- clause after which the new clause is to be inserted. Flag In_Place
1313 -- should be set when normalizing the last output of an output list.
1314 -- Flag Multiple should be set when Output comes from a list with
1315 -- multiple items.
1317 -----------------------------
1318 -- Create_Or_Modify_Clause --
1319 -----------------------------
1321 procedure Create_Or_Modify_Clause
1322 (Output : Node_Id;
1323 Outputs : Node_Id;
1324 Inputs : Node_Id;
1325 After : Node_Id;
1326 In_Place : Boolean;
1327 Multiple : Boolean)
1329 procedure Propagate_Output
1330 (Output : Node_Id;
1331 Inputs : Node_Id);
1332 -- Handle the various cases of output propagation to the input
1333 -- list. Output denotes a self-referencial output item. Inputs is
1334 -- the input list of a clause.
1336 ----------------------
1337 -- Propagate_Output --
1338 ----------------------
1340 procedure Propagate_Output
1341 (Output : Node_Id;
1342 Inputs : Node_Id)
1344 function In_Input_List
1345 (Item : Entity_Id;
1346 Inputs : List_Id) return Boolean;
1347 -- Determine whether a particulat item appears in the input
1348 -- list of a clause.
1350 -------------------
1351 -- In_Input_List --
1352 -------------------
1354 function In_Input_List
1355 (Item : Entity_Id;
1356 Inputs : List_Id) return Boolean
1358 Elmt : Node_Id;
1360 begin
1361 Elmt := First (Inputs);
1362 while Present (Elmt) loop
1363 if Entity_Of (Elmt) = Item then
1364 return True;
1365 end if;
1367 Next (Elmt);
1368 end loop;
1370 return False;
1371 end In_Input_List;
1373 -- Local variables
1375 Output_Id : constant Entity_Id := Entity_Of (Output);
1376 Grouped : List_Id;
1378 -- Start of processing for Propagate_Output
1380 begin
1381 -- The clause is of the form:
1383 -- (Output =>+ null)
1385 -- Remove null input and replace it with a copy of the output:
1387 -- (Output => Output)
1389 if Nkind (Inputs) = N_Null then
1390 Rewrite (Inputs, New_Copy_Tree (Output));
1392 -- The clause is of the form:
1394 -- (Output =>+ (Input1, ..., InputN))
1396 -- Determine whether the output is not already mentioned in the
1397 -- input list and if not, add it to the list of inputs:
1399 -- (Output => (Output, Input1, ..., InputN))
1401 elsif Nkind (Inputs) = N_Aggregate then
1402 Grouped := Expressions (Inputs);
1404 if not In_Input_List
1405 (Item => Output_Id,
1406 Inputs => Grouped)
1407 then
1408 Prepend_To (Grouped, New_Copy_Tree (Output));
1409 end if;
1411 -- The clause is of the form:
1413 -- (Output =>+ Input)
1415 -- If the input does not mention the output, group the two
1416 -- together:
1418 -- (Output => (Output, Input))
1420 elsif Entity_Of (Inputs) /= Output_Id then
1421 Rewrite (Inputs,
1422 Make_Aggregate (Loc,
1423 Expressions => New_List (
1424 New_Copy_Tree (Output),
1425 New_Copy_Tree (Inputs))));
1426 end if;
1427 end Propagate_Output;
1429 -- Local variables
1431 Loc : constant Source_Ptr := Sloc (Clause);
1432 New_Clause : Node_Id;
1434 -- Start of processing for Create_Or_Modify_Clause
1436 begin
1437 -- A null output depending on itself does not require any
1438 -- normalization.
1440 if Nkind (Output) = N_Null then
1441 return;
1443 -- A function result cannot depend on itself because it cannot
1444 -- appear in the input list of a relation (SPARK RM 6.1.5(10)).
1446 elsif Is_Attribute_Result (Output) then
1447 SPARK_Msg_N ("function result cannot depend on itself", Output);
1448 return;
1449 end if;
1451 -- When performing the transformation in place, simply add the
1452 -- output to the list of inputs (if not already there). This case
1453 -- arises when dealing with the last output of an output list -
1454 -- we perform the normalization in place to avoid generating a
1455 -- malformed tree.
1457 if In_Place then
1458 Propagate_Output (Output, Inputs);
1460 -- A list with multiple outputs is slowly trimmed until only
1461 -- one element remains. When this happens, replace aggregate
1462 -- with the element itself.
1464 if Multiple then
1465 Remove (Output);
1466 Rewrite (Outputs, Output);
1467 end if;
1469 -- Default case
1471 else
1472 -- Unchain the output from its output list as it will appear in
1473 -- a new clause. Note that we cannot simply rewrite the output
1474 -- as null because this will violate the semantics of pragma
1475 -- Depends.
1477 Remove (Output);
1479 -- Generate a new clause of the form:
1480 -- (Output => Inputs)
1482 New_Clause :=
1483 Make_Component_Association (Loc,
1484 Choices => New_List (Output),
1485 Expression => New_Copy_Tree (Inputs));
1487 -- The new clause contains replicated content that has already
1488 -- been analyzed. There is not need to reanalyze it or
1489 -- renormalize it again.
1491 Set_Analyzed (New_Clause);
1493 Propagate_Output
1494 (Output => First (Choices (New_Clause)),
1495 Inputs => Expression (New_Clause));
1497 Insert_After (After, New_Clause);
1498 end if;
1499 end Create_Or_Modify_Clause;
1501 -- Local variables
1503 Outputs : constant Node_Id := First (Choices (Clause));
1504 Inputs : Node_Id;
1505 Last_Output : Node_Id;
1506 Next_Output : Node_Id;
1507 Output : Node_Id;
1509 -- Start of processing for Normalize_Clause
1511 begin
1512 -- A self-dependency appears as operator "+". Remove the "+" from the
1513 -- tree by moving the real inputs to their proper place.
1515 if Nkind (Expression (Clause)) = N_Op_Plus then
1516 Rewrite (Expression (Clause), Right_Opnd (Expression (Clause)));
1517 Inputs := Expression (Clause);
1519 -- Multiple outputs appear as an aggregate
1521 if Nkind (Outputs) = N_Aggregate then
1522 Last_Output := Last (Expressions (Outputs));
1524 Output := First (Expressions (Outputs));
1525 while Present (Output) loop
1527 -- Normalization may remove an output from its list,
1528 -- preserve the subsequent output now.
1530 Next_Output := Next (Output);
1532 Create_Or_Modify_Clause
1533 (Output => Output,
1534 Outputs => Outputs,
1535 Inputs => Inputs,
1536 After => Clause,
1537 In_Place => Output = Last_Output,
1538 Multiple => True);
1540 Output := Next_Output;
1541 end loop;
1543 -- Solitary output
1545 else
1546 Create_Or_Modify_Clause
1547 (Output => Outputs,
1548 Outputs => Empty,
1549 Inputs => Inputs,
1550 After => Empty,
1551 In_Place => True,
1552 Multiple => False);
1553 end if;
1554 end if;
1555 end Normalize_Clause;
1557 -- Local variables
1559 Deps : constant Node_Id :=
1560 Get_Pragma_Arg
1561 (First (Pragma_Argument_Associations (N)));
1562 Clause : Node_Id;
1563 Errors : Nat;
1564 Last_Clause : Node_Id;
1565 Subp_Decl : Node_Id;
1567 Restore_Scope : Boolean := False;
1568 -- Gets set True if we do a Push_Scope needing a Pop_Scope on exit
1570 -- Start of processing for Analyze_Depends_In_Decl_Part
1572 begin
1573 Set_Analyzed (N);
1575 Subp_Decl := Find_Related_Subprogram_Or_Body (N);
1576 Subp_Id := Defining_Entity (Subp_Decl);
1578 -- The logic in this routine is used to analyze both pragma Depends and
1579 -- pragma Refined_Depends since they have the same syntax and base
1580 -- semantics. Find the entity of the corresponding spec when analyzing
1581 -- Refined_Depends.
1583 if Nkind (Subp_Decl) = N_Subprogram_Body
1584 and then Present (Corresponding_Spec (Subp_Decl))
1585 then
1586 Spec_Id := Corresponding_Spec (Subp_Decl);
1588 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
1589 and then Present (Corresponding_Spec_Of_Stub (Subp_Decl))
1590 then
1591 Spec_Id := Corresponding_Spec_Of_Stub (Subp_Decl);
1593 else
1594 Spec_Id := Subp_Id;
1595 end if;
1597 -- Empty dependency list
1599 if Nkind (Deps) = N_Null then
1601 -- Gather all states, variables and formal parameters that the
1602 -- subprogram may depend on. These items are obtained from the
1603 -- parameter profile or pragma [Refined_]Global (if available).
1605 Collect_Subprogram_Inputs_Outputs
1606 (Subp_Id => Subp_Id,
1607 Subp_Inputs => Subp_Inputs,
1608 Subp_Outputs => Subp_Outputs,
1609 Global_Seen => Global_Seen);
1611 -- Verify that every input or output of the subprogram appear in a
1612 -- dependency.
1614 Check_Usage (Subp_Inputs, All_Inputs_Seen, True);
1615 Check_Usage (Subp_Outputs, All_Outputs_Seen, False);
1616 Check_Function_Return;
1618 -- Dependency clauses appear as component associations of an aggregate
1620 elsif Nkind (Deps) = N_Aggregate then
1622 -- Do not attempt to perform analysis of a syntactically illegal
1623 -- clause as this will lead to misleading errors.
1625 if Has_Extra_Parentheses (Deps) then
1626 return;
1627 end if;
1629 if Present (Component_Associations (Deps)) then
1630 Last_Clause := Last (Component_Associations (Deps));
1632 -- Gather all states, variables and formal parameters that the
1633 -- subprogram may depend on. These items are obtained from the
1634 -- parameter profile or pragma [Refined_]Global (if available).
1636 Collect_Subprogram_Inputs_Outputs
1637 (Subp_Id => Subp_Id,
1638 Subp_Inputs => Subp_Inputs,
1639 Subp_Outputs => Subp_Outputs,
1640 Global_Seen => Global_Seen);
1642 -- Ensure that the formal parameters are visible when analyzing
1643 -- all clauses. This falls out of the general rule of aspects
1644 -- pertaining to subprogram declarations. Skip the installation
1645 -- for subprogram bodies because the formals are already visible.
1647 if not In_Open_Scopes (Spec_Id) then
1648 Restore_Scope := True;
1649 Push_Scope (Spec_Id);
1650 Install_Formals (Spec_Id);
1651 end if;
1653 Clause := First (Component_Associations (Deps));
1654 while Present (Clause) loop
1655 Errors := Serious_Errors_Detected;
1657 -- Normalization may create extra clauses that contain
1658 -- replicated input and output names. There is no need to
1659 -- reanalyze them.
1661 if not Analyzed (Clause) then
1662 Set_Analyzed (Clause);
1664 Analyze_Dependency_Clause
1665 (Clause => Clause,
1666 Is_Last => Clause = Last_Clause);
1667 end if;
1669 -- Do not normalize a clause if errors were detected (count
1670 -- of Serious_Errors has increased) because the inputs and/or
1671 -- outputs may denote illegal items. Normalization is disabled
1672 -- in ASIS mode as it alters the tree by introducing new nodes
1673 -- similar to expansion.
1675 if Serious_Errors_Detected = Errors and then not ASIS_Mode then
1676 Normalize_Clause (Clause);
1677 end if;
1679 Next (Clause);
1680 end loop;
1682 if Restore_Scope then
1683 End_Scope;
1684 end if;
1686 -- Verify that every input or output of the subprogram appear in a
1687 -- dependency.
1689 Check_Usage (Subp_Inputs, All_Inputs_Seen, True);
1690 Check_Usage (Subp_Outputs, All_Outputs_Seen, False);
1691 Check_Function_Return;
1693 -- The dependency list is malformed. This is a syntax error, always
1694 -- report.
1696 else
1697 Error_Msg_N ("malformed dependency relation", Deps);
1698 return;
1699 end if;
1701 -- The top level dependency relation is malformed. This is a syntax
1702 -- error, always report.
1704 else
1705 Error_Msg_N ("malformed dependency relation", Deps);
1706 return;
1707 end if;
1709 -- Ensure that a state and a corresponding constituent do not appear
1710 -- together in pragma [Refined_]Depends.
1712 Check_State_And_Constituent_Use
1713 (States => States_Seen,
1714 Constits => Constits_Seen,
1715 Context => N);
1716 end Analyze_Depends_In_Decl_Part;
1718 --------------------------------------------
1719 -- Analyze_External_Property_In_Decl_Part --
1720 --------------------------------------------
1722 procedure Analyze_External_Property_In_Decl_Part
1723 (N : Node_Id;
1724 Expr_Val : out Boolean)
1726 Arg1 : constant Node_Id := First (Pragma_Argument_Associations (N));
1727 Obj_Id : constant Entity_Id := Entity (Get_Pragma_Arg (Arg1));
1728 Expr : constant Node_Id := Get_Pragma_Arg (Next (Arg1));
1730 begin
1731 Error_Msg_Name_1 := Pragma_Name (N);
1733 -- An external property pragma must apply to an effectively volatile
1734 -- object other than a formal subprogram parameter (SPARK RM 7.1.3(2)).
1735 -- The check is performed at the end of the declarative region due to a
1736 -- possible out-of-order arrangement of pragmas:
1738 -- Obj : ...;
1739 -- pragma Async_Readers (Obj);
1740 -- pragma Volatile (Obj);
1742 if not Is_Effectively_Volatile (Obj_Id) then
1743 SPARK_Msg_N
1744 ("external property % must apply to a volatile object", N);
1745 end if;
1747 -- Ensure that the Boolean expression (if present) is static. A missing
1748 -- argument defaults the value to True (SPARK RM 7.1.2(5)).
1750 Expr_Val := True;
1752 if Present (Expr) then
1753 Analyze_And_Resolve (Expr, Standard_Boolean);
1755 if Is_OK_Static_Expression (Expr) then
1756 Expr_Val := Is_True (Expr_Value (Expr));
1757 else
1758 SPARK_Msg_N ("expression of % must be static", Expr);
1759 end if;
1760 end if;
1761 end Analyze_External_Property_In_Decl_Part;
1763 ---------------------------------
1764 -- Analyze_Global_In_Decl_Part --
1765 ---------------------------------
1767 procedure Analyze_Global_In_Decl_Part (N : Node_Id) is
1768 Constits_Seen : Elist_Id := No_Elist;
1769 -- A list containing the entities of all constituents processed so far.
1770 -- It aids in detecting illegal usage of a state and a corresponding
1771 -- constituent in pragma [Refinde_]Global.
1773 Seen : Elist_Id := No_Elist;
1774 -- A list containing the entities of all the items processed so far. It
1775 -- plays a role in detecting distinct entities.
1777 Spec_Id : Entity_Id;
1778 -- The entity of the subprogram subject to pragma [Refined_]Global
1780 States_Seen : Elist_Id := No_Elist;
1781 -- A list containing the entities of all states processed so far. It
1782 -- helps in detecting illegal usage of a state and a corresponding
1783 -- constituent in pragma [Refined_]Global.
1785 Subp_Id : Entity_Id;
1786 -- The entity of the subprogram [body or stub] subject to pragma
1787 -- [Refined_]Global.
1789 In_Out_Seen : Boolean := False;
1790 Input_Seen : Boolean := False;
1791 Output_Seen : Boolean := False;
1792 Proof_Seen : Boolean := False;
1793 -- Flags used to verify the consistency of modes
1795 procedure Analyze_Global_List
1796 (List : Node_Id;
1797 Global_Mode : Name_Id := Name_Input);
1798 -- Verify the legality of a single global list declaration. Global_Mode
1799 -- denotes the current mode in effect.
1801 -------------------------
1802 -- Analyze_Global_List --
1803 -------------------------
1805 procedure Analyze_Global_List
1806 (List : Node_Id;
1807 Global_Mode : Name_Id := Name_Input)
1809 procedure Analyze_Global_Item
1810 (Item : Node_Id;
1811 Global_Mode : Name_Id);
1812 -- Verify the legality of a single global item declaration.
1813 -- Global_Mode denotes the current mode in effect.
1815 procedure Check_Duplicate_Mode
1816 (Mode : Node_Id;
1817 Status : in out Boolean);
1818 -- Flag Status denotes whether a particular mode has been seen while
1819 -- processing a global list. This routine verifies that Mode is not a
1820 -- duplicate mode and sets the flag Status (SPARK RM 6.1.4(9)).
1822 procedure Check_Mode_Restriction_In_Enclosing_Context
1823 (Item : Node_Id;
1824 Item_Id : Entity_Id);
1825 -- Verify that an item of mode In_Out or Output does not appear as an
1826 -- input in the Global aspect of an enclosing subprogram. If this is
1827 -- the case, emit an error. Item and Item_Id are respectively the
1828 -- item and its entity.
1830 procedure Check_Mode_Restriction_In_Function (Mode : Node_Id);
1831 -- Mode denotes either In_Out or Output. Depending on the kind of the
1832 -- related subprogram, emit an error if those two modes apply to a
1833 -- function (SPARK RM 6.1.4(10)).
1835 -------------------------
1836 -- Analyze_Global_Item --
1837 -------------------------
1839 procedure Analyze_Global_Item
1840 (Item : Node_Id;
1841 Global_Mode : Name_Id)
1843 Item_Id : Entity_Id;
1845 begin
1846 -- Detect one of the following cases
1848 -- with Global => (null, Name)
1849 -- with Global => (Name_1, null, Name_2)
1850 -- with Global => (Name, null)
1852 if Nkind (Item) = N_Null then
1853 SPARK_Msg_N ("cannot mix null and non-null global items", Item);
1854 return;
1855 end if;
1857 Analyze (Item);
1858 Resolve_State (Item);
1860 -- Find the entity of the item. If this is a renaming, climb the
1861 -- renaming chain to reach the root object. Renamings of non-
1862 -- entire objects do not yield an entity (Empty).
1864 Item_Id := Entity_Of (Item);
1866 if Present (Item_Id) then
1868 -- A global item may denote a formal parameter of an enclosing
1869 -- subprogram (SPARK RM 6.1.4(6)). Do this check first to
1870 -- provide a better error diagnostic.
1872 if Is_Formal (Item_Id) then
1873 if Scope (Item_Id) = Spec_Id then
1874 SPARK_Msg_NE
1875 ("global item cannot reference parameter of subprogram",
1876 Item, Spec_Id);
1877 return;
1878 end if;
1880 -- A constant cannot act as a global item (SPARK RM 6.1.4(7)).
1881 -- Do this check first to provide a better error diagnostic.
1883 elsif Ekind (Item_Id) = E_Constant then
1884 SPARK_Msg_N ("global item cannot denote a constant", Item);
1886 -- A formal object may act as a global item inside a generic
1888 elsif Is_Formal_Object (Item_Id) then
1889 null;
1891 -- The only legal references are those to abstract states and
1892 -- variables (SPARK RM 6.1.4(4)).
1894 elsif not Ekind_In (Item_Id, E_Abstract_State, E_Variable) then
1895 SPARK_Msg_N
1896 ("global item must denote variable or state", Item);
1897 return;
1898 end if;
1900 -- State related checks
1902 if Ekind (Item_Id) = E_Abstract_State then
1904 -- An abstract state with visible refinement cannot appear
1905 -- in pragma [Refined_]Global as its place must be taken by
1906 -- some of its constituents (SPARK RM 6.1.4(8)).
1908 if Has_Visible_Refinement (Item_Id) then
1909 SPARK_Msg_NE
1910 ("cannot mention state & in global refinement",
1911 Item, Item_Id);
1912 SPARK_Msg_N ("\use its constituents instead", Item);
1913 return;
1915 -- If the reference to the abstract state appears in an
1916 -- enclosing package body that will eventually refine the
1917 -- state, record the reference for future checks.
1919 else
1920 Record_Possible_Body_Reference
1921 (State_Id => Item_Id,
1922 Ref => Item);
1923 end if;
1925 -- Variable related checks. These are only relevant when
1926 -- SPARK_Mode is on as they are not standard Ada legality
1927 -- rules.
1929 elsif SPARK_Mode = On
1930 and then Is_Effectively_Volatile (Item_Id)
1931 then
1932 -- An effectively volatile object cannot appear as a global
1933 -- item of a function (SPARK RM 7.1.3(9)).
1935 if Ekind_In (Spec_Id, E_Function, E_Generic_Function) then
1936 Error_Msg_NE
1937 ("volatile object & cannot act as global item of a "
1938 & "function", Item, Item_Id);
1939 return;
1941 -- An effectively volatile object with external property
1942 -- Effective_Reads set to True must have mode Output or
1943 -- In_Out.
1945 elsif Effective_Reads_Enabled (Item_Id)
1946 and then Global_Mode = Name_Input
1947 then
1948 Error_Msg_NE
1949 ("volatile object & with property Effective_Reads must "
1950 & "have mode In_Out or Output (SPARK RM 7.1.3(11))",
1951 Item, Item_Id);
1952 return;
1953 end if;
1954 end if;
1956 -- When the item renames an entire object, replace the item
1957 -- with a reference to the object.
1959 if Present (Renamed_Object (Entity (Item))) then
1960 Rewrite (Item, New_Occurrence_Of (Item_Id, Sloc (Item)));
1961 Analyze (Item);
1962 end if;
1964 -- Some form of illegal construct masquerading as a name
1965 -- (SPARK RM 6.1.4(4)).
1967 else
1968 Error_Msg_N ("global item must denote variable or state", Item);
1969 return;
1970 end if;
1972 -- Verify that an output does not appear as an input in an
1973 -- enclosing subprogram.
1975 if Nam_In (Global_Mode, Name_In_Out, Name_Output) then
1976 Check_Mode_Restriction_In_Enclosing_Context (Item, Item_Id);
1977 end if;
1979 -- The same entity might be referenced through various way.
1980 -- Check the entity of the item rather than the item itself
1981 -- (SPARK RM 6.1.4(11)).
1983 if Contains (Seen, Item_Id) then
1984 SPARK_Msg_N ("duplicate global item", Item);
1986 -- Add the entity of the current item to the list of processed
1987 -- items.
1989 else
1990 Add_Item (Item_Id, Seen);
1992 if Ekind (Item_Id) = E_Abstract_State then
1993 Add_Item (Item_Id, States_Seen);
1994 end if;
1996 if Ekind_In (Item_Id, E_Abstract_State, E_Variable)
1997 and then Present (Encapsulating_State (Item_Id))
1998 then
1999 Add_Item (Item_Id, Constits_Seen);
2000 end if;
2001 end if;
2002 end Analyze_Global_Item;
2004 --------------------------
2005 -- Check_Duplicate_Mode --
2006 --------------------------
2008 procedure Check_Duplicate_Mode
2009 (Mode : Node_Id;
2010 Status : in out Boolean)
2012 begin
2013 if Status then
2014 SPARK_Msg_N ("duplicate global mode", Mode);
2015 end if;
2017 Status := True;
2018 end Check_Duplicate_Mode;
2020 -------------------------------------------------
2021 -- Check_Mode_Restriction_In_Enclosing_Context --
2022 -------------------------------------------------
2024 procedure Check_Mode_Restriction_In_Enclosing_Context
2025 (Item : Node_Id;
2026 Item_Id : Entity_Id)
2028 Context : Entity_Id;
2029 Dummy : Boolean;
2030 Inputs : Elist_Id := No_Elist;
2031 Outputs : Elist_Id := No_Elist;
2033 begin
2034 -- Traverse the scope stack looking for enclosing subprograms
2035 -- subject to pragma [Refined_]Global.
2037 Context := Scope (Subp_Id);
2038 while Present (Context) and then Context /= Standard_Standard loop
2039 if Is_Subprogram (Context)
2040 and then
2041 (Present (Get_Pragma (Context, Pragma_Global))
2042 or else
2043 Present (Get_Pragma (Context, Pragma_Refined_Global)))
2044 then
2045 Collect_Subprogram_Inputs_Outputs
2046 (Subp_Id => Context,
2047 Subp_Inputs => Inputs,
2048 Subp_Outputs => Outputs,
2049 Global_Seen => Dummy);
2051 -- The item is classified as In_Out or Output but appears as
2052 -- an Input in an enclosing subprogram (SPARK RM 6.1.4(12)).
2054 if Appears_In (Inputs, Item_Id)
2055 and then not Appears_In (Outputs, Item_Id)
2056 then
2057 SPARK_Msg_NE
2058 ("global item & cannot have mode In_Out or Output",
2059 Item, Item_Id);
2060 SPARK_Msg_NE
2061 ("\item already appears as input of subprogram &",
2062 Item, Context);
2064 -- Stop the traversal once an error has been detected
2066 exit;
2067 end if;
2068 end if;
2070 Context := Scope (Context);
2071 end loop;
2072 end Check_Mode_Restriction_In_Enclosing_Context;
2074 ----------------------------------------
2075 -- Check_Mode_Restriction_In_Function --
2076 ----------------------------------------
2078 procedure Check_Mode_Restriction_In_Function (Mode : Node_Id) is
2079 begin
2080 if Ekind (Spec_Id) = E_Function then
2081 SPARK_Msg_N
2082 ("global mode & is not applicable to functions", Mode);
2083 end if;
2084 end Check_Mode_Restriction_In_Function;
2086 -- Local variables
2088 Assoc : Node_Id;
2089 Item : Node_Id;
2090 Mode : Node_Id;
2092 -- Start of processing for Analyze_Global_List
2094 begin
2095 if Nkind (List) = N_Null then
2096 Set_Analyzed (List);
2098 -- Single global item declaration
2100 elsif Nkind_In (List, N_Expanded_Name,
2101 N_Identifier,
2102 N_Selected_Component)
2103 then
2104 Analyze_Global_Item (List, Global_Mode);
2106 -- Simple global list or moded global list declaration
2108 elsif Nkind (List) = N_Aggregate then
2109 Set_Analyzed (List);
2111 -- The declaration of a simple global list appear as a collection
2112 -- of expressions.
2114 if Present (Expressions (List)) then
2115 if Present (Component_Associations (List)) then
2116 SPARK_Msg_N
2117 ("cannot mix moded and non-moded global lists", List);
2118 end if;
2120 Item := First (Expressions (List));
2121 while Present (Item) loop
2122 Analyze_Global_Item (Item, Global_Mode);
2124 Next (Item);
2125 end loop;
2127 -- The declaration of a moded global list appears as a collection
2128 -- of component associations where individual choices denote
2129 -- modes.
2131 elsif Present (Component_Associations (List)) then
2132 if Present (Expressions (List)) then
2133 SPARK_Msg_N
2134 ("cannot mix moded and non-moded global lists", List);
2135 end if;
2137 Assoc := First (Component_Associations (List));
2138 while Present (Assoc) loop
2139 Mode := First (Choices (Assoc));
2141 if Nkind (Mode) = N_Identifier then
2142 if Chars (Mode) = Name_In_Out then
2143 Check_Duplicate_Mode (Mode, In_Out_Seen);
2144 Check_Mode_Restriction_In_Function (Mode);
2146 elsif Chars (Mode) = Name_Input then
2147 Check_Duplicate_Mode (Mode, Input_Seen);
2149 elsif Chars (Mode) = Name_Output then
2150 Check_Duplicate_Mode (Mode, Output_Seen);
2151 Check_Mode_Restriction_In_Function (Mode);
2153 elsif Chars (Mode) = Name_Proof_In then
2154 Check_Duplicate_Mode (Mode, Proof_Seen);
2156 else
2157 SPARK_Msg_N ("invalid mode selector", Mode);
2158 end if;
2160 else
2161 SPARK_Msg_N ("invalid mode selector", Mode);
2162 end if;
2164 -- Items in a moded list appear as a collection of
2165 -- expressions. Reuse the existing machinery to analyze
2166 -- them.
2168 Analyze_Global_List
2169 (List => Expression (Assoc),
2170 Global_Mode => Chars (Mode));
2172 Next (Assoc);
2173 end loop;
2175 -- Invalid tree
2177 else
2178 raise Program_Error;
2179 end if;
2181 -- Any other attempt to declare a global item is illegal. This is a
2182 -- syntax error, always report.
2184 else
2185 Error_Msg_N ("malformed global list", List);
2186 end if;
2187 end Analyze_Global_List;
2189 -- Local variables
2191 Items : constant Node_Id :=
2192 Get_Pragma_Arg (First (Pragma_Argument_Associations (N)));
2193 Subp_Decl : Node_Id;
2195 Restore_Scope : Boolean := False;
2196 -- Set True if we do a Push_Scope requiring a Pop_Scope on exit
2198 -- Start of processing for Analyze_Global_In_Decl_List
2200 begin
2201 Set_Analyzed (N);
2202 Check_SPARK_Aspect_For_ASIS (N);
2204 Subp_Decl := Find_Related_Subprogram_Or_Body (N);
2205 Subp_Id := Defining_Entity (Subp_Decl);
2207 -- The logic in this routine is used to analyze both pragma Global and
2208 -- pragma Refined_Global since they have the same syntax and base
2209 -- semantics. Find the entity of the corresponding spec when analyzing
2210 -- Refined_Global.
2212 if Nkind (Subp_Decl) = N_Subprogram_Body
2213 and then Present (Corresponding_Spec (Subp_Decl))
2214 then
2215 Spec_Id := Corresponding_Spec (Subp_Decl);
2217 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
2218 and then Present (Corresponding_Spec_Of_Stub (Subp_Decl))
2219 then
2220 Spec_Id := Corresponding_Spec_Of_Stub (Subp_Decl);
2222 else
2223 Spec_Id := Subp_Id;
2224 end if;
2226 -- There is nothing to be done for a null global list
2228 if Nkind (Items) = N_Null then
2229 Set_Analyzed (Items);
2231 -- Analyze the various forms of global lists and items. Note that some
2232 -- of these may be malformed in which case the analysis emits error
2233 -- messages.
2235 else
2236 -- Ensure that the formal parameters are visible when processing an
2237 -- item. This falls out of the general rule of aspects pertaining to
2238 -- subprogram declarations.
2240 if not In_Open_Scopes (Spec_Id) then
2241 Restore_Scope := True;
2242 Push_Scope (Spec_Id);
2243 Install_Formals (Spec_Id);
2244 end if;
2246 Analyze_Global_List (Items);
2248 if Restore_Scope then
2249 End_Scope;
2250 end if;
2251 end if;
2253 -- Ensure that a state and a corresponding constituent do not appear
2254 -- together in pragma [Refined_]Global.
2256 Check_State_And_Constituent_Use
2257 (States => States_Seen,
2258 Constits => Constits_Seen,
2259 Context => N);
2260 end Analyze_Global_In_Decl_Part;
2262 --------------------------------------------
2263 -- Analyze_Initial_Condition_In_Decl_Part --
2264 --------------------------------------------
2266 procedure Analyze_Initial_Condition_In_Decl_Part (N : Node_Id) is
2267 Expr : constant Node_Id :=
2268 Get_Pragma_Arg (First (Pragma_Argument_Associations (N)));
2270 begin
2271 Set_Analyzed (N);
2273 -- The expression is preanalyzed because it has not been moved to its
2274 -- final place yet. A direct analysis may generate side effects and this
2275 -- is not desired at this point.
2277 Preanalyze_Assert_Expression (Expr, Standard_Boolean);
2278 end Analyze_Initial_Condition_In_Decl_Part;
2280 --------------------------------------
2281 -- Analyze_Initializes_In_Decl_Part --
2282 --------------------------------------
2284 procedure Analyze_Initializes_In_Decl_Part (N : Node_Id) is
2285 Pack_Spec : constant Node_Id := Parent (N);
2286 Pack_Id : constant Entity_Id := Defining_Entity (Parent (Pack_Spec));
2288 Constits_Seen : Elist_Id := No_Elist;
2289 -- A list containing the entities of all constituents processed so far.
2290 -- It aids in detecting illegal usage of a state and a corresponding
2291 -- constituent in pragma Initializes.
2293 Items_Seen : Elist_Id := No_Elist;
2294 -- A list of all initialization items processed so far. This list is
2295 -- used to detect duplicate items.
2297 Non_Null_Seen : Boolean := False;
2298 Null_Seen : Boolean := False;
2299 -- Flags used to check the legality of a null initialization list
2301 States_And_Vars : Elist_Id := No_Elist;
2302 -- A list of all abstract states and variables declared in the visible
2303 -- declarations of the related package. This list is used to detect the
2304 -- legality of initialization items.
2306 States_Seen : Elist_Id := No_Elist;
2307 -- A list containing the entities of all states processed so far. It
2308 -- helps in detecting illegal usage of a state and a corresponding
2309 -- constituent in pragma Initializes.
2311 procedure Analyze_Initialization_Item (Item : Node_Id);
2312 -- Verify the legality of a single initialization item
2314 procedure Analyze_Initialization_Item_With_Inputs (Item : Node_Id);
2315 -- Verify the legality of a single initialization item followed by a
2316 -- list of input items.
2318 procedure Collect_States_And_Variables;
2319 -- Inspect the visible declarations of the related package and gather
2320 -- the entities of all abstract states and variables in States_And_Vars.
2322 ---------------------------------
2323 -- Analyze_Initialization_Item --
2324 ---------------------------------
2326 procedure Analyze_Initialization_Item (Item : Node_Id) is
2327 Item_Id : Entity_Id;
2329 begin
2330 -- Null initialization list
2332 if Nkind (Item) = N_Null then
2333 if Null_Seen then
2334 SPARK_Msg_N ("multiple null initializations not allowed", Item);
2336 elsif Non_Null_Seen then
2337 SPARK_Msg_N
2338 ("cannot mix null and non-null initialization items", Item);
2339 else
2340 Null_Seen := True;
2341 end if;
2343 -- Initialization item
2345 else
2346 Non_Null_Seen := True;
2348 if Null_Seen then
2349 SPARK_Msg_N
2350 ("cannot mix null and non-null initialization items", Item);
2351 end if;
2353 Analyze (Item);
2354 Resolve_State (Item);
2356 if Is_Entity_Name (Item) then
2357 Item_Id := Entity_Of (Item);
2359 if Ekind_In (Item_Id, E_Abstract_State, E_Variable) then
2361 -- The state or variable must be declared in the visible
2362 -- declarations of the package (SPARK RM 7.1.5(7)).
2364 if not Contains (States_And_Vars, Item_Id) then
2365 Error_Msg_Name_1 := Chars (Pack_Id);
2366 SPARK_Msg_NE
2367 ("initialization item & must appear in the visible "
2368 & "declarations of package %", Item, Item_Id);
2370 -- Detect a duplicate use of the same initialization item
2371 -- (SPARK RM 7.1.5(5)).
2373 elsif Contains (Items_Seen, Item_Id) then
2374 SPARK_Msg_N ("duplicate initialization item", Item);
2376 -- The item is legal, add it to the list of processed states
2377 -- and variables.
2379 else
2380 Add_Item (Item_Id, Items_Seen);
2382 if Ekind (Item_Id) = E_Abstract_State then
2383 Add_Item (Item_Id, States_Seen);
2384 end if;
2386 if Present (Encapsulating_State (Item_Id)) then
2387 Add_Item (Item_Id, Constits_Seen);
2388 end if;
2389 end if;
2391 -- The item references something that is not a state or a
2392 -- variable (SPARK RM 7.1.5(3)).
2394 else
2395 SPARK_Msg_N
2396 ("initialization item must denote variable or state",
2397 Item);
2398 end if;
2400 -- Some form of illegal construct masquerading as a name
2401 -- (SPARK RM 7.1.5(3)). This is a syntax error, always report.
2403 else
2404 Error_Msg_N
2405 ("initialization item must denote variable or state", Item);
2406 end if;
2407 end if;
2408 end Analyze_Initialization_Item;
2410 ---------------------------------------------
2411 -- Analyze_Initialization_Item_With_Inputs --
2412 ---------------------------------------------
2414 procedure Analyze_Initialization_Item_With_Inputs (Item : Node_Id) is
2415 Inputs_Seen : Elist_Id := No_Elist;
2416 -- A list of all inputs processed so far. This list is used to detect
2417 -- duplicate uses of an input.
2419 Non_Null_Seen : Boolean := False;
2420 Null_Seen : Boolean := False;
2421 -- Flags used to check the legality of an input list
2423 procedure Analyze_Input_Item (Input : Node_Id);
2424 -- Verify the legality of a single input item
2426 ------------------------
2427 -- Analyze_Input_Item --
2428 ------------------------
2430 procedure Analyze_Input_Item (Input : Node_Id) is
2431 Input_Id : Entity_Id;
2433 begin
2434 -- Null input list
2436 if Nkind (Input) = N_Null then
2437 if Null_Seen then
2438 SPARK_Msg_N
2439 ("multiple null initializations not allowed", Item);
2441 elsif Non_Null_Seen then
2442 SPARK_Msg_N
2443 ("cannot mix null and non-null initialization item", Item);
2444 else
2445 Null_Seen := True;
2446 end if;
2448 -- Input item
2450 else
2451 Non_Null_Seen := True;
2453 if Null_Seen then
2454 SPARK_Msg_N
2455 ("cannot mix null and non-null initialization item", Item);
2456 end if;
2458 Analyze (Input);
2459 Resolve_State (Input);
2461 if Is_Entity_Name (Input) then
2462 Input_Id := Entity_Of (Input);
2464 if Ekind_In (Input_Id, E_Abstract_State,
2465 E_In_Parameter,
2466 E_In_Out_Parameter,
2467 E_Out_Parameter,
2468 E_Variable)
2469 then
2470 -- The input cannot denote states or variables declared
2471 -- within the related package.
2473 if Within_Scope (Input_Id, Current_Scope) then
2474 Error_Msg_Name_1 := Chars (Pack_Id);
2475 SPARK_Msg_NE
2476 ("input item & cannot denote a visible variable or "
2477 & "state of package % (SPARK RM 7.1.5(4))",
2478 Input, Input_Id);
2480 -- Detect a duplicate use of the same input item
2481 -- (SPARK RM 7.1.5(5)).
2483 elsif Contains (Inputs_Seen, Input_Id) then
2484 SPARK_Msg_N ("duplicate input item", Input);
2486 -- Input is legal, add it to the list of processed inputs
2488 else
2489 Add_Item (Input_Id, Inputs_Seen);
2491 if Ekind (Input_Id) = E_Abstract_State then
2492 Add_Item (Input_Id, States_Seen);
2493 end if;
2495 if Ekind_In (Input_Id, E_Abstract_State, E_Variable)
2496 and then Present (Encapsulating_State (Input_Id))
2497 then
2498 Add_Item (Input_Id, Constits_Seen);
2499 end if;
2500 end if;
2502 -- The input references something that is not a state or a
2503 -- variable (SPARK RM 7.1.5(3)).
2505 else
2506 SPARK_Msg_N
2507 ("input item must denote variable or state", Input);
2508 end if;
2510 -- Some form of illegal construct masquerading as a name
2511 -- (SPARK RM 7.1.5(3)).
2513 else
2514 SPARK_Msg_N
2515 ("input item must denote variable or state", Input);
2516 end if;
2517 end if;
2518 end Analyze_Input_Item;
2520 -- Local variables
2522 Inputs : constant Node_Id := Expression (Item);
2523 Elmt : Node_Id;
2524 Input : Node_Id;
2526 Name_Seen : Boolean := False;
2527 -- A flag used to detect multiple item names
2529 -- Start of processing for Analyze_Initialization_Item_With_Inputs
2531 begin
2532 -- Inspect the name of an item with inputs
2534 Elmt := First (Choices (Item));
2535 while Present (Elmt) loop
2536 if Name_Seen then
2537 SPARK_Msg_N ("only one item allowed in initialization", Elmt);
2538 else
2539 Name_Seen := True;
2540 Analyze_Initialization_Item (Elmt);
2541 end if;
2543 Next (Elmt);
2544 end loop;
2546 -- Multiple input items appear as an aggregate
2548 if Nkind (Inputs) = N_Aggregate then
2549 if Present (Expressions (Inputs)) then
2550 Input := First (Expressions (Inputs));
2551 while Present (Input) loop
2552 Analyze_Input_Item (Input);
2553 Next (Input);
2554 end loop;
2555 end if;
2557 if Present (Component_Associations (Inputs)) then
2558 SPARK_Msg_N
2559 ("inputs must appear in named association form", Inputs);
2560 end if;
2562 -- Single input item
2564 else
2565 Analyze_Input_Item (Inputs);
2566 end if;
2567 end Analyze_Initialization_Item_With_Inputs;
2569 ----------------------------------
2570 -- Collect_States_And_Variables --
2571 ----------------------------------
2573 procedure Collect_States_And_Variables is
2574 Decl : Node_Id;
2576 begin
2577 -- Collect the abstract states defined in the package (if any)
2579 if Present (Abstract_States (Pack_Id)) then
2580 States_And_Vars := New_Copy_Elist (Abstract_States (Pack_Id));
2581 end if;
2583 -- Collect all variables the appear in the visible declarations of
2584 -- the related package.
2586 if Present (Visible_Declarations (Pack_Spec)) then
2587 Decl := First (Visible_Declarations (Pack_Spec));
2588 while Present (Decl) loop
2589 if Nkind (Decl) = N_Object_Declaration
2590 and then Ekind (Defining_Entity (Decl)) = E_Variable
2591 and then Comes_From_Source (Decl)
2592 then
2593 Add_Item (Defining_Entity (Decl), States_And_Vars);
2594 end if;
2596 Next (Decl);
2597 end loop;
2598 end if;
2599 end Collect_States_And_Variables;
2601 -- Local variables
2603 Inits : constant Node_Id :=
2604 Get_Pragma_Arg (First (Pragma_Argument_Associations (N)));
2605 Init : Node_Id;
2607 -- Start of processing for Analyze_Initializes_In_Decl_Part
2609 begin
2610 Set_Analyzed (N);
2612 Check_SPARK_Aspect_For_ASIS (N);
2614 -- Nothing to do when the initialization list is empty
2616 if Nkind (Inits) = N_Null then
2617 return;
2618 end if;
2620 -- Single and multiple initialization clauses appear as an aggregate. If
2621 -- this is not the case, then either the parser or the analysis of the
2622 -- pragma failed to produce an aggregate.
2624 pragma Assert (Nkind (Inits) = N_Aggregate);
2626 -- Initialize the various lists used during analysis
2628 Collect_States_And_Variables;
2630 if Present (Expressions (Inits)) then
2631 Init := First (Expressions (Inits));
2632 while Present (Init) loop
2633 Analyze_Initialization_Item (Init);
2634 Next (Init);
2635 end loop;
2636 end if;
2638 if Present (Component_Associations (Inits)) then
2639 Init := First (Component_Associations (Inits));
2640 while Present (Init) loop
2641 Analyze_Initialization_Item_With_Inputs (Init);
2642 Next (Init);
2643 end loop;
2644 end if;
2646 -- Ensure that a state and a corresponding constituent do not appear
2647 -- together in pragma Initializes.
2649 Check_State_And_Constituent_Use
2650 (States => States_Seen,
2651 Constits => Constits_Seen,
2652 Context => N);
2653 end Analyze_Initializes_In_Decl_Part;
2655 --------------------
2656 -- Analyze_Pragma --
2657 --------------------
2659 procedure Analyze_Pragma (N : Node_Id) is
2660 Loc : constant Source_Ptr := Sloc (N);
2661 Prag_Id : Pragma_Id;
2663 Pname : Name_Id;
2664 -- Name of the source pragma, or name of the corresponding aspect for
2665 -- pragmas which originate in a source aspect. In the latter case, the
2666 -- name may be different from the pragma name.
2668 Pragma_Exit : exception;
2669 -- This exception is used to exit pragma processing completely. It
2670 -- is used when an error is detected, and no further processing is
2671 -- required. It is also used if an earlier error has left the tree in
2672 -- a state where the pragma should not be processed.
2674 Arg_Count : Nat;
2675 -- Number of pragma argument associations
2677 Arg1 : Node_Id;
2678 Arg2 : Node_Id;
2679 Arg3 : Node_Id;
2680 Arg4 : Node_Id;
2681 -- First four pragma arguments (pragma argument association nodes, or
2682 -- Empty if the corresponding argument does not exist).
2684 type Name_List is array (Natural range <>) of Name_Id;
2685 type Args_List is array (Natural range <>) of Node_Id;
2686 -- Types used for arguments to Check_Arg_Order and Gather_Associations
2688 -----------------------
2689 -- Local Subprograms --
2690 -----------------------
2692 procedure Acquire_Warning_Match_String (Arg : Node_Id);
2693 -- Used by pragma Warnings (Off, string), and Warn_As_Error (string) to
2694 -- get the given string argument, and place it in Name_Buffer, adding
2695 -- leading and trailing asterisks if they are not already present. The
2696 -- caller has already checked that Arg is a static string expression.
2698 procedure Ada_2005_Pragma;
2699 -- Called for pragmas defined in Ada 2005, that are not in Ada 95. In
2700 -- Ada 95 mode, these are implementation defined pragmas, so should be
2701 -- caught by the No_Implementation_Pragmas restriction.
2703 procedure Ada_2012_Pragma;
2704 -- Called for pragmas defined in Ada 2012, that are not in Ada 95 or 05.
2705 -- In Ada 95 or 05 mode, these are implementation defined pragmas, so
2706 -- should be caught by the No_Implementation_Pragmas restriction.
2708 procedure Analyze_Part_Of
2709 (Item_Id : Entity_Id;
2710 State : Node_Id;
2711 Indic : Node_Id;
2712 Legal : out Boolean);
2713 -- Subsidiary to the analysis of pragmas Abstract_State and Part_Of.
2714 -- Perform full analysis of indicator Part_Of. Item_Id is the entity of
2715 -- an abstract state, variable or package instantiation. State is the
2716 -- encapsulating state. Indic is the Part_Of indicator. Flag Legal is
2717 -- set when the indicator is legal.
2719 procedure Analyze_Refined_Pragma
2720 (Spec_Id : out Entity_Id;
2721 Body_Id : out Entity_Id;
2722 Legal : out Boolean);
2723 -- Subsidiary routine to the analysis of body pragmas Refined_Depends,
2724 -- Refined_Global and Refined_Post. Check the placement and related
2725 -- context of the pragma. Spec_Id is the entity of the related
2726 -- subprogram. Body_Id is the entity of the subprogram body. Flag
2727 -- Legal is set when the pragma is properly placed.
2729 procedure Check_Ada_83_Warning;
2730 -- Issues a warning message for the current pragma if operating in Ada
2731 -- 83 mode (used for language pragmas that are not a standard part of
2732 -- Ada 83). This procedure does not raise Pragma_Exit. Also notes use
2733 -- of 95 pragma.
2735 procedure Check_Arg_Count (Required : Nat);
2736 -- Check argument count for pragma is equal to given parameter. If not,
2737 -- then issue an error message and raise Pragma_Exit.
2739 -- Note: all routines whose name is Check_Arg_Is_xxx take an argument
2740 -- Arg which can either be a pragma argument association, in which case
2741 -- the check is applied to the expression of the association or an
2742 -- expression directly.
2744 procedure Check_Arg_Is_External_Name (Arg : Node_Id);
2745 -- Check that an argument has the right form for an EXTERNAL_NAME
2746 -- parameter of an extended import/export pragma. The rule is that the
2747 -- name must be an identifier or string literal (in Ada 83 mode) or a
2748 -- static string expression (in Ada 95 mode).
2750 procedure Check_Arg_Is_Identifier (Arg : Node_Id);
2751 -- Check the specified argument Arg to make sure that it is an
2752 -- identifier. If not give error and raise Pragma_Exit.
2754 procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id);
2755 -- Check the specified argument Arg to make sure that it is an integer
2756 -- literal. If not give error and raise Pragma_Exit.
2758 procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id);
2759 -- Check the specified argument Arg to make sure that it has the proper
2760 -- syntactic form for a local name and meets the semantic requirements
2761 -- for a local name. The local name is analyzed as part of the
2762 -- processing for this call. In addition, the local name is required
2763 -- to represent an entity at the library level.
2765 procedure Check_Arg_Is_Local_Name (Arg : Node_Id);
2766 -- Check the specified argument Arg to make sure that it has the proper
2767 -- syntactic form for a local name and meets the semantic requirements
2768 -- for a local name. The local name is analyzed as part of the
2769 -- processing for this call.
2771 procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id);
2772 -- Check the specified argument Arg to make sure that it is a valid
2773 -- locking policy name. If not give error and raise Pragma_Exit.
2775 procedure Check_Arg_Is_Partition_Elaboration_Policy (Arg : Node_Id);
2776 -- Check the specified argument Arg to make sure that it is a valid
2777 -- elaboration policy name. If not give error and raise Pragma_Exit.
2779 procedure Check_Arg_Is_One_Of
2780 (Arg : Node_Id;
2781 N1, N2 : Name_Id);
2782 procedure Check_Arg_Is_One_Of
2783 (Arg : Node_Id;
2784 N1, N2, N3 : Name_Id);
2785 procedure Check_Arg_Is_One_Of
2786 (Arg : Node_Id;
2787 N1, N2, N3, N4 : Name_Id);
2788 procedure Check_Arg_Is_One_Of
2789 (Arg : Node_Id;
2790 N1, N2, N3, N4, N5 : Name_Id);
2791 -- Check the specified argument Arg to make sure that it is an
2792 -- identifier whose name matches either N1 or N2 (or N3, N4, N5 if
2793 -- present). If not then give error and raise Pragma_Exit.
2795 procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id);
2796 -- Check the specified argument Arg to make sure that it is a valid
2797 -- queuing policy name. If not give error and raise Pragma_Exit.
2799 procedure Check_Arg_Is_OK_Static_Expression
2800 (Arg : Node_Id;
2801 Typ : Entity_Id := Empty);
2802 -- Check the specified argument Arg to make sure that it is a static
2803 -- expression of the given type (i.e. it will be analyzed and resolved
2804 -- using this type, which can be any valid argument to Resolve, e.g.
2805 -- Any_Integer is OK). If not, given error and raise Pragma_Exit. If
2806 -- Typ is left Empty, then any static expression is allowed. Includes
2807 -- checking that the argument does not raise Constraint_Error.
2809 procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id);
2810 -- Check the specified argument Arg to make sure that it is a valid task
2811 -- dispatching policy name. If not give error and raise Pragma_Exit.
2813 procedure Check_Arg_Order (Names : Name_List);
2814 -- Checks for an instance of two arguments with identifiers for the
2815 -- current pragma which are not in the sequence indicated by Names,
2816 -- and if so, generates a fatal message about bad order of arguments.
2818 procedure Check_At_Least_N_Arguments (N : Nat);
2819 -- Check there are at least N arguments present
2821 procedure Check_At_Most_N_Arguments (N : Nat);
2822 -- Check there are no more than N arguments present
2824 procedure Check_Component
2825 (Comp : Node_Id;
2826 UU_Typ : Entity_Id;
2827 In_Variant_Part : Boolean := False);
2828 -- Examine an Unchecked_Union component for correct use of per-object
2829 -- constrained subtypes, and for restrictions on finalizable components.
2830 -- UU_Typ is the related Unchecked_Union type. Flag In_Variant_Part
2831 -- should be set when Comp comes from a record variant.
2833 procedure Check_Declaration_Order (First : Node_Id; Second : Node_Id);
2834 -- Subsidiary routine to the analysis of pragmas Abstract_State,
2835 -- Initial_Condition and Initializes. Determine whether pragma First
2836 -- appears before pragma Second. If this is not the case, emit an error.
2838 procedure Check_Duplicate_Pragma (E : Entity_Id);
2839 -- Check if a rep item of the same name as the current pragma is already
2840 -- chained as a rep pragma to the given entity. If so give a message
2841 -- about the duplicate, and then raise Pragma_Exit so does not return.
2842 -- Note that if E is a type, then this routine avoids flagging a pragma
2843 -- which applies to a parent type from which E is derived.
2845 procedure Check_Duplicated_Export_Name (Nam : Node_Id);
2846 -- Nam is an N_String_Literal node containing the external name set by
2847 -- an Import or Export pragma (or extended Import or Export pragma).
2848 -- This procedure checks for possible duplications if this is the export
2849 -- case, and if found, issues an appropriate error message.
2851 procedure Check_Expr_Is_OK_Static_Expression
2852 (Expr : Node_Id;
2853 Typ : Entity_Id := Empty);
2854 -- Check the specified expression Expr to make sure that it is a static
2855 -- expression of the given type (i.e. it will be analyzed and resolved
2856 -- using this type, which can be any valid argument to Resolve, e.g.
2857 -- Any_Integer is OK). If not, given error and raise Pragma_Exit. If
2858 -- Typ is left Empty, then any static expression is allowed. Includes
2859 -- checking that the expression does not raise Constraint_Error.
2861 procedure Check_First_Subtype (Arg : Node_Id);
2862 -- Checks that Arg, whose expression is an entity name, references a
2863 -- first subtype.
2865 procedure Check_Identifier (Arg : Node_Id; Id : Name_Id);
2866 -- Checks that the given argument has an identifier, and if so, requires
2867 -- it to match the given identifier name. If there is no identifier, or
2868 -- a non-matching identifier, then an error message is given and
2869 -- Pragma_Exit is raised.
2871 procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id);
2872 -- Checks that the given argument has an identifier, and if so, requires
2873 -- it to match one of the given identifier names. If there is no
2874 -- identifier, or a non-matching identifier, then an error message is
2875 -- given and Pragma_Exit is raised.
2877 procedure Check_In_Main_Program;
2878 -- Common checks for pragmas that appear within a main program
2879 -- (Priority, Main_Storage, Time_Slice, Relative_Deadline, CPU).
2881 procedure Check_Interrupt_Or_Attach_Handler;
2882 -- Common processing for first argument of pragma Interrupt_Handler or
2883 -- pragma Attach_Handler.
2885 procedure Check_Loop_Pragma_Placement;
2886 -- Verify whether pragmas Loop_Invariant, Loop_Optimize and Loop_Variant
2887 -- appear immediately within a construct restricted to loops, and that
2888 -- pragmas Loop_Invariant and Loop_Variant are grouped together.
2890 procedure Check_Is_In_Decl_Part_Or_Package_Spec;
2891 -- Check that pragma appears in a declarative part, or in a package
2892 -- specification, i.e. that it does not occur in a statement sequence
2893 -- in a body.
2895 procedure Check_No_Identifier (Arg : Node_Id);
2896 -- Checks that the given argument does not have an identifier. If
2897 -- an identifier is present, then an error message is issued, and
2898 -- Pragma_Exit is raised.
2900 procedure Check_No_Identifiers;
2901 -- Checks that none of the arguments to the pragma has an identifier.
2902 -- If any argument has an identifier, then an error message is issued,
2903 -- and Pragma_Exit is raised.
2905 procedure Check_No_Link_Name;
2906 -- Checks that no link name is specified
2908 procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id);
2909 -- Checks if the given argument has an identifier, and if so, requires
2910 -- it to match the given identifier name. If there is a non-matching
2911 -- identifier, then an error message is given and Pragma_Exit is raised.
2913 procedure Check_Optional_Identifier (Arg : Node_Id; Id : String);
2914 -- Checks if the given argument has an identifier, and if so, requires
2915 -- it to match the given identifier name. If there is a non-matching
2916 -- identifier, then an error message is given and Pragma_Exit is raised.
2917 -- In this version of the procedure, the identifier name is given as
2918 -- a string with lower case letters.
2920 procedure Check_Pre_Post;
2921 -- Called to perform checks for Pre, Pre_Class, Post, Post_Class
2922 -- pragmas. These are processed by transformation to equivalent
2923 -- Precondition and Postcondition pragmas, but Pre and Post need an
2924 -- additional check that they are not used in a subprogram body when
2925 -- there is a separate spec present.
2927 procedure Check_Precondition_Postcondition (In_Body : out Boolean);
2928 -- Called to process a precondition or postcondition pragma. There are
2929 -- three cases:
2931 -- The pragma appears after a subprogram spec
2933 -- If the corresponding check is not enabled, the pragma is analyzed
2934 -- but otherwise ignored and control returns with In_Body set False.
2936 -- If the check is enabled, then the first step is to analyze the
2937 -- pragma, but this is skipped if the subprogram spec appears within
2938 -- a package specification (because this is the case where we delay
2939 -- analysis till the end of the spec). Then (whether or not it was
2940 -- analyzed), the pragma is chained to the subprogram in question
2941 -- (using Pre_Post_Conditions and Next_Pragma) and control returns
2942 -- to the caller with In_Body set False.
2944 -- The pragma appears at the start of subprogram body declarations
2946 -- In this case an immediate return to the caller is made with
2947 -- In_Body set True, and the pragma is NOT analyzed.
2949 -- In all other cases, an error message for bad placement is given
2951 procedure Check_Static_Constraint (Constr : Node_Id);
2952 -- Constr is a constraint from an N_Subtype_Indication node from a
2953 -- component constraint in an Unchecked_Union type. This routine checks
2954 -- that the constraint is static as required by the restrictions for
2955 -- Unchecked_Union.
2957 procedure Check_Test_Case;
2958 -- Called to process a test-case pragma. It starts with checking pragma
2959 -- arguments, and the rest of the treatment is similar to the one for
2960 -- pre- and postcondition in Check_Precondition_Postcondition, except
2961 -- the placement rules for the test-case pragma are stricter. These
2962 -- pragmas may only occur after a subprogram spec declared directly
2963 -- in a package spec unit. In this case, the pragma is chained to the
2964 -- subprogram in question (using Contract_Test_Cases and Next_Pragma)
2965 -- and analysis of the pragma is delayed till the end of the spec. In
2966 -- all other cases, an error message for bad placement is given.
2968 procedure Check_Valid_Configuration_Pragma;
2969 -- Legality checks for placement of a configuration pragma
2971 procedure Check_Valid_Library_Unit_Pragma;
2972 -- Legality checks for library unit pragmas. A special case arises for
2973 -- pragmas in generic instances that come from copies of the original
2974 -- library unit pragmas in the generic templates. In the case of other
2975 -- than library level instantiations these can appear in contexts which
2976 -- would normally be invalid (they only apply to the original template
2977 -- and to library level instantiations), and they are simply ignored,
2978 -- which is implemented by rewriting them as null statements.
2980 procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id);
2981 -- Check an Unchecked_Union variant for lack of nested variants and
2982 -- presence of at least one component. UU_Typ is the related Unchecked_
2983 -- Union type.
2985 procedure Ensure_Aggregate_Form (Arg : Node_Id);
2986 -- Subsidiary routine to the processing of pragmas Abstract_State,
2987 -- Contract_Cases, Depends, Global, Initializes, Refined_Depends,
2988 -- Refined_Global and Refined_State. Transform argument Arg into an
2989 -- aggregate if not one already. N_Null is never transformed.
2991 procedure Error_Pragma (Msg : String);
2992 pragma No_Return (Error_Pragma);
2993 -- Outputs error message for current pragma. The message contains a %
2994 -- that will be replaced with the pragma name, and the flag is placed
2995 -- on the pragma itself. Pragma_Exit is then raised. Note: this routine
2996 -- calls Fix_Error (see spec of that procedure for details).
2998 procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id);
2999 pragma No_Return (Error_Pragma_Arg);
3000 -- Outputs error message for current pragma. The message may contain
3001 -- a % that will be replaced with the pragma name. The parameter Arg
3002 -- may either be a pragma argument association, in which case the flag
3003 -- is placed on the expression of this association, or an expression,
3004 -- in which case the flag is placed directly on the expression. The
3005 -- message is placed using Error_Msg_N, so the message may also contain
3006 -- an & insertion character which will reference the given Arg value.
3007 -- After placing the message, Pragma_Exit is raised. Note: this routine
3008 -- calls Fix_Error (see spec of that procedure for details).
3010 procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id);
3011 pragma No_Return (Error_Pragma_Arg);
3012 -- Similar to above form of Error_Pragma_Arg except that two messages
3013 -- are provided, the second is a continuation comment starting with \.
3015 procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id);
3016 pragma No_Return (Error_Pragma_Arg_Ident);
3017 -- Outputs error message for current pragma. The message may contain a %
3018 -- that will be replaced with the pragma name. The parameter Arg must be
3019 -- a pragma argument association with a non-empty identifier (i.e. its
3020 -- Chars field must be set), and the error message is placed on the
3021 -- identifier. The message is placed using Error_Msg_N so the message
3022 -- may also contain an & insertion character which will reference
3023 -- the identifier. After placing the message, Pragma_Exit is raised.
3024 -- Note: this routine calls Fix_Error (see spec of that procedure for
3025 -- details).
3027 procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id);
3028 pragma No_Return (Error_Pragma_Ref);
3029 -- Outputs error message for current pragma. The message may contain
3030 -- a % that will be replaced with the pragma name. The parameter Ref
3031 -- must be an entity whose name can be referenced by & and sloc by #.
3032 -- After placing the message, Pragma_Exit is raised. Note: this routine
3033 -- calls Fix_Error (see spec of that procedure for details).
3035 function Find_Lib_Unit_Name return Entity_Id;
3036 -- Used for a library unit pragma to find the entity to which the
3037 -- library unit pragma applies, returns the entity found.
3039 procedure Find_Program_Unit_Name (Id : Node_Id);
3040 -- If the pragma is a compilation unit pragma, the id must denote the
3041 -- compilation unit in the same compilation, and the pragma must appear
3042 -- in the list of preceding or trailing pragmas. If it is a program
3043 -- unit pragma that is not a compilation unit pragma, then the
3044 -- identifier must be visible.
3046 function Find_Unique_Parameterless_Procedure
3047 (Name : Entity_Id;
3048 Arg : Node_Id) return Entity_Id;
3049 -- Used for a procedure pragma to find the unique parameterless
3050 -- procedure identified by Name, returns it if it exists, otherwise
3051 -- errors out and uses Arg as the pragma argument for the message.
3053 function Fix_Error (Msg : String) return String;
3054 -- This is called prior to issuing an error message. Msg is the normal
3055 -- error message issued in the pragma case. This routine checks for the
3056 -- case of a pragma coming from an aspect in the source, and returns a
3057 -- message suitable for the aspect case as follows:
3059 -- Each substring "pragma" is replaced by "aspect"
3061 -- If "argument of" is at the start of the error message text, it is
3062 -- replaced by "entity for".
3064 -- If "argument" is at the start of the error message text, it is
3065 -- replaced by "entity".
3067 -- So for example, "argument of pragma X must be discrete type"
3068 -- returns "entity for aspect X must be a discrete type".
3070 -- Finally Error_Msg_Name_1 is set to the name of the aspect (which may
3071 -- be different from the pragma name). If the current pragma results
3072 -- from rewriting another pragma, then Error_Msg_Name_1 is set to the
3073 -- original pragma name.
3075 procedure Gather_Associations
3076 (Names : Name_List;
3077 Args : out Args_List);
3078 -- This procedure is used to gather the arguments for a pragma that
3079 -- permits arbitrary ordering of parameters using the normal rules
3080 -- for named and positional parameters. The Names argument is a list
3081 -- of Name_Id values that corresponds to the allowed pragma argument
3082 -- association identifiers in order. The result returned in Args is
3083 -- a list of corresponding expressions that are the pragma arguments.
3084 -- Note that this is a list of expressions, not of pragma argument
3085 -- associations (Gather_Associations has completely checked all the
3086 -- optional identifiers when it returns). An entry in Args is Empty
3087 -- on return if the corresponding argument is not present.
3089 procedure GNAT_Pragma;
3090 -- Called for all GNAT defined pragmas to check the relevant restriction
3091 -- (No_Implementation_Pragmas).
3093 function Is_Before_First_Decl
3094 (Pragma_Node : Node_Id;
3095 Decls : List_Id) return Boolean;
3096 -- Return True if Pragma_Node is before the first declarative item in
3097 -- Decls where Decls is the list of declarative items.
3099 function Is_Configuration_Pragma return Boolean;
3100 -- Determines if the placement of the current pragma is appropriate
3101 -- for a configuration pragma.
3103 function Is_In_Context_Clause return Boolean;
3104 -- Returns True if pragma appears within the context clause of a unit,
3105 -- and False for any other placement (does not generate any messages).
3107 function Is_Static_String_Expression (Arg : Node_Id) return Boolean;
3108 -- Analyzes the argument, and determines if it is a static string
3109 -- expression, returns True if so, False if non-static or not String.
3110 -- A special case is that a string literal returns True in Ada 83 mode
3111 -- (which has no such thing as static string expressions).
3113 procedure Pragma_Misplaced;
3114 pragma No_Return (Pragma_Misplaced);
3115 -- Issue fatal error message for misplaced pragma
3117 procedure Process_Atomic_Independent_Shared_Volatile;
3118 -- Common processing for pragmas Atomic, Independent, Shared, Volatile.
3119 -- Note that Shared is an obsolete Ada 83 pragma and treated as being
3120 -- identical in effect to pragma Atomic.
3122 procedure Process_Compile_Time_Warning_Or_Error;
3123 -- Common processing for Compile_Time_Error and Compile_Time_Warning
3125 procedure Process_Convention
3126 (C : out Convention_Id;
3127 Ent : out Entity_Id);
3128 -- Common processing for Convention, Interface, Import and Export.
3129 -- Checks first two arguments of pragma, and sets the appropriate
3130 -- convention value in the specified entity or entities. On return
3131 -- C is the convention, Ent is the referenced entity.
3133 procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id);
3134 -- Common processing for Disable/Enable_Atomic_Synchronization. Nam is
3135 -- Name_Suppress for Disable and Name_Unsuppress for Enable.
3137 procedure Process_Extended_Import_Export_Object_Pragma
3138 (Arg_Internal : Node_Id;
3139 Arg_External : Node_Id;
3140 Arg_Size : Node_Id);
3141 -- Common processing for the pragmas Import/Export_Object. The three
3142 -- arguments correspond to the three named parameters of the pragmas. An
3143 -- argument is empty if the corresponding parameter is not present in
3144 -- the pragma.
3146 procedure Process_Extended_Import_Export_Internal_Arg
3147 (Arg_Internal : Node_Id := Empty);
3148 -- Common processing for all extended Import and Export pragmas. The
3149 -- argument is the pragma parameter for the Internal argument. If
3150 -- Arg_Internal is empty or inappropriate, an error message is posted.
3151 -- Otherwise, on normal return, the Entity_Field of Arg_Internal is
3152 -- set to identify the referenced entity.
3154 procedure Process_Extended_Import_Export_Subprogram_Pragma
3155 (Arg_Internal : Node_Id;
3156 Arg_External : Node_Id;
3157 Arg_Parameter_Types : Node_Id;
3158 Arg_Result_Type : Node_Id := Empty;
3159 Arg_Mechanism : Node_Id;
3160 Arg_Result_Mechanism : Node_Id := Empty);
3161 -- Common processing for all extended Import and Export pragmas applying
3162 -- to subprograms. The caller omits any arguments that do not apply to
3163 -- the pragma in question (for example, Arg_Result_Type can be non-Empty
3164 -- only in the Import_Function and Export_Function cases). The argument
3165 -- names correspond to the allowed pragma association identifiers.
3167 procedure Process_Generic_List;
3168 -- Common processing for Share_Generic and Inline_Generic
3170 procedure Process_Import_Or_Interface;
3171 -- Common processing for Import of Interface
3173 procedure Process_Import_Predefined_Type;
3174 -- Processing for completing a type with pragma Import. This is used
3175 -- to declare types that match predefined C types, especially for cases
3176 -- without corresponding Ada predefined type.
3178 type Inline_Status is (Suppressed, Disabled, Enabled);
3179 -- Inline status of a subprogram, indicated as follows:
3180 -- Suppressed: inlining is suppressed for the subprogram
3181 -- Disabled: no inlining is requested for the subprogram
3182 -- Enabled: inlining is requested/required for the subprogram
3184 procedure Process_Inline (Status : Inline_Status);
3185 -- Common processing for Inline, Inline_Always and No_Inline. Parameter
3186 -- indicates the inline status specified by the pragma.
3188 procedure Process_Interface_Name
3189 (Subprogram_Def : Entity_Id;
3190 Ext_Arg : Node_Id;
3191 Link_Arg : Node_Id);
3192 -- Given the last two arguments of pragma Import, pragma Export, or
3193 -- pragma Interface_Name, performs validity checks and sets the
3194 -- Interface_Name field of the given subprogram entity to the
3195 -- appropriate external or link name, depending on the arguments given.
3196 -- Ext_Arg is always present, but Link_Arg may be missing. Note that
3197 -- Ext_Arg may represent the Link_Name if Link_Arg is missing, and
3198 -- appropriate named notation is used for Ext_Arg. If neither Ext_Arg
3199 -- nor Link_Arg is present, the interface name is set to the default
3200 -- from the subprogram name.
3202 procedure Process_Interrupt_Or_Attach_Handler;
3203 -- Common processing for Interrupt and Attach_Handler pragmas
3205 procedure Process_Restrictions_Or_Restriction_Warnings (Warn : Boolean);
3206 -- Common processing for Restrictions and Restriction_Warnings pragmas.
3207 -- Warn is True for Restriction_Warnings, or for Restrictions if the
3208 -- flag Treat_Restrictions_As_Warnings is set, and False if this flag
3209 -- is not set in the Restrictions case.
3211 procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean);
3212 -- Common processing for Suppress and Unsuppress. The boolean parameter
3213 -- Suppress_Case is True for the Suppress case, and False for the
3214 -- Unsuppress case.
3216 procedure Set_Exported (E : Entity_Id; Arg : Node_Id);
3217 -- This procedure sets the Is_Exported flag for the given entity,
3218 -- checking that the entity was not previously imported. Arg is
3219 -- the argument that specified the entity. A check is also made
3220 -- for exporting inappropriate entities.
3222 procedure Set_Extended_Import_Export_External_Name
3223 (Internal_Ent : Entity_Id;
3224 Arg_External : Node_Id);
3225 -- Common processing for all extended import export pragmas. The first
3226 -- argument, Internal_Ent, is the internal entity, which has already
3227 -- been checked for validity by the caller. Arg_External is from the
3228 -- Import or Export pragma, and may be null if no External parameter
3229 -- was present. If Arg_External is present and is a non-null string
3230 -- (a null string is treated as the default), then the Interface_Name
3231 -- field of Internal_Ent is set appropriately.
3233 procedure Set_Imported (E : Entity_Id);
3234 -- This procedure sets the Is_Imported flag for the given entity,
3235 -- checking that it is not previously exported or imported.
3237 procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id);
3238 -- Mech is a parameter passing mechanism (see Import_Function syntax
3239 -- for MECHANISM_NAME). This routine checks that the mechanism argument
3240 -- has the right form, and if not issues an error message. If the
3241 -- argument has the right form then the Mechanism field of Ent is
3242 -- set appropriately.
3244 procedure Set_Rational_Profile;
3245 -- Activate the set of configuration pragmas and permissions that make
3246 -- up the Rational profile.
3248 procedure Set_Ravenscar_Profile (N : Node_Id);
3249 -- Activate the set of configuration pragmas and restrictions that make
3250 -- up the Ravenscar Profile. N is the corresponding pragma node, which
3251 -- is used for error messages on any constructs violating the profile.
3253 ----------------------------------
3254 -- Acquire_Warning_Match_String --
3255 ----------------------------------
3257 procedure Acquire_Warning_Match_String (Arg : Node_Id) is
3258 begin
3259 String_To_Name_Buffer
3260 (Strval (Expr_Value_S (Get_Pragma_Arg (Arg))));
3262 -- Add asterisk at start if not already there
3264 if Name_Len > 0 and then Name_Buffer (1) /= '*' then
3265 Name_Buffer (2 .. Name_Len + 1) :=
3266 Name_Buffer (1 .. Name_Len);
3267 Name_Buffer (1) := '*';
3268 Name_Len := Name_Len + 1;
3269 end if;
3271 -- Add asterisk at end if not already there
3273 if Name_Buffer (Name_Len) /= '*' then
3274 Name_Len := Name_Len + 1;
3275 Name_Buffer (Name_Len) := '*';
3276 end if;
3277 end Acquire_Warning_Match_String;
3279 ---------------------
3280 -- Ada_2005_Pragma --
3281 ---------------------
3283 procedure Ada_2005_Pragma is
3284 begin
3285 if Ada_Version <= Ada_95 then
3286 Check_Restriction (No_Implementation_Pragmas, N);
3287 end if;
3288 end Ada_2005_Pragma;
3290 ---------------------
3291 -- Ada_2012_Pragma --
3292 ---------------------
3294 procedure Ada_2012_Pragma is
3295 begin
3296 if Ada_Version <= Ada_2005 then
3297 Check_Restriction (No_Implementation_Pragmas, N);
3298 end if;
3299 end Ada_2012_Pragma;
3301 ---------------------
3302 -- Analyze_Part_Of --
3303 ---------------------
3305 procedure Analyze_Part_Of
3306 (Item_Id : Entity_Id;
3307 State : Node_Id;
3308 Indic : Node_Id;
3309 Legal : out Boolean)
3311 Pack_Id : Entity_Id;
3312 Placement : State_Space_Kind;
3313 Parent_Unit : Entity_Id;
3314 State_Id : Entity_Id;
3316 begin
3317 -- Assume that the pragma/option is illegal
3319 Legal := False;
3321 if Nkind_In (State, N_Expanded_Name,
3322 N_Identifier,
3323 N_Selected_Component)
3324 then
3325 Analyze (State);
3326 Resolve_State (State);
3328 if Is_Entity_Name (State)
3329 and then Ekind (Entity (State)) = E_Abstract_State
3330 then
3331 State_Id := Entity (State);
3333 else
3334 SPARK_Msg_N
3335 ("indicator Part_Of must denote an abstract state", State);
3336 return;
3337 end if;
3339 -- This is a syntax error, always report
3341 else
3342 Error_Msg_N
3343 ("indicator Part_Of must denote an abstract state", State);
3344 return;
3345 end if;
3347 -- Determine where the state, variable or the package instantiation
3348 -- lives with respect to the enclosing packages or package bodies (if
3349 -- any). This placement dictates the legality of the encapsulating
3350 -- state.
3352 Find_Placement_In_State_Space
3353 (Item_Id => Item_Id,
3354 Placement => Placement,
3355 Pack_Id => Pack_Id);
3357 -- The item appears in a non-package construct with a declarative
3358 -- part (subprogram, block, etc). As such, the item is not allowed
3359 -- to be a part of an encapsulating state because the item is not
3360 -- visible.
3362 if Placement = Not_In_Package then
3363 SPARK_Msg_N
3364 ("indicator Part_Of cannot appear in this context "
3365 & "(SPARK RM 7.2.6(5))", Indic);
3366 Error_Msg_Name_1 := Chars (Scope (State_Id));
3367 SPARK_Msg_NE
3368 ("\& is not part of the hidden state of package %",
3369 Indic, Item_Id);
3371 -- The item appears in the visible state space of some package. In
3372 -- general this scenario does not warrant Part_Of except when the
3373 -- package is a private child unit and the encapsulating state is
3374 -- declared in a parent unit or a public descendant of that parent
3375 -- unit.
3377 elsif Placement = Visible_State_Space then
3378 if Is_Child_Unit (Pack_Id)
3379 and then Is_Private_Descendant (Pack_Id)
3380 then
3381 -- A variable or state abstraction which is part of the
3382 -- visible state of a private child unit (or one of its public
3383 -- descendants) must have its Part_Of indicator specified. The
3384 -- Part_Of indicator must denote a state abstraction declared
3385 -- by either the parent unit of the private unit or by a public
3386 -- descendant of that parent unit.
3388 -- Find nearest private ancestor (which can be the current unit
3389 -- itself).
3391 Parent_Unit := Pack_Id;
3392 while Present (Parent_Unit) loop
3393 exit when Private_Present
3394 (Parent (Unit_Declaration_Node (Parent_Unit)));
3395 Parent_Unit := Scope (Parent_Unit);
3396 end loop;
3398 Parent_Unit := Scope (Parent_Unit);
3400 if not Is_Child_Or_Sibling (Pack_Id, Scope (State_Id)) then
3401 SPARK_Msg_NE
3402 ("indicator Part_Of must denote an abstract state of& "
3403 & "or public descendant (SPARK RM 7.2.6(3))",
3404 Indic, Parent_Unit);
3406 elsif Scope (State_Id) = Parent_Unit
3407 or else (Is_Ancestor_Package (Parent_Unit, Scope (State_Id))
3408 and then
3409 not Is_Private_Descendant (Scope (State_Id)))
3410 then
3411 null;
3413 else
3414 SPARK_Msg_NE
3415 ("indicator Part_Of must denote an abstract state of& "
3416 & "or public descendant (SPARK RM 7.2.6(3))",
3417 Indic, Parent_Unit);
3418 end if;
3420 -- Indicator Part_Of is not needed when the related package is not
3421 -- a private child unit or a public descendant thereof.
3423 else
3424 SPARK_Msg_N
3425 ("indicator Part_Of cannot appear in this context "
3426 & "(SPARK RM 7.2.6(5))", Indic);
3427 Error_Msg_Name_1 := Chars (Pack_Id);
3428 SPARK_Msg_NE
3429 ("\& is declared in the visible part of package %",
3430 Indic, Item_Id);
3431 end if;
3433 -- When the item appears in the private state space of a package, the
3434 -- encapsulating state must be declared in the same package.
3436 elsif Placement = Private_State_Space then
3437 if Scope (State_Id) /= Pack_Id then
3438 SPARK_Msg_NE
3439 ("indicator Part_Of must designate an abstract state of "
3440 & "package & (SPARK RM 7.2.6(2))", Indic, Pack_Id);
3441 Error_Msg_Name_1 := Chars (Pack_Id);
3442 SPARK_Msg_NE
3443 ("\& is declared in the private part of package %",
3444 Indic, Item_Id);
3445 end if;
3447 -- Items declared in the body state space of a package do not need
3448 -- Part_Of indicators as the refinement has already been seen.
3450 else
3451 SPARK_Msg_N
3452 ("indicator Part_Of cannot appear in this context "
3453 & "(SPARK RM 7.2.6(5))", Indic);
3455 if Scope (State_Id) = Pack_Id then
3456 Error_Msg_Name_1 := Chars (Pack_Id);
3457 SPARK_Msg_NE
3458 ("\& is declared in the body of package %", Indic, Item_Id);
3459 end if;
3460 end if;
3462 Legal := True;
3463 end Analyze_Part_Of;
3465 ----------------------------
3466 -- Analyze_Refined_Pragma --
3467 ----------------------------
3469 procedure Analyze_Refined_Pragma
3470 (Spec_Id : out Entity_Id;
3471 Body_Id : out Entity_Id;
3472 Legal : out Boolean)
3474 Body_Decl : Node_Id;
3475 Spec_Decl : Node_Id;
3477 begin
3478 -- Assume that the pragma is illegal
3480 Spec_Id := Empty;
3481 Body_Id := Empty;
3482 Legal := False;
3484 GNAT_Pragma;
3485 Check_Arg_Count (1);
3486 Check_No_Identifiers;
3488 if Nam_In (Pname, Name_Refined_Depends,
3489 Name_Refined_Global,
3490 Name_Refined_State)
3491 then
3492 Ensure_Aggregate_Form (Arg1);
3493 end if;
3495 -- Verify the placement of the pragma and check for duplicates. The
3496 -- pragma must apply to a subprogram body [stub].
3498 Body_Decl := Find_Related_Subprogram_Or_Body (N, Do_Checks => True);
3500 -- Extract the entities of the spec and body
3502 if Nkind (Body_Decl) = N_Subprogram_Body then
3503 Body_Id := Defining_Entity (Body_Decl);
3504 Spec_Id := Corresponding_Spec (Body_Decl);
3506 elsif Nkind (Body_Decl) = N_Subprogram_Body_Stub then
3507 Body_Id := Defining_Entity (Body_Decl);
3508 Spec_Id := Corresponding_Spec_Of_Stub (Body_Decl);
3510 else
3511 Pragma_Misplaced;
3512 return;
3513 end if;
3515 -- The pragma must apply to the second declaration of a subprogram.
3516 -- In other words, the body [stub] cannot acts as a spec.
3518 if No (Spec_Id) then
3519 Error_Pragma ("pragma % cannot apply to a stand alone body");
3520 return;
3522 -- Catch the case where the subprogram body is a subunit and acts as
3523 -- the third declaration of the subprogram.
3525 elsif Nkind (Parent (Body_Decl)) = N_Subunit then
3526 Error_Pragma ("pragma % cannot apply to a subunit");
3527 return;
3528 end if;
3530 -- The pragma can only apply to the body [stub] of a subprogram
3531 -- declared in the visible part of a package. Retrieve the context of
3532 -- the subprogram declaration.
3534 Spec_Decl := Parent (Parent (Spec_Id));
3536 if Nkind (Parent (Spec_Decl)) /= N_Package_Specification then
3537 Error_Pragma
3538 ("pragma % must apply to the body of a subprogram declared in a "
3539 & "package specification");
3540 return;
3541 end if;
3543 -- If we get here, then the pragma is legal
3545 Legal := True;
3546 end Analyze_Refined_Pragma;
3548 --------------------------
3549 -- Check_Ada_83_Warning --
3550 --------------------------
3552 procedure Check_Ada_83_Warning is
3553 begin
3554 if Ada_Version = Ada_83 and then Comes_From_Source (N) then
3555 Error_Msg_N ("(Ada 83) pragma& is non-standard??", N);
3556 end if;
3557 end Check_Ada_83_Warning;
3559 ---------------------
3560 -- Check_Arg_Count --
3561 ---------------------
3563 procedure Check_Arg_Count (Required : Nat) is
3564 begin
3565 if Arg_Count /= Required then
3566 Error_Pragma ("wrong number of arguments for pragma%");
3567 end if;
3568 end Check_Arg_Count;
3570 --------------------------------
3571 -- Check_Arg_Is_External_Name --
3572 --------------------------------
3574 procedure Check_Arg_Is_External_Name (Arg : Node_Id) is
3575 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
3577 begin
3578 if Nkind (Argx) = N_Identifier then
3579 return;
3581 else
3582 Analyze_And_Resolve (Argx, Standard_String);
3584 if Is_OK_Static_Expression (Argx) then
3585 return;
3587 elsif Etype (Argx) = Any_Type then
3588 raise Pragma_Exit;
3590 -- An interesting special case, if we have a string literal and
3591 -- we are in Ada 83 mode, then we allow it even though it will
3592 -- not be flagged as static. This allows expected Ada 83 mode
3593 -- use of external names which are string literals, even though
3594 -- technically these are not static in Ada 83.
3596 elsif Ada_Version = Ada_83
3597 and then Nkind (Argx) = N_String_Literal
3598 then
3599 return;
3601 -- Static expression that raises Constraint_Error. This has
3602 -- already been flagged, so just exit from pragma processing.
3604 elsif Is_OK_Static_Expression (Argx) then
3605 raise Pragma_Exit;
3607 -- Here we have a real error (non-static expression)
3609 else
3610 Error_Msg_Name_1 := Pname;
3612 declare
3613 Msg : constant String :=
3614 "argument for pragma% must be a identifier or "
3615 & "static string expression!";
3616 begin
3617 Flag_Non_Static_Expr (Fix_Error (Msg), Argx);
3618 raise Pragma_Exit;
3619 end;
3620 end if;
3621 end if;
3622 end Check_Arg_Is_External_Name;
3624 -----------------------------
3625 -- Check_Arg_Is_Identifier --
3626 -----------------------------
3628 procedure Check_Arg_Is_Identifier (Arg : Node_Id) is
3629 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
3630 begin
3631 if Nkind (Argx) /= N_Identifier then
3632 Error_Pragma_Arg
3633 ("argument for pragma% must be identifier", Argx);
3634 end if;
3635 end Check_Arg_Is_Identifier;
3637 ----------------------------------
3638 -- Check_Arg_Is_Integer_Literal --
3639 ----------------------------------
3641 procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id) is
3642 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
3643 begin
3644 if Nkind (Argx) /= N_Integer_Literal then
3645 Error_Pragma_Arg
3646 ("argument for pragma% must be integer literal", Argx);
3647 end if;
3648 end Check_Arg_Is_Integer_Literal;
3650 -------------------------------------------
3651 -- Check_Arg_Is_Library_Level_Local_Name --
3652 -------------------------------------------
3654 -- LOCAL_NAME ::=
3655 -- DIRECT_NAME
3656 -- | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
3657 -- | library_unit_NAME
3659 procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id) is
3660 begin
3661 Check_Arg_Is_Local_Name (Arg);
3663 if not Is_Library_Level_Entity (Entity (Get_Pragma_Arg (Arg)))
3664 and then Comes_From_Source (N)
3665 then
3666 Error_Pragma_Arg
3667 ("argument for pragma% must be library level entity", Arg);
3668 end if;
3669 end Check_Arg_Is_Library_Level_Local_Name;
3671 -----------------------------
3672 -- Check_Arg_Is_Local_Name --
3673 -----------------------------
3675 -- LOCAL_NAME ::=
3676 -- DIRECT_NAME
3677 -- | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
3678 -- | library_unit_NAME
3680 procedure Check_Arg_Is_Local_Name (Arg : Node_Id) is
3681 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
3683 begin
3684 Analyze (Argx);
3686 if Nkind (Argx) not in N_Direct_Name
3687 and then (Nkind (Argx) /= N_Attribute_Reference
3688 or else Present (Expressions (Argx))
3689 or else Nkind (Prefix (Argx)) /= N_Identifier)
3690 and then (not Is_Entity_Name (Argx)
3691 or else not Is_Compilation_Unit (Entity (Argx)))
3692 then
3693 Error_Pragma_Arg ("argument for pragma% must be local name", Argx);
3694 end if;
3696 -- No further check required if not an entity name
3698 if not Is_Entity_Name (Argx) then
3699 null;
3701 else
3702 declare
3703 OK : Boolean;
3704 Ent : constant Entity_Id := Entity (Argx);
3705 Scop : constant Entity_Id := Scope (Ent);
3707 begin
3708 -- Case of a pragma applied to a compilation unit: pragma must
3709 -- occur immediately after the program unit in the compilation.
3711 if Is_Compilation_Unit (Ent) then
3712 declare
3713 Decl : constant Node_Id := Unit_Declaration_Node (Ent);
3715 begin
3716 -- Case of pragma placed immediately after spec
3718 if Parent (N) = Aux_Decls_Node (Parent (Decl)) then
3719 OK := True;
3721 -- Case of pragma placed immediately after body
3723 elsif Nkind (Decl) = N_Subprogram_Declaration
3724 and then Present (Corresponding_Body (Decl))
3725 then
3726 OK := Parent (N) =
3727 Aux_Decls_Node
3728 (Parent (Unit_Declaration_Node
3729 (Corresponding_Body (Decl))));
3731 -- All other cases are illegal
3733 else
3734 OK := False;
3735 end if;
3736 end;
3738 -- Special restricted placement rule from 10.2.1(11.8/2)
3740 elsif Is_Generic_Formal (Ent)
3741 and then Prag_Id = Pragma_Preelaborable_Initialization
3742 then
3743 OK := List_Containing (N) =
3744 Generic_Formal_Declarations
3745 (Unit_Declaration_Node (Scop));
3747 -- If this is an aspect applied to a subprogram body, the
3748 -- pragma is inserted in its declarative part.
3750 elsif From_Aspect_Specification (N)
3751 and then Ent = Current_Scope
3752 and then
3753 Nkind (Unit_Declaration_Node (Ent)) = N_Subprogram_Body
3754 then
3755 OK := True;
3757 -- If the aspect is a predicate (possibly others ???) and the
3758 -- context is a record type, this is a discriminant expression
3759 -- within a type declaration, that freezes the predicated
3760 -- subtype.
3762 elsif From_Aspect_Specification (N)
3763 and then Prag_Id = Pragma_Predicate
3764 and then Ekind (Current_Scope) = E_Record_Type
3765 and then Scop = Scope (Current_Scope)
3766 then
3767 OK := True;
3769 -- Default case, just check that the pragma occurs in the scope
3770 -- of the entity denoted by the name.
3772 else
3773 OK := Current_Scope = Scop;
3774 end if;
3776 if not OK then
3777 Error_Pragma_Arg
3778 ("pragma% argument must be in same declarative part", Arg);
3779 end if;
3780 end;
3781 end if;
3782 end Check_Arg_Is_Local_Name;
3784 ---------------------------------
3785 -- Check_Arg_Is_Locking_Policy --
3786 ---------------------------------
3788 procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id) is
3789 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
3791 begin
3792 Check_Arg_Is_Identifier (Argx);
3794 if not Is_Locking_Policy_Name (Chars (Argx)) then
3795 Error_Pragma_Arg ("& is not a valid locking policy name", Argx);
3796 end if;
3797 end Check_Arg_Is_Locking_Policy;
3799 -----------------------------------------------
3800 -- Check_Arg_Is_Partition_Elaboration_Policy --
3801 -----------------------------------------------
3803 procedure Check_Arg_Is_Partition_Elaboration_Policy (Arg : Node_Id) is
3804 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
3806 begin
3807 Check_Arg_Is_Identifier (Argx);
3809 if not Is_Partition_Elaboration_Policy_Name (Chars (Argx)) then
3810 Error_Pragma_Arg
3811 ("& is not a valid partition elaboration policy name", Argx);
3812 end if;
3813 end Check_Arg_Is_Partition_Elaboration_Policy;
3815 -------------------------
3816 -- Check_Arg_Is_One_Of --
3817 -------------------------
3819 procedure Check_Arg_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
3820 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
3822 begin
3823 Check_Arg_Is_Identifier (Argx);
3825 if not Nam_In (Chars (Argx), N1, N2) then
3826 Error_Msg_Name_2 := N1;
3827 Error_Msg_Name_3 := N2;
3828 Error_Pragma_Arg ("argument for pragma% must be% or%", Argx);
3829 end if;
3830 end Check_Arg_Is_One_Of;
3832 procedure Check_Arg_Is_One_Of
3833 (Arg : Node_Id;
3834 N1, N2, N3 : Name_Id)
3836 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
3838 begin
3839 Check_Arg_Is_Identifier (Argx);
3841 if not Nam_In (Chars (Argx), N1, N2, N3) then
3842 Error_Pragma_Arg ("invalid argument for pragma%", Argx);
3843 end if;
3844 end Check_Arg_Is_One_Of;
3846 procedure Check_Arg_Is_One_Of
3847 (Arg : Node_Id;
3848 N1, N2, N3, N4 : Name_Id)
3850 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
3852 begin
3853 Check_Arg_Is_Identifier (Argx);
3855 if not Nam_In (Chars (Argx), N1, N2, N3, N4) then
3856 Error_Pragma_Arg ("invalid argument for pragma%", Argx);
3857 end if;
3858 end Check_Arg_Is_One_Of;
3860 procedure Check_Arg_Is_One_Of
3861 (Arg : Node_Id;
3862 N1, N2, N3, N4, N5 : Name_Id)
3864 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
3866 begin
3867 Check_Arg_Is_Identifier (Argx);
3869 if not Nam_In (Chars (Argx), N1, N2, N3, N4, N5) then
3870 Error_Pragma_Arg ("invalid argument for pragma%", Argx);
3871 end if;
3872 end Check_Arg_Is_One_Of;
3874 ---------------------------------
3875 -- Check_Arg_Is_Queuing_Policy --
3876 ---------------------------------
3878 procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id) is
3879 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
3881 begin
3882 Check_Arg_Is_Identifier (Argx);
3884 if not Is_Queuing_Policy_Name (Chars (Argx)) then
3885 Error_Pragma_Arg ("& is not a valid queuing policy name", Argx);
3886 end if;
3887 end Check_Arg_Is_Queuing_Policy;
3889 ---------------------------------------
3890 -- Check_Arg_Is_OK_Static_Expression --
3891 ---------------------------------------
3893 procedure Check_Arg_Is_OK_Static_Expression
3894 (Arg : Node_Id;
3895 Typ : Entity_Id := Empty)
3897 begin
3898 Check_Expr_Is_OK_Static_Expression (Get_Pragma_Arg (Arg), Typ);
3899 end Check_Arg_Is_OK_Static_Expression;
3901 ------------------------------------------
3902 -- Check_Arg_Is_Task_Dispatching_Policy --
3903 ------------------------------------------
3905 procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id) is
3906 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
3908 begin
3909 Check_Arg_Is_Identifier (Argx);
3911 if not Is_Task_Dispatching_Policy_Name (Chars (Argx)) then
3912 Error_Pragma_Arg
3913 ("& is not an allowed task dispatching policy name", Argx);
3914 end if;
3915 end Check_Arg_Is_Task_Dispatching_Policy;
3917 ---------------------
3918 -- Check_Arg_Order --
3919 ---------------------
3921 procedure Check_Arg_Order (Names : Name_List) is
3922 Arg : Node_Id;
3924 Highest_So_Far : Natural := 0;
3925 -- Highest index in Names seen do far
3927 begin
3928 Arg := Arg1;
3929 for J in 1 .. Arg_Count loop
3930 if Chars (Arg) /= No_Name then
3931 for K in Names'Range loop
3932 if Chars (Arg) = Names (K) then
3933 if K < Highest_So_Far then
3934 Error_Msg_Name_1 := Pname;
3935 Error_Msg_N
3936 ("parameters out of order for pragma%", Arg);
3937 Error_Msg_Name_1 := Names (K);
3938 Error_Msg_Name_2 := Names (Highest_So_Far);
3939 Error_Msg_N ("\% must appear before %", Arg);
3940 raise Pragma_Exit;
3942 else
3943 Highest_So_Far := K;
3944 end if;
3945 end if;
3946 end loop;
3947 end if;
3949 Arg := Next (Arg);
3950 end loop;
3951 end Check_Arg_Order;
3953 --------------------------------
3954 -- Check_At_Least_N_Arguments --
3955 --------------------------------
3957 procedure Check_At_Least_N_Arguments (N : Nat) is
3958 begin
3959 if Arg_Count < N then
3960 Error_Pragma ("too few arguments for pragma%");
3961 end if;
3962 end Check_At_Least_N_Arguments;
3964 -------------------------------
3965 -- Check_At_Most_N_Arguments --
3966 -------------------------------
3968 procedure Check_At_Most_N_Arguments (N : Nat) is
3969 Arg : Node_Id;
3970 begin
3971 if Arg_Count > N then
3972 Arg := Arg1;
3973 for J in 1 .. N loop
3974 Next (Arg);
3975 Error_Pragma_Arg ("too many arguments for pragma%", Arg);
3976 end loop;
3977 end if;
3978 end Check_At_Most_N_Arguments;
3980 ---------------------
3981 -- Check_Component --
3982 ---------------------
3984 procedure Check_Component
3985 (Comp : Node_Id;
3986 UU_Typ : Entity_Id;
3987 In_Variant_Part : Boolean := False)
3989 Comp_Id : constant Entity_Id := Defining_Identifier (Comp);
3990 Sindic : constant Node_Id :=
3991 Subtype_Indication (Component_Definition (Comp));
3992 Typ : constant Entity_Id := Etype (Comp_Id);
3994 begin
3995 -- Ada 2005 (AI-216): If a component subtype is subject to a per-
3996 -- object constraint, then the component type shall be an Unchecked_
3997 -- Union.
3999 if Nkind (Sindic) = N_Subtype_Indication
4000 and then Has_Per_Object_Constraint (Comp_Id)
4001 and then not Is_Unchecked_Union (Etype (Subtype_Mark (Sindic)))
4002 then
4003 Error_Msg_N
4004 ("component subtype subject to per-object constraint "
4005 & "must be an Unchecked_Union", Comp);
4007 -- Ada 2012 (AI05-0026): For an unchecked union type declared within
4008 -- the body of a generic unit, or within the body of any of its
4009 -- descendant library units, no part of the type of a component
4010 -- declared in a variant_part of the unchecked union type shall be of
4011 -- a formal private type or formal private extension declared within
4012 -- the formal part of the generic unit.
4014 elsif Ada_Version >= Ada_2012
4015 and then In_Generic_Body (UU_Typ)
4016 and then In_Variant_Part
4017 and then Is_Private_Type (Typ)
4018 and then Is_Generic_Type (Typ)
4019 then
4020 Error_Msg_N
4021 ("component of unchecked union cannot be of generic type", Comp);
4023 elsif Needs_Finalization (Typ) then
4024 Error_Msg_N
4025 ("component of unchecked union cannot be controlled", Comp);
4027 elsif Has_Task (Typ) then
4028 Error_Msg_N
4029 ("component of unchecked union cannot have tasks", Comp);
4030 end if;
4031 end Check_Component;
4033 -----------------------------
4034 -- Check_Declaration_Order --
4035 -----------------------------
4037 procedure Check_Declaration_Order (First : Node_Id; Second : Node_Id) is
4038 procedure Check_Aspect_Specification_Order;
4039 -- Inspect the aspect specifications of the context to determine the
4040 -- proper order.
4042 --------------------------------------
4043 -- Check_Aspect_Specification_Order --
4044 --------------------------------------
4046 procedure Check_Aspect_Specification_Order is
4047 Asp_First : constant Node_Id := Corresponding_Aspect (First);
4048 Asp_Second : constant Node_Id := Corresponding_Aspect (Second);
4049 Asp : Node_Id;
4051 begin
4052 -- Both aspects must be part of the same aspect specification list
4054 pragma Assert
4055 (List_Containing (Asp_First) = List_Containing (Asp_Second));
4057 -- Try to reach Second starting from First in a left to right
4058 -- traversal of the aspect specifications.
4060 Asp := Next (Asp_First);
4061 while Present (Asp) loop
4063 -- The order is ok, First is followed by Second
4065 if Asp = Asp_Second then
4066 return;
4067 end if;
4069 Next (Asp);
4070 end loop;
4072 -- If we get here, then the aspects are out of order
4074 SPARK_Msg_N ("aspect % cannot come after aspect %", First);
4075 end Check_Aspect_Specification_Order;
4077 -- Local variables
4079 Stmt : Node_Id;
4081 -- Start of processing for Check_Declaration_Order
4083 begin
4084 -- Cannot check the order if one of the pragmas is missing
4086 if No (First) or else No (Second) then
4087 return;
4088 end if;
4090 -- Set up the error names in case the order is incorrect
4092 Error_Msg_Name_1 := Pragma_Name (First);
4093 Error_Msg_Name_2 := Pragma_Name (Second);
4095 if From_Aspect_Specification (First) then
4097 -- Both pragmas are actually aspects, check their declaration
4098 -- order in the associated aspect specification list. Otherwise
4099 -- First is an aspect and Second a source pragma.
4101 if From_Aspect_Specification (Second) then
4102 Check_Aspect_Specification_Order;
4103 end if;
4105 -- Abstract_States is a source pragma
4107 else
4108 if From_Aspect_Specification (Second) then
4109 SPARK_Msg_N ("pragma % cannot come after aspect %", First);
4111 -- Both pragmas are source constructs. Try to reach First from
4112 -- Second by traversing the declarations backwards.
4114 else
4115 Stmt := Prev (Second);
4116 while Present (Stmt) loop
4118 -- The order is ok, First is followed by Second
4120 if Stmt = First then
4121 return;
4122 end if;
4124 Prev (Stmt);
4125 end loop;
4127 -- If we get here, then the pragmas are out of order
4129 SPARK_Msg_N ("pragma % cannot come after pragma %", First);
4130 end if;
4131 end if;
4132 end Check_Declaration_Order;
4134 ----------------------------
4135 -- Check_Duplicate_Pragma --
4136 ----------------------------
4138 procedure Check_Duplicate_Pragma (E : Entity_Id) is
4139 Id : Entity_Id := E;
4140 P : Node_Id;
4142 begin
4143 -- Nothing to do if this pragma comes from an aspect specification,
4144 -- since we could not be duplicating a pragma, and we dealt with the
4145 -- case of duplicated aspects in Analyze_Aspect_Specifications.
4147 if From_Aspect_Specification (N) then
4148 return;
4149 end if;
4151 -- Otherwise current pragma may duplicate previous pragma or a
4152 -- previously given aspect specification or attribute definition
4153 -- clause for the same pragma.
4155 P := Get_Rep_Item (E, Pragma_Name (N), Check_Parents => False);
4157 if Present (P) then
4159 -- If the entity is a type, then we have to make sure that the
4160 -- ostensible duplicate is not for a parent type from which this
4161 -- type is derived.
4163 if Is_Type (E) then
4164 if Nkind (P) = N_Pragma then
4165 declare
4166 Args : constant List_Id :=
4167 Pragma_Argument_Associations (P);
4168 begin
4169 if Present (Args)
4170 and then Is_Entity_Name (Expression (First (Args)))
4171 and then Is_Type (Entity (Expression (First (Args))))
4172 and then Entity (Expression (First (Args))) /= E
4173 then
4174 return;
4175 end if;
4176 end;
4178 elsif Nkind (P) = N_Aspect_Specification
4179 and then Is_Type (Entity (P))
4180 and then Entity (P) /= E
4181 then
4182 return;
4183 end if;
4184 end if;
4186 -- Here we have a definite duplicate
4188 Error_Msg_Name_1 := Pragma_Name (N);
4189 Error_Msg_Sloc := Sloc (P);
4191 -- For a single protected or a single task object, the error is
4192 -- issued on the original entity.
4194 if Ekind_In (Id, E_Task_Type, E_Protected_Type) then
4195 Id := Defining_Identifier (Original_Node (Parent (Id)));
4196 end if;
4198 if Nkind (P) = N_Aspect_Specification
4199 or else From_Aspect_Specification (P)
4200 then
4201 Error_Msg_NE ("aspect% for & previously given#", N, Id);
4202 else
4203 Error_Msg_NE ("pragma% for & duplicates pragma#", N, Id);
4204 end if;
4206 raise Pragma_Exit;
4207 end if;
4208 end Check_Duplicate_Pragma;
4210 ----------------------------------
4211 -- Check_Duplicated_Export_Name --
4212 ----------------------------------
4214 procedure Check_Duplicated_Export_Name (Nam : Node_Id) is
4215 String_Val : constant String_Id := Strval (Nam);
4217 begin
4218 -- We are only interested in the export case, and in the case of
4219 -- generics, it is the instance, not the template, that is the
4220 -- problem (the template will generate a warning in any case).
4222 if not Inside_A_Generic
4223 and then (Prag_Id = Pragma_Export
4224 or else
4225 Prag_Id = Pragma_Export_Procedure
4226 or else
4227 Prag_Id = Pragma_Export_Valued_Procedure
4228 or else
4229 Prag_Id = Pragma_Export_Function)
4230 then
4231 for J in Externals.First .. Externals.Last loop
4232 if String_Equal (String_Val, Strval (Externals.Table (J))) then
4233 Error_Msg_Sloc := Sloc (Externals.Table (J));
4234 Error_Msg_N ("external name duplicates name given#", Nam);
4235 exit;
4236 end if;
4237 end loop;
4239 Externals.Append (Nam);
4240 end if;
4241 end Check_Duplicated_Export_Name;
4243 ----------------------------------------
4244 -- Check_Expr_Is_OK_Static_Expression --
4245 ----------------------------------------
4247 procedure Check_Expr_Is_OK_Static_Expression
4248 (Expr : Node_Id;
4249 Typ : Entity_Id := Empty)
4251 begin
4252 if Present (Typ) then
4253 Analyze_And_Resolve (Expr, Typ);
4254 else
4255 Analyze_And_Resolve (Expr);
4256 end if;
4258 if Is_OK_Static_Expression (Expr) then
4259 return;
4261 elsif Etype (Expr) = Any_Type then
4262 raise Pragma_Exit;
4264 -- An interesting special case, if we have a string literal and we
4265 -- are in Ada 83 mode, then we allow it even though it will not be
4266 -- flagged as static. This allows the use of Ada 95 pragmas like
4267 -- Import in Ada 83 mode. They will of course be flagged with
4268 -- warnings as usual, but will not cause errors.
4270 elsif Ada_Version = Ada_83
4271 and then Nkind (Expr) = N_String_Literal
4272 then
4273 return;
4275 -- Static expression that raises Constraint_Error. This has already
4276 -- been flagged, so just exit from pragma processing.
4278 elsif Is_OK_Static_Expression (Expr) then
4279 raise Pragma_Exit;
4281 -- Finally, we have a real error
4283 else
4284 Error_Msg_Name_1 := Pname;
4285 Flag_Non_Static_Expr
4286 (Fix_Error ("argument for pragma% must be a static expression!"),
4287 Expr);
4288 raise Pragma_Exit;
4289 end if;
4290 end Check_Expr_Is_OK_Static_Expression;
4292 -------------------------
4293 -- Check_First_Subtype --
4294 -------------------------
4296 procedure Check_First_Subtype (Arg : Node_Id) is
4297 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
4298 Ent : constant Entity_Id := Entity (Argx);
4300 begin
4301 if Is_First_Subtype (Ent) then
4302 null;
4304 elsif Is_Type (Ent) then
4305 Error_Pragma_Arg
4306 ("pragma% cannot apply to subtype", Argx);
4308 elsif Is_Object (Ent) then
4309 Error_Pragma_Arg
4310 ("pragma% cannot apply to object, requires a type", Argx);
4312 else
4313 Error_Pragma_Arg
4314 ("pragma% cannot apply to&, requires a type", Argx);
4315 end if;
4316 end Check_First_Subtype;
4318 ----------------------
4319 -- Check_Identifier --
4320 ----------------------
4322 procedure Check_Identifier (Arg : Node_Id; Id : Name_Id) is
4323 begin
4324 if Present (Arg)
4325 and then Nkind (Arg) = N_Pragma_Argument_Association
4326 then
4327 if Chars (Arg) = No_Name or else Chars (Arg) /= Id then
4328 Error_Msg_Name_1 := Pname;
4329 Error_Msg_Name_2 := Id;
4330 Error_Msg_N ("pragma% argument expects identifier%", Arg);
4331 raise Pragma_Exit;
4332 end if;
4333 end if;
4334 end Check_Identifier;
4336 --------------------------------
4337 -- Check_Identifier_Is_One_Of --
4338 --------------------------------
4340 procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
4341 begin
4342 if Present (Arg)
4343 and then Nkind (Arg) = N_Pragma_Argument_Association
4344 then
4345 if Chars (Arg) = No_Name then
4346 Error_Msg_Name_1 := Pname;
4347 Error_Msg_N ("pragma% argument expects an identifier", Arg);
4348 raise Pragma_Exit;
4350 elsif Chars (Arg) /= N1
4351 and then Chars (Arg) /= N2
4352 then
4353 Error_Msg_Name_1 := Pname;
4354 Error_Msg_N ("invalid identifier for pragma% argument", Arg);
4355 raise Pragma_Exit;
4356 end if;
4357 end if;
4358 end Check_Identifier_Is_One_Of;
4360 ---------------------------
4361 -- Check_In_Main_Program --
4362 ---------------------------
4364 procedure Check_In_Main_Program is
4365 P : constant Node_Id := Parent (N);
4367 begin
4368 -- Must be at in subprogram body
4370 if Nkind (P) /= N_Subprogram_Body then
4371 Error_Pragma ("% pragma allowed only in subprogram");
4373 -- Otherwise warn if obviously not main program
4375 elsif Present (Parameter_Specifications (Specification (P)))
4376 or else not Is_Compilation_Unit (Defining_Entity (P))
4377 then
4378 Error_Msg_Name_1 := Pname;
4379 Error_Msg_N
4380 ("??pragma% is only effective in main program", N);
4381 end if;
4382 end Check_In_Main_Program;
4384 ---------------------------------------
4385 -- Check_Interrupt_Or_Attach_Handler --
4386 ---------------------------------------
4388 procedure Check_Interrupt_Or_Attach_Handler is
4389 Arg1_X : constant Node_Id := Get_Pragma_Arg (Arg1);
4390 Handler_Proc, Proc_Scope : Entity_Id;
4392 begin
4393 Analyze (Arg1_X);
4395 if Prag_Id = Pragma_Interrupt_Handler then
4396 Check_Restriction (No_Dynamic_Attachment, N);
4397 end if;
4399 Handler_Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
4400 Proc_Scope := Scope (Handler_Proc);
4402 -- On AAMP only, a pragma Interrupt_Handler is supported for
4403 -- nonprotected parameterless procedures.
4405 if not AAMP_On_Target
4406 or else Prag_Id = Pragma_Attach_Handler
4407 then
4408 if Ekind (Proc_Scope) /= E_Protected_Type then
4409 Error_Pragma_Arg
4410 ("argument of pragma% must be protected procedure", Arg1);
4411 end if;
4413 -- For pragma case (as opposed to access case), check placement.
4414 -- We don't need to do that for aspects, because we have the
4415 -- check that they aspect applies an appropriate procedure.
4417 if not From_Aspect_Specification (N)
4418 and then Parent (N) /= Protected_Definition (Parent (Proc_Scope))
4419 then
4420 Error_Pragma ("pragma% must be in protected definition");
4421 end if;
4422 end if;
4424 if not Is_Library_Level_Entity (Proc_Scope)
4425 or else (AAMP_On_Target
4426 and then not Is_Library_Level_Entity (Handler_Proc))
4427 then
4428 Error_Pragma_Arg
4429 ("argument for pragma% must be library level entity", Arg1);
4430 end if;
4432 -- AI05-0033: A pragma cannot appear within a generic body, because
4433 -- instance can be in a nested scope. The check that protected type
4434 -- is itself a library-level declaration is done elsewhere.
4436 -- Note: we omit this check in Relaxed_RM_Semantics mode to properly
4437 -- handle code prior to AI-0033. Analysis tools typically are not
4438 -- interested in this pragma in any case, so no need to worry too
4439 -- much about its placement.
4441 if Inside_A_Generic then
4442 if Ekind (Scope (Current_Scope)) = E_Generic_Package
4443 and then In_Package_Body (Scope (Current_Scope))
4444 and then not Relaxed_RM_Semantics
4445 then
4446 Error_Pragma ("pragma% cannot be used inside a generic");
4447 end if;
4448 end if;
4449 end Check_Interrupt_Or_Attach_Handler;
4451 ---------------------------------
4452 -- Check_Loop_Pragma_Placement --
4453 ---------------------------------
4455 procedure Check_Loop_Pragma_Placement is
4456 procedure Check_Loop_Pragma_Grouping (Loop_Stmt : Node_Id);
4457 -- Verify whether the current pragma is properly grouped with other
4458 -- pragma Loop_Invariant and/or Loop_Variant. Node Loop_Stmt is the
4459 -- related loop where the pragma appears.
4461 function Is_Loop_Pragma (Stmt : Node_Id) return Boolean;
4462 -- Determine whether an arbitrary statement Stmt denotes pragma
4463 -- Loop_Invariant or Loop_Variant.
4465 procedure Placement_Error (Constr : Node_Id);
4466 pragma No_Return (Placement_Error);
4467 -- Node Constr denotes the last loop restricted construct before we
4468 -- encountered an illegal relation between enclosing constructs. Emit
4469 -- an error depending on what Constr was.
4471 --------------------------------
4472 -- Check_Loop_Pragma_Grouping --
4473 --------------------------------
4475 procedure Check_Loop_Pragma_Grouping (Loop_Stmt : Node_Id) is
4476 Stop_Search : exception;
4477 -- This exception is used to terminate the recursive descent of
4478 -- routine Check_Grouping.
4480 procedure Check_Grouping (L : List_Id);
4481 -- Find the first group of pragmas in list L and if successful,
4482 -- ensure that the current pragma is part of that group. The
4483 -- routine raises Stop_Search once such a check is performed to
4484 -- halt the recursive descent.
4486 procedure Grouping_Error (Prag : Node_Id);
4487 pragma No_Return (Grouping_Error);
4488 -- Emit an error concerning the current pragma indicating that it
4489 -- should be placed after pragma Prag.
4491 --------------------
4492 -- Check_Grouping --
4493 --------------------
4495 procedure Check_Grouping (L : List_Id) is
4496 HSS : Node_Id;
4497 Prag : Node_Id;
4498 Stmt : Node_Id;
4500 begin
4501 -- Inspect the list of declarations or statements looking for
4502 -- the first grouping of pragmas:
4504 -- loop
4505 -- pragma Loop_Invariant ...;
4506 -- pragma Loop_Variant ...;
4507 -- . . . -- (1)
4508 -- pragma Loop_Variant ...; -- current pragma
4510 -- If the current pragma is not in the grouping, then it must
4511 -- either appear in a different declarative or statement list
4512 -- or the construct at (1) is separating the pragma from the
4513 -- grouping.
4515 Stmt := First (L);
4516 while Present (Stmt) loop
4518 -- Pragmas Loop_Invariant and Loop_Variant may only appear
4519 -- inside a loop or a block housed inside a loop. Inspect
4520 -- the declarations and statements of the block as they may
4521 -- contain the first grouping.
4523 if Nkind (Stmt) = N_Block_Statement then
4524 HSS := Handled_Statement_Sequence (Stmt);
4526 Check_Grouping (Declarations (Stmt));
4528 if Present (HSS) then
4529 Check_Grouping (Statements (HSS));
4530 end if;
4532 -- First pragma of the first topmost grouping has been found
4534 elsif Is_Loop_Pragma (Stmt) then
4536 -- The group and the current pragma are not in the same
4537 -- declarative or statement list.
4539 if List_Containing (Stmt) /= List_Containing (N) then
4540 Grouping_Error (Stmt);
4542 -- Try to reach the current pragma from the first pragma
4543 -- of the grouping while skipping other members:
4545 -- pragma Loop_Invariant ...; -- first pragma
4546 -- pragma Loop_Variant ...; -- member
4547 -- . . .
4548 -- pragma Loop_Variant ...; -- current pragma
4550 else
4551 while Present (Stmt) loop
4553 -- The current pragma is either the first pragma
4554 -- of the group or is a member of the group. Stop
4555 -- the search as the placement is legal.
4557 if Stmt = N then
4558 raise Stop_Search;
4560 -- Skip group members, but keep track of the last
4561 -- pragma in the group.
4563 elsif Is_Loop_Pragma (Stmt) then
4564 Prag := Stmt;
4566 -- A non-pragma is separating the group from the
4567 -- current pragma, the placement is illegal.
4569 else
4570 Grouping_Error (Prag);
4571 end if;
4573 Next (Stmt);
4574 end loop;
4576 -- If the traversal did not reach the current pragma,
4577 -- then the list must be malformed.
4579 raise Program_Error;
4580 end if;
4581 end if;
4583 Next (Stmt);
4584 end loop;
4585 end Check_Grouping;
4587 --------------------
4588 -- Grouping_Error --
4589 --------------------
4591 procedure Grouping_Error (Prag : Node_Id) is
4592 begin
4593 Error_Msg_Sloc := Sloc (Prag);
4594 Error_Pragma ("pragma% must appear next to pragma#");
4595 end Grouping_Error;
4597 -- Start of processing for Check_Loop_Pragma_Grouping
4599 begin
4600 -- Inspect the statements of the loop or nested blocks housed
4601 -- within to determine whether the current pragma is part of the
4602 -- first topmost grouping of Loop_Invariant and Loop_Variant.
4604 Check_Grouping (Statements (Loop_Stmt));
4606 exception
4607 when Stop_Search => null;
4608 end Check_Loop_Pragma_Grouping;
4610 --------------------
4611 -- Is_Loop_Pragma --
4612 --------------------
4614 function Is_Loop_Pragma (Stmt : Node_Id) return Boolean is
4615 begin
4616 -- Inspect the original node as Loop_Invariant and Loop_Variant
4617 -- pragmas are rewritten to null when assertions are disabled.
4619 if Nkind (Original_Node (Stmt)) = N_Pragma then
4620 return
4621 Nam_In (Pragma_Name (Original_Node (Stmt)),
4622 Name_Loop_Invariant,
4623 Name_Loop_Variant);
4624 else
4625 return False;
4626 end if;
4627 end Is_Loop_Pragma;
4629 ---------------------
4630 -- Placement_Error --
4631 ---------------------
4633 procedure Placement_Error (Constr : Node_Id) is
4634 LA : constant String := " with Loop_Entry";
4636 begin
4637 if Prag_Id = Pragma_Assert then
4638 Error_Msg_String (1 .. LA'Length) := LA;
4639 Error_Msg_Strlen := LA'Length;
4640 else
4641 Error_Msg_Strlen := 0;
4642 end if;
4644 if Nkind (Constr) = N_Pragma then
4645 Error_Pragma
4646 ("pragma %~ must appear immediately within the statements "
4647 & "of a loop");
4648 else
4649 Error_Pragma_Arg
4650 ("block containing pragma %~ must appear immediately within "
4651 & "the statements of a loop", Constr);
4652 end if;
4653 end Placement_Error;
4655 -- Local declarations
4657 Prev : Node_Id;
4658 Stmt : Node_Id;
4660 -- Start of processing for Check_Loop_Pragma_Placement
4662 begin
4663 -- Check that pragma appears immediately within a loop statement,
4664 -- ignoring intervening block statements.
4666 Prev := N;
4667 Stmt := Parent (N);
4668 while Present (Stmt) loop
4670 -- The pragma or previous block must appear immediately within the
4671 -- current block's declarative or statement part.
4673 if Nkind (Stmt) = N_Block_Statement then
4674 if (No (Declarations (Stmt))
4675 or else List_Containing (Prev) /= Declarations (Stmt))
4676 and then
4677 List_Containing (Prev) /=
4678 Statements (Handled_Statement_Sequence (Stmt))
4679 then
4680 Placement_Error (Prev);
4681 return;
4683 -- Keep inspecting the parents because we are now within a
4684 -- chain of nested blocks.
4686 else
4687 Prev := Stmt;
4688 Stmt := Parent (Stmt);
4689 end if;
4691 -- The pragma or previous block must appear immediately within the
4692 -- statements of the loop.
4694 elsif Nkind (Stmt) = N_Loop_Statement then
4695 if List_Containing (Prev) /= Statements (Stmt) then
4696 Placement_Error (Prev);
4697 end if;
4699 -- Stop the traversal because we reached the innermost loop
4700 -- regardless of whether we encountered an error or not.
4702 exit;
4704 -- Ignore a handled statement sequence. Note that this node may
4705 -- be related to a subprogram body in which case we will emit an
4706 -- error on the next iteration of the search.
4708 elsif Nkind (Stmt) = N_Handled_Sequence_Of_Statements then
4709 Stmt := Parent (Stmt);
4711 -- Any other statement breaks the chain from the pragma to the
4712 -- loop.
4714 else
4715 Placement_Error (Prev);
4716 return;
4717 end if;
4718 end loop;
4720 -- Check that the current pragma Loop_Invariant or Loop_Variant is
4721 -- grouped together with other such pragmas.
4723 if Is_Loop_Pragma (N) then
4725 -- The previous check should have located the related loop
4727 pragma Assert (Nkind (Stmt) = N_Loop_Statement);
4728 Check_Loop_Pragma_Grouping (Stmt);
4729 end if;
4730 end Check_Loop_Pragma_Placement;
4732 -------------------------------------------
4733 -- Check_Is_In_Decl_Part_Or_Package_Spec --
4734 -------------------------------------------
4736 procedure Check_Is_In_Decl_Part_Or_Package_Spec is
4737 P : Node_Id;
4739 begin
4740 P := Parent (N);
4741 loop
4742 if No (P) then
4743 exit;
4745 elsif Nkind (P) = N_Handled_Sequence_Of_Statements then
4746 exit;
4748 elsif Nkind_In (P, N_Package_Specification,
4749 N_Block_Statement)
4750 then
4751 return;
4753 -- Note: the following tests seem a little peculiar, because
4754 -- they test for bodies, but if we were in the statement part
4755 -- of the body, we would already have hit the handled statement
4756 -- sequence, so the only way we get here is by being in the
4757 -- declarative part of the body.
4759 elsif Nkind_In (P, N_Subprogram_Body,
4760 N_Package_Body,
4761 N_Task_Body,
4762 N_Entry_Body)
4763 then
4764 return;
4765 end if;
4767 P := Parent (P);
4768 end loop;
4770 Error_Pragma ("pragma% is not in declarative part or package spec");
4771 end Check_Is_In_Decl_Part_Or_Package_Spec;
4773 -------------------------
4774 -- Check_No_Identifier --
4775 -------------------------
4777 procedure Check_No_Identifier (Arg : Node_Id) is
4778 begin
4779 if Nkind (Arg) = N_Pragma_Argument_Association
4780 and then Chars (Arg) /= No_Name
4781 then
4782 Error_Pragma_Arg_Ident
4783 ("pragma% does not permit identifier& here", Arg);
4784 end if;
4785 end Check_No_Identifier;
4787 --------------------------
4788 -- Check_No_Identifiers --
4789 --------------------------
4791 procedure Check_No_Identifiers is
4792 Arg_Node : Node_Id;
4793 begin
4794 Arg_Node := Arg1;
4795 for J in 1 .. Arg_Count loop
4796 Check_No_Identifier (Arg_Node);
4797 Next (Arg_Node);
4798 end loop;
4799 end Check_No_Identifiers;
4801 ------------------------
4802 -- Check_No_Link_Name --
4803 ------------------------
4805 procedure Check_No_Link_Name is
4806 begin
4807 if Present (Arg3) and then Chars (Arg3) = Name_Link_Name then
4808 Arg4 := Arg3;
4809 end if;
4811 if Present (Arg4) then
4812 Error_Pragma_Arg
4813 ("Link_Name argument not allowed for Import Intrinsic", Arg4);
4814 end if;
4815 end Check_No_Link_Name;
4817 -------------------------------
4818 -- Check_Optional_Identifier --
4819 -------------------------------
4821 procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id) is
4822 begin
4823 if Present (Arg)
4824 and then Nkind (Arg) = N_Pragma_Argument_Association
4825 and then Chars (Arg) /= No_Name
4826 then
4827 if Chars (Arg) /= Id then
4828 Error_Msg_Name_1 := Pname;
4829 Error_Msg_Name_2 := Id;
4830 Error_Msg_N ("pragma% argument expects identifier%", Arg);
4831 raise Pragma_Exit;
4832 end if;
4833 end if;
4834 end Check_Optional_Identifier;
4836 procedure Check_Optional_Identifier (Arg : Node_Id; Id : String) is
4837 begin
4838 Name_Buffer (1 .. Id'Length) := Id;
4839 Name_Len := Id'Length;
4840 Check_Optional_Identifier (Arg, Name_Find);
4841 end Check_Optional_Identifier;
4843 --------------------
4844 -- Check_Pre_Post --
4845 --------------------
4847 procedure Check_Pre_Post is
4848 P : Node_Id;
4849 PO : Node_Id;
4851 begin
4852 if not Is_List_Member (N) then
4853 Pragma_Misplaced;
4854 end if;
4856 -- If we are within an inlined body, the legality of the pragma
4857 -- has been checked already.
4859 if In_Inlined_Body then
4860 return;
4861 end if;
4863 -- Search prior declarations
4865 P := N;
4866 while Present (Prev (P)) loop
4867 P := Prev (P);
4869 -- If the previous node is a generic subprogram, do not go to to
4870 -- the original node, which is the unanalyzed tree: we need to
4871 -- attach the pre/postconditions to the analyzed version at this
4872 -- point. They get propagated to the original tree when analyzing
4873 -- the corresponding body.
4875 if Nkind (P) not in N_Generic_Declaration then
4876 PO := Original_Node (P);
4877 else
4878 PO := P;
4879 end if;
4881 -- Skip past prior pragma
4883 if Nkind (PO) = N_Pragma then
4884 null;
4886 -- Skip stuff not coming from source
4888 elsif not Comes_From_Source (PO) then
4890 -- The condition may apply to a subprogram instantiation
4892 if Nkind (PO) = N_Subprogram_Declaration
4893 and then Present (Generic_Parent (Specification (PO)))
4894 then
4895 return;
4897 elsif Nkind (PO) = N_Subprogram_Declaration
4898 and then In_Instance
4899 then
4900 return;
4902 -- For all other cases of non source code, do nothing
4904 else
4905 null;
4906 end if;
4908 -- Only remaining possibility is subprogram declaration
4910 else
4911 return;
4912 end if;
4913 end loop;
4915 -- If we fall through loop, pragma is at start of list, so see if it
4916 -- is at the start of declarations of a subprogram body.
4918 PO := Parent (N);
4920 if Nkind (PO) = N_Subprogram_Body
4921 and then List_Containing (N) = Declarations (PO)
4922 then
4923 -- This is only allowed if there is no separate specification
4925 if Present (Corresponding_Spec (PO)) then
4926 Error_Pragma
4927 ("pragma% must apply to subprogram specification");
4928 end if;
4930 return;
4931 end if;
4932 end Check_Pre_Post;
4934 --------------------------------------
4935 -- Check_Precondition_Postcondition --
4936 --------------------------------------
4938 procedure Check_Precondition_Postcondition (In_Body : out Boolean) is
4939 P : Node_Id;
4940 PO : Node_Id;
4942 procedure Chain_PPC (PO : Node_Id);
4943 -- If PO is an entry or a [generic] subprogram declaration node, then
4944 -- the precondition/postcondition applies to this subprogram and the
4945 -- processing for the pragma is completed. Otherwise the pragma is
4946 -- misplaced.
4948 ---------------
4949 -- Chain_PPC --
4950 ---------------
4952 procedure Chain_PPC (PO : Node_Id) is
4953 S : Entity_Id;
4955 begin
4956 if Nkind (PO) = N_Abstract_Subprogram_Declaration then
4957 if not From_Aspect_Specification (N) then
4958 Error_Pragma
4959 ("pragma% cannot be applied to abstract subprogram");
4961 elsif Class_Present (N) then
4962 null;
4964 else
4965 Error_Pragma
4966 ("aspect % requires ''Class for abstract subprogram");
4967 end if;
4969 -- AI05-0230: The same restriction applies to null procedures. For
4970 -- compatibility with earlier uses of the Ada pragma, apply this
4971 -- rule only to aspect specifications.
4973 -- The above discrepency needs documentation. Robert is dubious
4974 -- about whether it is a good idea ???
4976 elsif Nkind (PO) = N_Subprogram_Declaration
4977 and then Nkind (Specification (PO)) = N_Procedure_Specification
4978 and then Null_Present (Specification (PO))
4979 and then From_Aspect_Specification (N)
4980 and then not Class_Present (N)
4981 then
4982 Error_Pragma
4983 ("aspect % requires ''Class for null procedure");
4985 -- Pre/postconditions are legal on a subprogram body if it is not
4986 -- a completion of a declaration. They are also legal on a stub
4987 -- with no previous declarations (this is checked when processing
4988 -- the corresponding aspects).
4990 elsif Nkind (PO) = N_Subprogram_Body
4991 and then Acts_As_Spec (PO)
4992 then
4993 null;
4995 elsif Nkind (PO) = N_Subprogram_Body_Stub then
4996 null;
4998 elsif not Nkind_In (PO, N_Subprogram_Declaration,
4999 N_Expression_Function,
5000 N_Generic_Subprogram_Declaration,
5001 N_Entry_Declaration)
5002 then
5003 Pragma_Misplaced;
5004 end if;
5006 -- Here if we have [generic] subprogram or entry declaration
5008 if Nkind (PO) = N_Entry_Declaration then
5009 S := Defining_Entity (PO);
5010 else
5011 S := Defining_Unit_Name (Specification (PO));
5013 if Nkind (S) = N_Defining_Program_Unit_Name then
5014 S := Defining_Identifier (S);
5015 end if;
5016 end if;
5018 -- Note: we do not analyze the pragma at this point. Instead we
5019 -- delay this analysis until the end of the declarative part in
5020 -- which the pragma appears. This implements the required delay
5021 -- in this analysis, allowing forward references. The analysis
5022 -- happens at the end of Analyze_Declarations.
5024 -- Chain spec PPC pragma to list for subprogram
5026 Add_Contract_Item (N, S);
5028 -- Return indicating spec case
5030 In_Body := False;
5031 return;
5032 end Chain_PPC;
5034 -- Start of processing for Check_Precondition_Postcondition
5036 begin
5037 if not Is_List_Member (N) then
5038 Pragma_Misplaced;
5039 end if;
5041 -- Preanalyze message argument if present. Visibility in this
5042 -- argument is established at the point of pragma occurrence.
5044 if Arg_Count = 2 then
5045 Check_Optional_Identifier (Arg2, Name_Message);
5046 Preanalyze_Spec_Expression
5047 (Get_Pragma_Arg (Arg2), Standard_String);
5048 end if;
5050 -- For a pragma PPC in the extended main source unit, record enabled
5051 -- status in SCO.
5053 if Is_Checked (N) and then not Split_PPC (N) then
5054 Set_SCO_Pragma_Enabled (Loc);
5055 end if;
5057 -- If we are within an inlined body, the legality of the pragma
5058 -- has been checked already.
5060 if In_Inlined_Body then
5061 In_Body := True;
5062 return;
5063 end if;
5065 -- Search prior declarations
5067 P := N;
5068 while Present (Prev (P)) loop
5069 P := Prev (P);
5071 -- If the previous node is a generic subprogram, do not go to to
5072 -- the original node, which is the unanalyzed tree: we need to
5073 -- attach the pre/postconditions to the analyzed version at this
5074 -- point. They get propagated to the original tree when analyzing
5075 -- the corresponding body.
5077 if Nkind (P) not in N_Generic_Declaration then
5078 PO := Original_Node (P);
5079 else
5080 PO := P;
5081 end if;
5083 -- Skip past prior pragma
5085 if Nkind (PO) = N_Pragma then
5086 null;
5088 -- Skip stuff not coming from source
5090 elsif not Comes_From_Source (PO) then
5092 -- The condition may apply to a subprogram instantiation
5094 if Nkind (PO) = N_Subprogram_Declaration
5095 and then Present (Generic_Parent (Specification (PO)))
5096 then
5097 Chain_PPC (PO);
5098 return;
5100 elsif Nkind (PO) = N_Subprogram_Declaration
5101 and then In_Instance
5102 then
5103 Chain_PPC (PO);
5104 return;
5106 -- For all other cases of non source code, do nothing
5108 else
5109 null;
5110 end if;
5112 -- Only remaining possibility is subprogram declaration
5114 else
5115 Chain_PPC (PO);
5116 return;
5117 end if;
5118 end loop;
5120 -- If we fall through loop, pragma is at start of list, so see if it
5121 -- is at the start of declarations of a subprogram body.
5123 PO := Parent (N);
5125 if Nkind (PO) = N_Subprogram_Body
5126 and then List_Containing (N) = Declarations (PO)
5127 then
5128 if Operating_Mode /= Generate_Code or else Inside_A_Generic then
5130 -- Analyze pragma expression for correctness and for ASIS use
5132 Preanalyze_Assert_Expression
5133 (Get_Pragma_Arg (Arg1), Standard_Boolean);
5135 -- In ASIS mode, for a pragma generated from a source aspect,
5136 -- also analyze the original aspect expression.
5138 if ASIS_Mode and then Present (Corresponding_Aspect (N)) then
5139 Preanalyze_Assert_Expression
5140 (Expression (Corresponding_Aspect (N)), Standard_Boolean);
5141 end if;
5142 end if;
5144 -- Retain copy of the pre/postcondition pragma in GNATprove mode.
5145 -- The copy is needed because the pragma is expanded into other
5146 -- constructs which are not acceptable in the N_Contract node.
5148 if Acts_As_Spec (PO) and then GNATprove_Mode then
5149 declare
5150 Prag : constant Node_Id := New_Copy_Tree (N);
5152 begin
5153 -- Preanalyze the pragma
5155 Preanalyze_Assert_Expression
5156 (Get_Pragma_Arg
5157 (First (Pragma_Argument_Associations (Prag))),
5158 Standard_Boolean);
5160 -- Preanalyze the corresponding aspect (if any)
5162 if Present (Corresponding_Aspect (Prag)) then
5163 Preanalyze_Assert_Expression
5164 (Expression (Corresponding_Aspect (Prag)),
5165 Standard_Boolean);
5166 end if;
5168 -- Chain the copy on the contract of the body
5170 Add_Contract_Item
5171 (Prag, Defining_Unit_Name (Specification (PO)));
5172 end;
5173 end if;
5175 In_Body := True;
5176 return;
5178 -- See if it is in the pragmas after a library level subprogram
5180 elsif Nkind (PO) = N_Compilation_Unit_Aux then
5182 -- In GNATprove mode, analyze pragma expression for correctness,
5183 -- as it is not expanded later. Ditto in ASIS_Mode where there is
5184 -- no later point at which the aspect will be analyzed.
5186 if GNATprove_Mode or ASIS_Mode then
5187 Analyze_Pre_Post_Condition_In_Decl_Part
5188 (N, Defining_Entity (Unit (Parent (PO))));
5189 end if;
5191 Chain_PPC (Unit (Parent (PO)));
5192 return;
5193 end if;
5195 -- If we fall through, pragma was misplaced
5197 Pragma_Misplaced;
5198 end Check_Precondition_Postcondition;
5200 -----------------------------
5201 -- Check_Static_Constraint --
5202 -----------------------------
5204 -- Note: for convenience in writing this procedure, in addition to
5205 -- the officially (i.e. by spec) allowed argument which is always a
5206 -- constraint, it also allows ranges and discriminant associations.
5207 -- Above is not clear ???
5209 procedure Check_Static_Constraint (Constr : Node_Id) is
5211 procedure Require_Static (E : Node_Id);
5212 -- Require given expression to be static expression
5214 --------------------
5215 -- Require_Static --
5216 --------------------
5218 procedure Require_Static (E : Node_Id) is
5219 begin
5220 if not Is_OK_Static_Expression (E) then
5221 Flag_Non_Static_Expr
5222 ("non-static constraint not allowed in Unchecked_Union!", E);
5223 raise Pragma_Exit;
5224 end if;
5225 end Require_Static;
5227 -- Start of processing for Check_Static_Constraint
5229 begin
5230 case Nkind (Constr) is
5231 when N_Discriminant_Association =>
5232 Require_Static (Expression (Constr));
5234 when N_Range =>
5235 Require_Static (Low_Bound (Constr));
5236 Require_Static (High_Bound (Constr));
5238 when N_Attribute_Reference =>
5239 Require_Static (Type_Low_Bound (Etype (Prefix (Constr))));
5240 Require_Static (Type_High_Bound (Etype (Prefix (Constr))));
5242 when N_Range_Constraint =>
5243 Check_Static_Constraint (Range_Expression (Constr));
5245 when N_Index_Or_Discriminant_Constraint =>
5246 declare
5247 IDC : Entity_Id;
5248 begin
5249 IDC := First (Constraints (Constr));
5250 while Present (IDC) loop
5251 Check_Static_Constraint (IDC);
5252 Next (IDC);
5253 end loop;
5254 end;
5256 when others =>
5257 null;
5258 end case;
5259 end Check_Static_Constraint;
5261 ---------------------
5262 -- Check_Test_Case --
5263 ---------------------
5265 procedure Check_Test_Case is
5266 P : Node_Id;
5267 PO : Node_Id;
5269 procedure Chain_CTC (PO : Node_Id);
5270 -- If PO is a [generic] subprogram declaration node, then the
5271 -- test-case applies to this subprogram and the processing for
5272 -- the pragma is completed. Otherwise the pragma is misplaced.
5274 ---------------
5275 -- Chain_CTC --
5276 ---------------
5278 procedure Chain_CTC (PO : Node_Id) is
5279 Name : constant String_Id := Get_Name_From_CTC_Pragma (N);
5280 CTC : Node_Id;
5281 S : Entity_Id;
5283 begin
5284 if Nkind (PO) = N_Abstract_Subprogram_Declaration then
5285 Error_Pragma
5286 ("pragma% cannot be applied to abstract subprogram");
5288 elsif Nkind (PO) = N_Entry_Declaration then
5289 Error_Pragma ("pragma% cannot be applied to entry");
5291 elsif not Nkind_In (PO, N_Subprogram_Declaration,
5292 N_Generic_Subprogram_Declaration)
5293 then
5294 Pragma_Misplaced;
5295 end if;
5297 -- Here if we have [generic] subprogram declaration
5299 S := Defining_Unit_Name (Specification (PO));
5301 -- Note: we do not analyze the pragma at this point. Instead we
5302 -- delay this analysis until the end of the declarative part in
5303 -- which the pragma appears. This implements the required delay
5304 -- in this analysis, allowing forward references. The analysis
5305 -- happens at the end of Analyze_Declarations.
5307 -- There should not be another test-case with the same name
5308 -- associated to this subprogram.
5310 CTC := Contract_Test_Cases (Contract (S));
5311 while Present (CTC) loop
5313 -- Omit pragma Contract_Cases because it does not introduce
5314 -- a unique case name and it does not follow the syntax of
5315 -- Test_Case.
5317 if Pragma_Name (CTC) = Name_Contract_Cases then
5318 null;
5320 elsif String_Equal (Name, Get_Name_From_CTC_Pragma (CTC)) then
5321 Error_Msg_Sloc := Sloc (CTC);
5322 Error_Pragma ("name for pragma% is already used#");
5323 end if;
5325 CTC := Next_Pragma (CTC);
5326 end loop;
5328 -- Chain spec CTC pragma to list for subprogram
5330 Add_Contract_Item (N, S);
5331 end Chain_CTC;
5333 -- Start of processing for Check_Test_Case
5335 begin
5336 -- First check pragma arguments
5338 Check_At_Least_N_Arguments (2);
5339 Check_At_Most_N_Arguments (4);
5340 Check_Arg_Order
5341 ((Name_Name, Name_Mode, Name_Requires, Name_Ensures));
5343 Check_Optional_Identifier (Arg1, Name_Name);
5344 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
5346 -- In ASIS mode, for a pragma generated from a source aspect, also
5347 -- analyze the original aspect expression.
5349 if ASIS_Mode and then Present (Corresponding_Aspect (N)) then
5350 Check_Expr_Is_OK_Static_Expression
5351 (Original_Node (Get_Pragma_Arg (Arg1)), Standard_String);
5352 end if;
5354 Check_Optional_Identifier (Arg2, Name_Mode);
5355 Check_Arg_Is_One_Of (Arg2, Name_Nominal, Name_Robustness);
5357 if Arg_Count = 4 then
5358 Check_Identifier (Arg3, Name_Requires);
5359 Check_Identifier (Arg4, Name_Ensures);
5361 elsif Arg_Count = 3 then
5362 Check_Identifier_Is_One_Of (Arg3, Name_Requires, Name_Ensures);
5363 end if;
5365 -- Check pragma placement
5367 if not Is_List_Member (N) then
5368 Pragma_Misplaced;
5369 end if;
5371 -- Test-case should only appear in package spec unit
5373 if Get_Source_Unit (N) = No_Unit
5374 or else not Nkind_In (Sinfo.Unit (Cunit (Current_Sem_Unit)),
5375 N_Package_Declaration,
5376 N_Generic_Package_Declaration)
5377 then
5378 Pragma_Misplaced;
5379 end if;
5381 -- Search prior declarations
5383 P := N;
5384 while Present (Prev (P)) loop
5385 P := Prev (P);
5387 -- If the previous node is a generic subprogram, do not go to to
5388 -- the original node, which is the unanalyzed tree: we need to
5389 -- attach the test-case to the analyzed version at this point.
5390 -- They get propagated to the original tree when analyzing the
5391 -- corresponding body.
5393 if Nkind (P) not in N_Generic_Declaration then
5394 PO := Original_Node (P);
5395 else
5396 PO := P;
5397 end if;
5399 -- Skip past prior pragma
5401 if Nkind (PO) = N_Pragma then
5402 null;
5404 -- Skip stuff not coming from source
5406 elsif not Comes_From_Source (PO) then
5407 null;
5409 -- Only remaining possibility is subprogram declaration. First
5410 -- check that it is declared directly in a package declaration.
5411 -- This may be either the package declaration for the current unit
5412 -- being defined or a local package declaration.
5414 elsif not Present (Parent (Parent (PO)))
5415 or else not Present (Parent (Parent (Parent (PO))))
5416 or else not Nkind_In (Parent (Parent (PO)),
5417 N_Package_Declaration,
5418 N_Generic_Package_Declaration)
5419 then
5420 Pragma_Misplaced;
5422 else
5423 Chain_CTC (PO);
5424 return;
5425 end if;
5426 end loop;
5428 -- If we fall through, pragma was misplaced
5430 Pragma_Misplaced;
5431 end Check_Test_Case;
5433 --------------------------------------
5434 -- Check_Valid_Configuration_Pragma --
5435 --------------------------------------
5437 -- A configuration pragma must appear in the context clause of a
5438 -- compilation unit, and only other pragmas may precede it. Note that
5439 -- the test also allows use in a configuration pragma file.
5441 procedure Check_Valid_Configuration_Pragma is
5442 begin
5443 if not Is_Configuration_Pragma then
5444 Error_Pragma ("incorrect placement for configuration pragma%");
5445 end if;
5446 end Check_Valid_Configuration_Pragma;
5448 -------------------------------------
5449 -- Check_Valid_Library_Unit_Pragma --
5450 -------------------------------------
5452 procedure Check_Valid_Library_Unit_Pragma is
5453 Plist : List_Id;
5454 Parent_Node : Node_Id;
5455 Unit_Name : Entity_Id;
5456 Unit_Kind : Node_Kind;
5457 Unit_Node : Node_Id;
5458 Sindex : Source_File_Index;
5460 begin
5461 if not Is_List_Member (N) then
5462 Pragma_Misplaced;
5464 else
5465 Plist := List_Containing (N);
5466 Parent_Node := Parent (Plist);
5468 if Parent_Node = Empty then
5469 Pragma_Misplaced;
5471 -- Case of pragma appearing after a compilation unit. In this case
5472 -- it must have an argument with the corresponding name and must
5473 -- be part of the following pragmas of its parent.
5475 elsif Nkind (Parent_Node) = N_Compilation_Unit_Aux then
5476 if Plist /= Pragmas_After (Parent_Node) then
5477 Pragma_Misplaced;
5479 elsif Arg_Count = 0 then
5480 Error_Pragma
5481 ("argument required if outside compilation unit");
5483 else
5484 Check_No_Identifiers;
5485 Check_Arg_Count (1);
5486 Unit_Node := Unit (Parent (Parent_Node));
5487 Unit_Kind := Nkind (Unit_Node);
5489 Analyze (Get_Pragma_Arg (Arg1));
5491 if Unit_Kind = N_Generic_Subprogram_Declaration
5492 or else Unit_Kind = N_Subprogram_Declaration
5493 then
5494 Unit_Name := Defining_Entity (Unit_Node);
5496 elsif Unit_Kind in N_Generic_Instantiation then
5497 Unit_Name := Defining_Entity (Unit_Node);
5499 else
5500 Unit_Name := Cunit_Entity (Current_Sem_Unit);
5501 end if;
5503 if Chars (Unit_Name) /=
5504 Chars (Entity (Get_Pragma_Arg (Arg1)))
5505 then
5506 Error_Pragma_Arg
5507 ("pragma% argument is not current unit name", Arg1);
5508 end if;
5510 if Ekind (Unit_Name) = E_Package
5511 and then Present (Renamed_Entity (Unit_Name))
5512 then
5513 Error_Pragma ("pragma% not allowed for renamed package");
5514 end if;
5515 end if;
5517 -- Pragma appears other than after a compilation unit
5519 else
5520 -- Here we check for the generic instantiation case and also
5521 -- for the case of processing a generic formal package. We
5522 -- detect these cases by noting that the Sloc on the node
5523 -- does not belong to the current compilation unit.
5525 Sindex := Source_Index (Current_Sem_Unit);
5527 if Loc not in Source_First (Sindex) .. Source_Last (Sindex) then
5528 Rewrite (N, Make_Null_Statement (Loc));
5529 return;
5531 -- If before first declaration, the pragma applies to the
5532 -- enclosing unit, and the name if present must be this name.
5534 elsif Is_Before_First_Decl (N, Plist) then
5535 Unit_Node := Unit_Declaration_Node (Current_Scope);
5536 Unit_Kind := Nkind (Unit_Node);
5538 if Nkind (Parent (Unit_Node)) /= N_Compilation_Unit then
5539 Pragma_Misplaced;
5541 elsif Unit_Kind = N_Subprogram_Body
5542 and then not Acts_As_Spec (Unit_Node)
5543 then
5544 Pragma_Misplaced;
5546 elsif Nkind (Parent_Node) = N_Package_Body then
5547 Pragma_Misplaced;
5549 elsif Nkind (Parent_Node) = N_Package_Specification
5550 and then Plist = Private_Declarations (Parent_Node)
5551 then
5552 Pragma_Misplaced;
5554 elsif (Nkind (Parent_Node) = N_Generic_Package_Declaration
5555 or else Nkind (Parent_Node) =
5556 N_Generic_Subprogram_Declaration)
5557 and then Plist = Generic_Formal_Declarations (Parent_Node)
5558 then
5559 Pragma_Misplaced;
5561 elsif Arg_Count > 0 then
5562 Analyze (Get_Pragma_Arg (Arg1));
5564 if Entity (Get_Pragma_Arg (Arg1)) /= Current_Scope then
5565 Error_Pragma_Arg
5566 ("name in pragma% must be enclosing unit", Arg1);
5567 end if;
5569 -- It is legal to have no argument in this context
5571 else
5572 return;
5573 end if;
5575 -- Error if not before first declaration. This is because a
5576 -- library unit pragma argument must be the name of a library
5577 -- unit (RM 10.1.5(7)), but the only names permitted in this
5578 -- context are (RM 10.1.5(6)) names of subprogram declarations,
5579 -- generic subprogram declarations or generic instantiations.
5581 else
5582 Error_Pragma
5583 ("pragma% misplaced, must be before first declaration");
5584 end if;
5585 end if;
5586 end if;
5587 end Check_Valid_Library_Unit_Pragma;
5589 -------------------
5590 -- Check_Variant --
5591 -------------------
5593 procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id) is
5594 Clist : constant Node_Id := Component_List (Variant);
5595 Comp : Node_Id;
5597 begin
5598 Comp := First (Component_Items (Clist));
5599 while Present (Comp) loop
5600 Check_Component (Comp, UU_Typ, In_Variant_Part => True);
5601 Next (Comp);
5602 end loop;
5603 end Check_Variant;
5605 ---------------------------
5606 -- Ensure_Aggregate_Form --
5607 ---------------------------
5609 procedure Ensure_Aggregate_Form (Arg : Node_Id) is
5610 Expr : constant Node_Id := Get_Pragma_Arg (Arg);
5611 Loc : constant Source_Ptr := Sloc (Arg);
5612 Nam : constant Name_Id := Chars (Arg);
5613 Comps : List_Id := No_List;
5614 Exprs : List_Id := No_List;
5616 CFSD : constant Boolean := Get_Comes_From_Source_Default;
5617 -- Used to restore Comes_From_Source_Default
5619 begin
5620 -- The argument is already in aggregate form, but the presence of a
5621 -- name causes this to be interpreted as a named association which in
5622 -- turn must be converted into an aggregate.
5624 -- pragma Global (In_Out => (A, B, C))
5625 -- ^ ^
5626 -- name aggregate
5628 -- pragma Global ((In_Out => (A, B, C)))
5629 -- ^ ^
5630 -- aggregate aggregate
5632 if Nkind (Expr) = N_Aggregate then
5633 if Nam = No_Name then
5634 return;
5635 end if;
5637 -- Do not transform a null argument into an aggregate as N_Null has
5638 -- special meaning in formal verification pragmas.
5640 elsif Nkind (Expr) = N_Null then
5641 return;
5642 end if;
5644 -- Everything comes from source if the original comes from source
5646 Set_Comes_From_Source_Default (Comes_From_Source (Arg));
5648 -- Positional argument is transformed into an aggregate with an
5649 -- Expressions list.
5651 if Nam = No_Name then
5652 Exprs := New_List (Relocate_Node (Expr));
5654 -- An associative argument is transformed into an aggregate with
5655 -- Component_Associations.
5657 else
5658 Comps := New_List (
5659 Make_Component_Association (Loc,
5660 Choices => New_List (Make_Identifier (Loc, Chars (Arg))),
5661 Expression => Relocate_Node (Expr)));
5662 end if;
5664 -- Remove the pragma argument name as this information has been
5665 -- captured in the aggregate.
5667 Set_Chars (Arg, No_Name);
5669 Set_Expression (Arg,
5670 Make_Aggregate (Loc,
5671 Component_Associations => Comps,
5672 Expressions => Exprs));
5674 -- Restore Comes_From_Source default
5676 Set_Comes_From_Source_Default (CFSD);
5677 end Ensure_Aggregate_Form;
5679 ------------------
5680 -- Error_Pragma --
5681 ------------------
5683 procedure Error_Pragma (Msg : String) is
5684 begin
5685 Error_Msg_Name_1 := Pname;
5686 Error_Msg_N (Fix_Error (Msg), N);
5687 raise Pragma_Exit;
5688 end Error_Pragma;
5690 ----------------------
5691 -- Error_Pragma_Arg --
5692 ----------------------
5694 procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id) is
5695 begin
5696 Error_Msg_Name_1 := Pname;
5697 Error_Msg_N (Fix_Error (Msg), Get_Pragma_Arg (Arg));
5698 raise Pragma_Exit;
5699 end Error_Pragma_Arg;
5701 procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id) is
5702 begin
5703 Error_Msg_Name_1 := Pname;
5704 Error_Msg_N (Fix_Error (Msg1), Get_Pragma_Arg (Arg));
5705 Error_Pragma_Arg (Msg2, Arg);
5706 end Error_Pragma_Arg;
5708 ----------------------------
5709 -- Error_Pragma_Arg_Ident --
5710 ----------------------------
5712 procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id) is
5713 begin
5714 Error_Msg_Name_1 := Pname;
5715 Error_Msg_N (Fix_Error (Msg), Arg);
5716 raise Pragma_Exit;
5717 end Error_Pragma_Arg_Ident;
5719 ----------------------
5720 -- Error_Pragma_Ref --
5721 ----------------------
5723 procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id) is
5724 begin
5725 Error_Msg_Name_1 := Pname;
5726 Error_Msg_Sloc := Sloc (Ref);
5727 Error_Msg_NE (Fix_Error (Msg), N, Ref);
5728 raise Pragma_Exit;
5729 end Error_Pragma_Ref;
5731 ------------------------
5732 -- Find_Lib_Unit_Name --
5733 ------------------------
5735 function Find_Lib_Unit_Name return Entity_Id is
5736 begin
5737 -- Return inner compilation unit entity, for case of nested
5738 -- categorization pragmas. This happens in generic unit.
5740 if Nkind (Parent (N)) = N_Package_Specification
5741 and then Defining_Entity (Parent (N)) /= Current_Scope
5742 then
5743 return Defining_Entity (Parent (N));
5744 else
5745 return Current_Scope;
5746 end if;
5747 end Find_Lib_Unit_Name;
5749 ----------------------------
5750 -- Find_Program_Unit_Name --
5751 ----------------------------
5753 procedure Find_Program_Unit_Name (Id : Node_Id) is
5754 Unit_Name : Entity_Id;
5755 Unit_Kind : Node_Kind;
5756 P : constant Node_Id := Parent (N);
5758 begin
5759 if Nkind (P) = N_Compilation_Unit then
5760 Unit_Kind := Nkind (Unit (P));
5762 if Nkind_In (Unit_Kind, N_Subprogram_Declaration,
5763 N_Package_Declaration)
5764 or else Unit_Kind in N_Generic_Declaration
5765 then
5766 Unit_Name := Defining_Entity (Unit (P));
5768 if Chars (Id) = Chars (Unit_Name) then
5769 Set_Entity (Id, Unit_Name);
5770 Set_Etype (Id, Etype (Unit_Name));
5771 else
5772 Set_Etype (Id, Any_Type);
5773 Error_Pragma
5774 ("cannot find program unit referenced by pragma%");
5775 end if;
5777 else
5778 Set_Etype (Id, Any_Type);
5779 Error_Pragma ("pragma% inapplicable to this unit");
5780 end if;
5782 else
5783 Analyze (Id);
5784 end if;
5785 end Find_Program_Unit_Name;
5787 -----------------------------------------
5788 -- Find_Unique_Parameterless_Procedure --
5789 -----------------------------------------
5791 function Find_Unique_Parameterless_Procedure
5792 (Name : Entity_Id;
5793 Arg : Node_Id) return Entity_Id
5795 Proc : Entity_Id := Empty;
5797 begin
5798 -- The body of this procedure needs some comments ???
5800 if not Is_Entity_Name (Name) then
5801 Error_Pragma_Arg
5802 ("argument of pragma% must be entity name", Arg);
5804 elsif not Is_Overloaded (Name) then
5805 Proc := Entity (Name);
5807 if Ekind (Proc) /= E_Procedure
5808 or else Present (First_Formal (Proc))
5809 then
5810 Error_Pragma_Arg
5811 ("argument of pragma% must be parameterless procedure", Arg);
5812 end if;
5814 else
5815 declare
5816 Found : Boolean := False;
5817 It : Interp;
5818 Index : Interp_Index;
5820 begin
5821 Get_First_Interp (Name, Index, It);
5822 while Present (It.Nam) loop
5823 Proc := It.Nam;
5825 if Ekind (Proc) = E_Procedure
5826 and then No (First_Formal (Proc))
5827 then
5828 if not Found then
5829 Found := True;
5830 Set_Entity (Name, Proc);
5831 Set_Is_Overloaded (Name, False);
5832 else
5833 Error_Pragma_Arg
5834 ("ambiguous handler name for pragma% ", Arg);
5835 end if;
5836 end if;
5838 Get_Next_Interp (Index, It);
5839 end loop;
5841 if not Found then
5842 Error_Pragma_Arg
5843 ("argument of pragma% must be parameterless procedure",
5844 Arg);
5845 else
5846 Proc := Entity (Name);
5847 end if;
5848 end;
5849 end if;
5851 return Proc;
5852 end Find_Unique_Parameterless_Procedure;
5854 ---------------
5855 -- Fix_Error --
5856 ---------------
5858 function Fix_Error (Msg : String) return String is
5859 Res : String (Msg'Range) := Msg;
5860 Res_Last : Natural := Msg'Last;
5861 J : Natural;
5863 begin
5864 -- If we have a rewriting of another pragma, go to that pragma
5866 if Is_Rewrite_Substitution (N)
5867 and then Nkind (Original_Node (N)) = N_Pragma
5868 then
5869 Error_Msg_Name_1 := Pragma_Name (Original_Node (N));
5870 end if;
5872 -- Case where pragma comes from an aspect specification
5874 if From_Aspect_Specification (N) then
5876 -- Change appearence of "pragma" in message to "aspect"
5878 J := Res'First;
5879 while J <= Res_Last - 5 loop
5880 if Res (J .. J + 5) = "pragma" then
5881 Res (J .. J + 5) := "aspect";
5882 J := J + 6;
5884 else
5885 J := J + 1;
5886 end if;
5887 end loop;
5889 -- Change "argument of" at start of message to "entity for"
5891 if Res'Length > 11
5892 and then Res (Res'First .. Res'First + 10) = "argument of"
5893 then
5894 Res (Res'First .. Res'First + 9) := "entity for";
5895 Res (Res'First + 10 .. Res_Last - 1) :=
5896 Res (Res'First + 11 .. Res_Last);
5897 Res_Last := Res_Last - 1;
5898 end if;
5900 -- Change "argument" at start of message to "entity"
5902 if Res'Length > 8
5903 and then Res (Res'First .. Res'First + 7) = "argument"
5904 then
5905 Res (Res'First .. Res'First + 5) := "entity";
5906 Res (Res'First + 6 .. Res_Last - 2) :=
5907 Res (Res'First + 8 .. Res_Last);
5908 Res_Last := Res_Last - 2;
5909 end if;
5911 -- Get name from corresponding aspect
5913 Error_Msg_Name_1 := Original_Aspect_Name (N);
5914 end if;
5916 -- Return possibly modified message
5918 return Res (Res'First .. Res_Last);
5919 end Fix_Error;
5921 -------------------------
5922 -- Gather_Associations --
5923 -------------------------
5925 procedure Gather_Associations
5926 (Names : Name_List;
5927 Args : out Args_List)
5929 Arg : Node_Id;
5931 begin
5932 -- Initialize all parameters to Empty
5934 for J in Args'Range loop
5935 Args (J) := Empty;
5936 end loop;
5938 -- That's all we have to do if there are no argument associations
5940 if No (Pragma_Argument_Associations (N)) then
5941 return;
5942 end if;
5944 -- Otherwise first deal with any positional parameters present
5946 Arg := First (Pragma_Argument_Associations (N));
5947 for Index in Args'Range loop
5948 exit when No (Arg) or else Chars (Arg) /= No_Name;
5949 Args (Index) := Get_Pragma_Arg (Arg);
5950 Next (Arg);
5951 end loop;
5953 -- Positional parameters all processed, if any left, then we
5954 -- have too many positional parameters.
5956 if Present (Arg) and then Chars (Arg) = No_Name then
5957 Error_Pragma_Arg
5958 ("too many positional associations for pragma%", Arg);
5959 end if;
5961 -- Process named parameters if any are present
5963 while Present (Arg) loop
5964 if Chars (Arg) = No_Name then
5965 Error_Pragma_Arg
5966 ("positional association cannot follow named association",
5967 Arg);
5969 else
5970 for Index in Names'Range loop
5971 if Names (Index) = Chars (Arg) then
5972 if Present (Args (Index)) then
5973 Error_Pragma_Arg
5974 ("duplicate argument association for pragma%", Arg);
5975 else
5976 Args (Index) := Get_Pragma_Arg (Arg);
5977 exit;
5978 end if;
5979 end if;
5981 if Index = Names'Last then
5982 Error_Msg_Name_1 := Pname;
5983 Error_Msg_N ("pragma% does not allow & argument", Arg);
5985 -- Check for possible misspelling
5987 for Index1 in Names'Range loop
5988 if Is_Bad_Spelling_Of
5989 (Chars (Arg), Names (Index1))
5990 then
5991 Error_Msg_Name_1 := Names (Index1);
5992 Error_Msg_N -- CODEFIX
5993 ("\possible misspelling of%", Arg);
5994 exit;
5995 end if;
5996 end loop;
5998 raise Pragma_Exit;
5999 end if;
6000 end loop;
6001 end if;
6003 Next (Arg);
6004 end loop;
6005 end Gather_Associations;
6007 -----------------
6008 -- GNAT_Pragma --
6009 -----------------
6011 procedure GNAT_Pragma is
6012 begin
6013 -- We need to check the No_Implementation_Pragmas restriction for
6014 -- the case of a pragma from source. Note that the case of aspects
6015 -- generating corresponding pragmas marks these pragmas as not being
6016 -- from source, so this test also catches that case.
6018 if Comes_From_Source (N) then
6019 Check_Restriction (No_Implementation_Pragmas, N);
6020 end if;
6021 end GNAT_Pragma;
6023 --------------------------
6024 -- Is_Before_First_Decl --
6025 --------------------------
6027 function Is_Before_First_Decl
6028 (Pragma_Node : Node_Id;
6029 Decls : List_Id) return Boolean
6031 Item : Node_Id := First (Decls);
6033 begin
6034 -- Only other pragmas can come before this pragma
6036 loop
6037 if No (Item) or else Nkind (Item) /= N_Pragma then
6038 return False;
6040 elsif Item = Pragma_Node then
6041 return True;
6042 end if;
6044 Next (Item);
6045 end loop;
6046 end Is_Before_First_Decl;
6048 -----------------------------
6049 -- Is_Configuration_Pragma --
6050 -----------------------------
6052 -- A configuration pragma must appear in the context clause of a
6053 -- compilation unit, and only other pragmas may precede it. Note that
6054 -- the test below also permits use in a configuration pragma file.
6056 function Is_Configuration_Pragma return Boolean is
6057 Lis : constant List_Id := List_Containing (N);
6058 Par : constant Node_Id := Parent (N);
6059 Prg : Node_Id;
6061 begin
6062 -- If no parent, then we are in the configuration pragma file,
6063 -- so the placement is definitely appropriate.
6065 if No (Par) then
6066 return True;
6068 -- Otherwise we must be in the context clause of a compilation unit
6069 -- and the only thing allowed before us in the context list is more
6070 -- configuration pragmas.
6072 elsif Nkind (Par) = N_Compilation_Unit
6073 and then Context_Items (Par) = Lis
6074 then
6075 Prg := First (Lis);
6077 loop
6078 if Prg = N then
6079 return True;
6080 elsif Nkind (Prg) /= N_Pragma then
6081 return False;
6082 end if;
6084 Next (Prg);
6085 end loop;
6087 else
6088 return False;
6089 end if;
6090 end Is_Configuration_Pragma;
6092 --------------------------
6093 -- Is_In_Context_Clause --
6094 --------------------------
6096 function Is_In_Context_Clause return Boolean is
6097 Plist : List_Id;
6098 Parent_Node : Node_Id;
6100 begin
6101 if not Is_List_Member (N) then
6102 return False;
6104 else
6105 Plist := List_Containing (N);
6106 Parent_Node := Parent (Plist);
6108 if Parent_Node = Empty
6109 or else Nkind (Parent_Node) /= N_Compilation_Unit
6110 or else Context_Items (Parent_Node) /= Plist
6111 then
6112 return False;
6113 end if;
6114 end if;
6116 return True;
6117 end Is_In_Context_Clause;
6119 ---------------------------------
6120 -- Is_Static_String_Expression --
6121 ---------------------------------
6123 function Is_Static_String_Expression (Arg : Node_Id) return Boolean is
6124 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
6125 Lit : constant Boolean := Nkind (Argx) = N_String_Literal;
6127 begin
6128 Analyze_And_Resolve (Argx);
6130 -- Special case Ada 83, where the expression will never be static,
6131 -- but we will return true if we had a string literal to start with.
6133 if Ada_Version = Ada_83 then
6134 return Lit;
6136 -- Normal case, true only if we end up with a string literal that
6137 -- is marked as being the result of evaluating a static expression.
6139 else
6140 return Is_OK_Static_Expression (Argx)
6141 and then Nkind (Argx) = N_String_Literal;
6142 end if;
6144 end Is_Static_String_Expression;
6146 ----------------------
6147 -- Pragma_Misplaced --
6148 ----------------------
6150 procedure Pragma_Misplaced is
6151 begin
6152 Error_Pragma ("incorrect placement of pragma%");
6153 end Pragma_Misplaced;
6155 ------------------------------------------------
6156 -- Process_Atomic_Independent_Shared_Volatile --
6157 ------------------------------------------------
6159 procedure Process_Atomic_Independent_Shared_Volatile is
6160 E_Id : Node_Id;
6161 E : Entity_Id;
6162 D : Node_Id;
6163 K : Node_Kind;
6164 Utyp : Entity_Id;
6166 procedure Set_Atomic (E : Entity_Id);
6167 -- Set given type as atomic, and if no explicit alignment was given,
6168 -- set alignment to unknown, since back end knows what the alignment
6169 -- requirements are for atomic arrays. Note: this step is necessary
6170 -- for derived types.
6172 ----------------
6173 -- Set_Atomic --
6174 ----------------
6176 procedure Set_Atomic (E : Entity_Id) is
6177 begin
6178 Set_Is_Atomic (E);
6180 if not Has_Alignment_Clause (E) then
6181 Set_Alignment (E, Uint_0);
6182 end if;
6183 end Set_Atomic;
6185 -- Start of processing for Process_Atomic_Independent_Shared_Volatile
6187 begin
6188 Check_Ada_83_Warning;
6189 Check_No_Identifiers;
6190 Check_Arg_Count (1);
6191 Check_Arg_Is_Local_Name (Arg1);
6192 E_Id := Get_Pragma_Arg (Arg1);
6194 if Etype (E_Id) = Any_Type then
6195 return;
6196 end if;
6198 E := Entity (E_Id);
6199 D := Declaration_Node (E);
6200 K := Nkind (D);
6202 -- Check duplicate before we chain ourselves
6204 Check_Duplicate_Pragma (E);
6206 -- Now check appropriateness of the entity
6208 if Is_Type (E) then
6209 if Rep_Item_Too_Early (E, N)
6210 or else
6211 Rep_Item_Too_Late (E, N)
6212 then
6213 return;
6214 else
6215 Check_First_Subtype (Arg1);
6216 end if;
6218 if Prag_Id = Pragma_Atomic or else Prag_Id = Pragma_Shared then
6219 Set_Atomic (E);
6220 Set_Atomic (Underlying_Type (E));
6221 Set_Atomic (Base_Type (E));
6222 end if;
6224 -- Atomic/Shared imply both Independent and Volatile
6226 if Prag_Id /= Pragma_Volatile then
6227 Set_Is_Independent (E);
6228 Set_Is_Independent (Underlying_Type (E));
6229 Set_Is_Independent (Base_Type (E));
6231 if Prag_Id = Pragma_Independent then
6232 Independence_Checks.Append ((N, Base_Type (E)));
6233 end if;
6234 end if;
6236 -- Attribute belongs on the base type. If the view of the type is
6237 -- currently private, it also belongs on the underlying type.
6239 if Prag_Id /= Pragma_Independent then
6240 Set_Is_Volatile (Base_Type (E));
6241 Set_Is_Volatile (Underlying_Type (E));
6243 Set_Treat_As_Volatile (E);
6244 Set_Treat_As_Volatile (Underlying_Type (E));
6245 end if;
6247 elsif K = N_Object_Declaration
6248 or else (K = N_Component_Declaration
6249 and then Original_Record_Component (E) = E)
6250 then
6251 if Rep_Item_Too_Late (E, N) then
6252 return;
6253 end if;
6255 if Prag_Id = Pragma_Atomic or else Prag_Id = Pragma_Shared then
6256 Set_Is_Atomic (E);
6258 -- If the object declaration has an explicit initialization, a
6259 -- temporary may have to be created to hold the expression, to
6260 -- ensure that access to the object remain atomic.
6262 if Nkind (Parent (E)) = N_Object_Declaration
6263 and then Present (Expression (Parent (E)))
6264 then
6265 Set_Has_Delayed_Freeze (E);
6266 end if;
6268 -- An interesting improvement here. If an object of composite
6269 -- type X is declared atomic, and the type X isn't, that's a
6270 -- pity, since it may not have appropriate alignment etc. We
6271 -- can rescue this in the special case where the object and
6272 -- type are in the same unit by just setting the type as
6273 -- atomic, so that the back end will process it as atomic.
6275 -- Note: we used to do this for elementary types as well,
6276 -- but that turns out to be a bad idea and can have unwanted
6277 -- effects, most notably if the type is elementary, the object
6278 -- a simple component within a record, and both are in a spec:
6279 -- every object of this type in the entire program will be
6280 -- treated as atomic, thus incurring a potentially costly
6281 -- synchronization operation for every access.
6283 -- Of course it would be best if the back end could just adjust
6284 -- the alignment etc for the specific object, but that's not
6285 -- something we are capable of doing at this point.
6287 Utyp := Underlying_Type (Etype (E));
6289 if Present (Utyp)
6290 and then Is_Composite_Type (Utyp)
6291 and then Sloc (E) > No_Location
6292 and then Sloc (Utyp) > No_Location
6293 and then
6294 Get_Source_File_Index (Sloc (E)) =
6295 Get_Source_File_Index (Sloc (Underlying_Type (Etype (E))))
6296 then
6297 Set_Is_Atomic (Underlying_Type (Etype (E)));
6298 end if;
6299 end if;
6301 -- Atomic/Shared imply both Independent and Volatile
6303 if Prag_Id /= Pragma_Volatile then
6304 Set_Is_Independent (E);
6306 if Prag_Id = Pragma_Independent then
6307 Independence_Checks.Append ((N, E));
6308 end if;
6309 end if;
6311 if Prag_Id /= Pragma_Independent then
6312 Set_Is_Volatile (E);
6313 Set_Treat_As_Volatile (E);
6314 end if;
6316 else
6317 Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
6318 end if;
6320 -- The following check is only relevant when SPARK_Mode is on as
6321 -- this is not a standard Ada legality rule. Pragma Volatile can
6322 -- only apply to a full type declaration or an object declaration
6323 -- (SPARK RM C.6(1)).
6325 if SPARK_Mode = On
6326 and then Prag_Id = Pragma_Volatile
6327 and then not Nkind_In (K, N_Full_Type_Declaration,
6328 N_Object_Declaration)
6329 then
6330 Error_Pragma_Arg
6331 ("argument of pragma % must denote a full type or object "
6332 & "declaration", Arg1);
6333 end if;
6334 end Process_Atomic_Independent_Shared_Volatile;
6336 -------------------------------------------
6337 -- Process_Compile_Time_Warning_Or_Error --
6338 -------------------------------------------
6340 procedure Process_Compile_Time_Warning_Or_Error is
6341 Arg1x : constant Node_Id := Get_Pragma_Arg (Arg1);
6343 begin
6344 Check_Arg_Count (2);
6345 Check_No_Identifiers;
6346 Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
6347 Analyze_And_Resolve (Arg1x, Standard_Boolean);
6349 if Compile_Time_Known_Value (Arg1x) then
6350 if Is_True (Expr_Value (Get_Pragma_Arg (Arg1))) then
6351 declare
6352 Str : constant String_Id :=
6353 Strval (Get_Pragma_Arg (Arg2));
6354 Len : constant Int := String_Length (Str);
6355 Cont : Boolean;
6356 Ptr : Nat;
6357 CC : Char_Code;
6358 C : Character;
6359 Cent : constant Entity_Id :=
6360 Cunit_Entity (Current_Sem_Unit);
6362 Force : constant Boolean :=
6363 Prag_Id = Pragma_Compile_Time_Warning
6364 and then
6365 Is_Spec_Name (Unit_Name (Current_Sem_Unit))
6366 and then (Ekind (Cent) /= E_Package
6367 or else not In_Private_Part (Cent));
6368 -- Set True if this is the warning case, and we are in the
6369 -- visible part of a package spec, or in a subprogram spec,
6370 -- in which case we want to force the client to see the
6371 -- warning, even though it is not in the main unit.
6373 begin
6374 -- Loop through segments of message separated by line feeds.
6375 -- We output these segments as separate messages with
6376 -- continuation marks for all but the first.
6378 Cont := False;
6379 Ptr := 1;
6380 loop
6381 Error_Msg_Strlen := 0;
6383 -- Loop to copy characters from argument to error message
6384 -- string buffer.
6386 loop
6387 exit when Ptr > Len;
6388 CC := Get_String_Char (Str, Ptr);
6389 Ptr := Ptr + 1;
6391 -- Ignore wide chars ??? else store character
6393 if In_Character_Range (CC) then
6394 C := Get_Character (CC);
6395 exit when C = ASCII.LF;
6396 Error_Msg_Strlen := Error_Msg_Strlen + 1;
6397 Error_Msg_String (Error_Msg_Strlen) := C;
6398 end if;
6399 end loop;
6401 -- Here with one line ready to go
6403 Error_Msg_Warn := Prag_Id = Pragma_Compile_Time_Warning;
6405 -- If this is a warning in a spec, then we want clients
6406 -- to see the warning, so mark the message with the
6407 -- special sequence !! to force the warning. In the case
6408 -- of a package spec, we do not force this if we are in
6409 -- the private part of the spec.
6411 if Force then
6412 if Cont = False then
6413 Error_Msg_N ("<<~!!", Arg1);
6414 Cont := True;
6415 else
6416 Error_Msg_N ("\<<~!!", Arg1);
6417 end if;
6419 -- Error, rather than warning, or in a body, so we do not
6420 -- need to force visibility for client (error will be
6421 -- output in any case, and this is the situation in which
6422 -- we do not want a client to get a warning, since the
6423 -- warning is in the body or the spec private part).
6425 else
6426 if Cont = False then
6427 Error_Msg_N ("<<~", Arg1);
6428 Cont := True;
6429 else
6430 Error_Msg_N ("\<<~", Arg1);
6431 end if;
6432 end if;
6434 exit when Ptr > Len;
6435 end loop;
6436 end;
6437 end if;
6438 end if;
6439 end Process_Compile_Time_Warning_Or_Error;
6441 ------------------------
6442 -- Process_Convention --
6443 ------------------------
6445 procedure Process_Convention
6446 (C : out Convention_Id;
6447 Ent : out Entity_Id)
6449 Cname : Name_Id;
6451 procedure Diagnose_Multiple_Pragmas (S : Entity_Id);
6452 -- Called if we have more than one Export/Import/Convention pragma.
6453 -- This is generally illegal, but we have a special case of allowing
6454 -- Import and Interface to coexist if they specify the convention in
6455 -- a consistent manner. We are allowed to do this, since Interface is
6456 -- an implementation defined pragma, and we choose to do it since we
6457 -- know Rational allows this combination. S is the entity id of the
6458 -- subprogram in question. This procedure also sets the special flag
6459 -- Import_Interface_Present in both pragmas in the case where we do
6460 -- have matching Import and Interface pragmas.
6462 procedure Set_Convention_From_Pragma (E : Entity_Id);
6463 -- Set convention in entity E, and also flag that the entity has a
6464 -- convention pragma. If entity is for a private or incomplete type,
6465 -- also set convention and flag on underlying type. This procedure
6466 -- also deals with the special case of C_Pass_By_Copy convention,
6467 -- and error checks for inappropriate convention specification.
6469 -------------------------------
6470 -- Diagnose_Multiple_Pragmas --
6471 -------------------------------
6473 procedure Diagnose_Multiple_Pragmas (S : Entity_Id) is
6474 Pdec : constant Node_Id := Declaration_Node (S);
6475 Decl : Node_Id;
6476 Err : Boolean;
6478 function Same_Convention (Decl : Node_Id) return Boolean;
6479 -- Decl is a pragma node. This function returns True if this
6480 -- pragma has a first argument that is an identifier with a
6481 -- Chars field corresponding to the Convention_Id C.
6483 function Same_Name (Decl : Node_Id) return Boolean;
6484 -- Decl is a pragma node. This function returns True if this
6485 -- pragma has a second argument that is an identifier with a
6486 -- Chars field that matches the Chars of the current subprogram.
6488 ---------------------
6489 -- Same_Convention --
6490 ---------------------
6492 function Same_Convention (Decl : Node_Id) return Boolean is
6493 Arg1 : constant Node_Id :=
6494 First (Pragma_Argument_Associations (Decl));
6496 begin
6497 if Present (Arg1) then
6498 declare
6499 Arg : constant Node_Id := Get_Pragma_Arg (Arg1);
6500 begin
6501 if Nkind (Arg) = N_Identifier
6502 and then Is_Convention_Name (Chars (Arg))
6503 and then Get_Convention_Id (Chars (Arg)) = C
6504 then
6505 return True;
6506 end if;
6507 end;
6508 end if;
6510 return False;
6511 end Same_Convention;
6513 ---------------
6514 -- Same_Name --
6515 ---------------
6517 function Same_Name (Decl : Node_Id) return Boolean is
6518 Arg1 : constant Node_Id :=
6519 First (Pragma_Argument_Associations (Decl));
6520 Arg2 : Node_Id;
6522 begin
6523 if No (Arg1) then
6524 return False;
6525 end if;
6527 Arg2 := Next (Arg1);
6529 if No (Arg2) then
6530 return False;
6531 end if;
6533 declare
6534 Arg : constant Node_Id := Get_Pragma_Arg (Arg2);
6535 begin
6536 if Nkind (Arg) = N_Identifier
6537 and then Chars (Arg) = Chars (S)
6538 then
6539 return True;
6540 end if;
6541 end;
6543 return False;
6544 end Same_Name;
6546 -- Start of processing for Diagnose_Multiple_Pragmas
6548 begin
6549 Err := True;
6551 -- Definitely give message if we have Convention/Export here
6553 if Prag_Id = Pragma_Convention or else Prag_Id = Pragma_Export then
6554 null;
6556 -- If we have an Import or Export, scan back from pragma to
6557 -- find any previous pragma applying to the same procedure.
6558 -- The scan will be terminated by the start of the list, or
6559 -- hitting the subprogram declaration. This won't allow one
6560 -- pragma to appear in the public part and one in the private
6561 -- part, but that seems very unlikely in practice.
6563 else
6564 Decl := Prev (N);
6565 while Present (Decl) and then Decl /= Pdec loop
6567 -- Look for pragma with same name as us
6569 if Nkind (Decl) = N_Pragma
6570 and then Same_Name (Decl)
6571 then
6572 -- Give error if same as our pragma or Export/Convention
6574 if Nam_In (Pragma_Name (Decl), Name_Export,
6575 Name_Convention,
6576 Pragma_Name (N))
6577 then
6578 exit;
6580 -- Case of Import/Interface or the other way round
6582 elsif Nam_In (Pragma_Name (Decl), Name_Interface,
6583 Name_Import)
6584 then
6585 -- Here we know that we have Import and Interface. It
6586 -- doesn't matter which way round they are. See if
6587 -- they specify the same convention. If so, all OK,
6588 -- and set special flags to stop other messages
6590 if Same_Convention (Decl) then
6591 Set_Import_Interface_Present (N);
6592 Set_Import_Interface_Present (Decl);
6593 Err := False;
6595 -- If different conventions, special message
6597 else
6598 Error_Msg_Sloc := Sloc (Decl);
6599 Error_Pragma_Arg
6600 ("convention differs from that given#", Arg1);
6601 return;
6602 end if;
6603 end if;
6604 end if;
6606 Next (Decl);
6607 end loop;
6608 end if;
6610 -- Give message if needed if we fall through those tests
6611 -- except on Relaxed_RM_Semantics where we let go: either this
6612 -- is a case accepted/ignored by other Ada compilers (e.g.
6613 -- a mix of Convention and Import), or another error will be
6614 -- generated later (e.g. using both Import and Export).
6616 if Err and not Relaxed_RM_Semantics then
6617 Error_Pragma_Arg
6618 ("at most one Convention/Export/Import pragma is allowed",
6619 Arg2);
6620 end if;
6621 end Diagnose_Multiple_Pragmas;
6623 --------------------------------
6624 -- Set_Convention_From_Pragma --
6625 --------------------------------
6627 procedure Set_Convention_From_Pragma (E : Entity_Id) is
6628 begin
6629 -- Ada 2005 (AI-430): Check invalid attempt to change convention
6630 -- for an overridden dispatching operation. Technically this is
6631 -- an amendment and should only be done in Ada 2005 mode. However,
6632 -- this is clearly a mistake, since the problem that is addressed
6633 -- by this AI is that there is a clear gap in the RM.
6635 if Is_Dispatching_Operation (E)
6636 and then Present (Overridden_Operation (E))
6637 and then C /= Convention (Overridden_Operation (E))
6638 then
6639 Error_Pragma_Arg
6640 ("cannot change convention for overridden dispatching "
6641 & "operation", Arg1);
6642 end if;
6644 -- Special checks for Convention_Stdcall
6646 if C = Convention_Stdcall then
6648 -- A dispatching call is not allowed. A dispatching subprogram
6649 -- cannot be used to interface to the Win32 API, so in fact
6650 -- this check does not impose any effective restriction.
6652 if Is_Dispatching_Operation (E) then
6653 Error_Msg_Sloc := Sloc (E);
6655 -- Note: make this unconditional so that if there is more
6656 -- than one call to which the pragma applies, we get a
6657 -- message for each call. Also don't use Error_Pragma,
6658 -- so that we get multiple messages.
6660 Error_Msg_N
6661 ("dispatching subprogram# cannot use Stdcall convention!",
6662 Arg1);
6664 -- Subprograms are not allowed
6666 elsif not Is_Subprogram_Or_Generic_Subprogram (E)
6668 -- A variable is OK
6670 and then Ekind (E) /= E_Variable
6672 -- An access to subprogram is also allowed
6674 and then not
6675 (Is_Access_Type (E)
6676 and then Ekind (Designated_Type (E)) = E_Subprogram_Type)
6678 -- Allow internal call to set convention of subprogram type
6680 and then not (Ekind (E) = E_Subprogram_Type)
6681 then
6682 Error_Pragma_Arg
6683 ("second argument of pragma% must be subprogram (type)",
6684 Arg2);
6685 end if;
6686 end if;
6688 -- Set the convention
6690 Set_Convention (E, C);
6691 Set_Has_Convention_Pragma (E);
6693 -- For the case of a record base type, also set the convention of
6694 -- any anonymous access types declared in the record which do not
6695 -- currently have a specified convention.
6697 if Is_Record_Type (E) and then Is_Base_Type (E) then
6698 declare
6699 Comp : Node_Id;
6701 begin
6702 Comp := First_Component (E);
6703 while Present (Comp) loop
6704 if Present (Etype (Comp))
6705 and then Ekind_In (Etype (Comp),
6706 E_Anonymous_Access_Type,
6707 E_Anonymous_Access_Subprogram_Type)
6708 and then not Has_Convention_Pragma (Comp)
6709 then
6710 Set_Convention (Comp, C);
6711 end if;
6713 Next_Component (Comp);
6714 end loop;
6715 end;
6716 end if;
6718 -- Deal with incomplete/private type case, where underlying type
6719 -- is available, so set convention of that underlying type.
6721 if Is_Incomplete_Or_Private_Type (E)
6722 and then Present (Underlying_Type (E))
6723 then
6724 Set_Convention (Underlying_Type (E), C);
6725 Set_Has_Convention_Pragma (Underlying_Type (E), True);
6726 end if;
6728 -- A class-wide type should inherit the convention of the specific
6729 -- root type (although this isn't specified clearly by the RM).
6731 if Is_Type (E) and then Present (Class_Wide_Type (E)) then
6732 Set_Convention (Class_Wide_Type (E), C);
6733 end if;
6735 -- If the entity is a record type, then check for special case of
6736 -- C_Pass_By_Copy, which is treated the same as C except that the
6737 -- special record flag is set. This convention is only permitted
6738 -- on record types (see AI95-00131).
6740 if Cname = Name_C_Pass_By_Copy then
6741 if Is_Record_Type (E) then
6742 Set_C_Pass_By_Copy (Base_Type (E));
6743 elsif Is_Incomplete_Or_Private_Type (E)
6744 and then Is_Record_Type (Underlying_Type (E))
6745 then
6746 Set_C_Pass_By_Copy (Base_Type (Underlying_Type (E)));
6747 else
6748 Error_Pragma_Arg
6749 ("C_Pass_By_Copy convention allowed only for record type",
6750 Arg2);
6751 end if;
6752 end if;
6754 -- If the entity is a derived boolean type, check for the special
6755 -- case of convention C, C++, or Fortran, where we consider any
6756 -- nonzero value to represent true.
6758 if Is_Discrete_Type (E)
6759 and then Root_Type (Etype (E)) = Standard_Boolean
6760 and then
6761 (C = Convention_C
6762 or else
6763 C = Convention_CPP
6764 or else
6765 C = Convention_Fortran)
6766 then
6767 Set_Nonzero_Is_True (Base_Type (E));
6768 end if;
6769 end Set_Convention_From_Pragma;
6771 -- Local variables
6773 Comp_Unit : Unit_Number_Type;
6774 E : Entity_Id;
6775 E1 : Entity_Id;
6776 Id : Node_Id;
6778 -- Start of processing for Process_Convention
6780 begin
6781 Check_At_Least_N_Arguments (2);
6782 Check_Optional_Identifier (Arg1, Name_Convention);
6783 Check_Arg_Is_Identifier (Arg1);
6784 Cname := Chars (Get_Pragma_Arg (Arg1));
6786 -- C_Pass_By_Copy is treated as a synonym for convention C (this is
6787 -- tested again below to set the critical flag).
6789 if Cname = Name_C_Pass_By_Copy then
6790 C := Convention_C;
6792 -- Otherwise we must have something in the standard convention list
6794 elsif Is_Convention_Name (Cname) then
6795 C := Get_Convention_Id (Chars (Get_Pragma_Arg (Arg1)));
6797 -- Otherwise warn on unrecognized convention
6799 else
6800 if Warn_On_Export_Import then
6801 Error_Msg_N
6802 ("??unrecognized convention name, C assumed",
6803 Get_Pragma_Arg (Arg1));
6804 end if;
6806 C := Convention_C;
6807 end if;
6809 Check_Optional_Identifier (Arg2, Name_Entity);
6810 Check_Arg_Is_Local_Name (Arg2);
6812 Id := Get_Pragma_Arg (Arg2);
6813 Analyze (Id);
6815 if not Is_Entity_Name (Id) then
6816 Error_Pragma_Arg ("entity name required", Arg2);
6817 end if;
6819 E := Entity (Id);
6821 -- Set entity to return
6823 Ent := E;
6825 -- Ada_Pass_By_Copy special checking
6827 if C = Convention_Ada_Pass_By_Copy then
6828 if not Is_First_Subtype (E) then
6829 Error_Pragma_Arg
6830 ("convention `Ada_Pass_By_Copy` only allowed for types",
6831 Arg2);
6832 end if;
6834 if Is_By_Reference_Type (E) then
6835 Error_Pragma_Arg
6836 ("convention `Ada_Pass_By_Copy` not allowed for by-reference "
6837 & "type", Arg1);
6838 end if;
6840 -- Ada_Pass_By_Reference special checking
6842 elsif C = Convention_Ada_Pass_By_Reference then
6843 if not Is_First_Subtype (E) then
6844 Error_Pragma_Arg
6845 ("convention `Ada_Pass_By_Reference` only allowed for types",
6846 Arg2);
6847 end if;
6849 if Is_By_Copy_Type (E) then
6850 Error_Pragma_Arg
6851 ("convention `Ada_Pass_By_Reference` not allowed for by-copy "
6852 & "type", Arg1);
6853 end if;
6854 end if;
6856 -- Go to renamed subprogram if present, since convention applies to
6857 -- the actual renamed entity, not to the renaming entity. If the
6858 -- subprogram is inherited, go to parent subprogram.
6860 if Is_Subprogram (E)
6861 and then Present (Alias (E))
6862 then
6863 if Nkind (Parent (Declaration_Node (E))) =
6864 N_Subprogram_Renaming_Declaration
6865 then
6866 if Scope (E) /= Scope (Alias (E)) then
6867 Error_Pragma_Ref
6868 ("cannot apply pragma% to non-local entity&#", E);
6869 end if;
6871 E := Alias (E);
6873 elsif Nkind_In (Parent (E), N_Full_Type_Declaration,
6874 N_Private_Extension_Declaration)
6875 and then Scope (E) = Scope (Alias (E))
6876 then
6877 E := Alias (E);
6879 -- Return the parent subprogram the entity was inherited from
6881 Ent := E;
6882 end if;
6883 end if;
6885 -- Check that we are not applying this to a specless body. Relax this
6886 -- check if Relaxed_RM_Semantics to accomodate other Ada compilers.
6888 if Is_Subprogram (E)
6889 and then Nkind (Parent (Declaration_Node (E))) = N_Subprogram_Body
6890 and then not Relaxed_RM_Semantics
6891 then
6892 Error_Pragma
6893 ("pragma% requires separate spec and must come before body");
6894 end if;
6896 -- Check that we are not applying this to a named constant
6898 if Ekind_In (E, E_Named_Integer, E_Named_Real) then
6899 Error_Msg_Name_1 := Pname;
6900 Error_Msg_N
6901 ("cannot apply pragma% to named constant!",
6902 Get_Pragma_Arg (Arg2));
6903 Error_Pragma_Arg
6904 ("\supply appropriate type for&!", Arg2);
6905 end if;
6907 if Ekind (E) = E_Enumeration_Literal then
6908 Error_Pragma ("enumeration literal not allowed for pragma%");
6909 end if;
6911 -- Check for rep item appearing too early or too late
6913 if Etype (E) = Any_Type
6914 or else Rep_Item_Too_Early (E, N)
6915 then
6916 raise Pragma_Exit;
6918 elsif Present (Underlying_Type (E)) then
6919 E := Underlying_Type (E);
6920 end if;
6922 if Rep_Item_Too_Late (E, N) then
6923 raise Pragma_Exit;
6924 end if;
6926 if Has_Convention_Pragma (E) then
6927 Diagnose_Multiple_Pragmas (E);
6929 elsif Convention (E) = Convention_Protected
6930 or else Ekind (Scope (E)) = E_Protected_Type
6931 then
6932 Error_Pragma_Arg
6933 ("a protected operation cannot be given a different convention",
6934 Arg2);
6935 end if;
6937 -- For Intrinsic, a subprogram is required
6939 if C = Convention_Intrinsic
6940 and then not Is_Subprogram_Or_Generic_Subprogram (E)
6941 then
6942 Error_Pragma_Arg
6943 ("second argument of pragma% must be a subprogram", Arg2);
6944 end if;
6946 -- Deal with non-subprogram cases
6948 if not Is_Subprogram_Or_Generic_Subprogram (E) then
6949 Set_Convention_From_Pragma (E);
6951 if Is_Type (E) then
6952 Check_First_Subtype (Arg2);
6953 Set_Convention_From_Pragma (Base_Type (E));
6955 -- For access subprograms, we must set the convention on the
6956 -- internally generated directly designated type as well.
6958 if Ekind (E) = E_Access_Subprogram_Type then
6959 Set_Convention_From_Pragma (Directly_Designated_Type (E));
6960 end if;
6961 end if;
6963 -- For the subprogram case, set proper convention for all homonyms
6964 -- in same scope and the same declarative part, i.e. the same
6965 -- compilation unit.
6967 else
6968 Comp_Unit := Get_Source_Unit (E);
6969 Set_Convention_From_Pragma (E);
6971 -- Treat a pragma Import as an implicit body, and pragma import
6972 -- as implicit reference (for navigation in GPS).
6974 if Prag_Id = Pragma_Import then
6975 Generate_Reference (E, Id, 'b');
6977 -- For exported entities we restrict the generation of references
6978 -- to entities exported to foreign languages since entities
6979 -- exported to Ada do not provide further information to GPS and
6980 -- add undesired references to the output of the gnatxref tool.
6982 elsif Prag_Id = Pragma_Export
6983 and then Convention (E) /= Convention_Ada
6984 then
6985 Generate_Reference (E, Id, 'i');
6986 end if;
6988 -- If the pragma comes from from an aspect, it only applies to the
6989 -- given entity, not its homonyms.
6991 if From_Aspect_Specification (N) then
6992 return;
6993 end if;
6995 -- Otherwise Loop through the homonyms of the pragma argument's
6996 -- entity, an apply convention to those in the current scope.
6998 E1 := Ent;
7000 loop
7001 E1 := Homonym (E1);
7002 exit when No (E1) or else Scope (E1) /= Current_Scope;
7004 -- Ignore entry for which convention is already set
7006 if Has_Convention_Pragma (E1) then
7007 goto Continue;
7008 end if;
7010 -- Do not set the pragma on inherited operations or on formal
7011 -- subprograms.
7013 if Comes_From_Source (E1)
7014 and then Comp_Unit = Get_Source_Unit (E1)
7015 and then not Is_Formal_Subprogram (E1)
7016 and then Nkind (Original_Node (Parent (E1))) /=
7017 N_Full_Type_Declaration
7018 then
7019 if Present (Alias (E1))
7020 and then Scope (E1) /= Scope (Alias (E1))
7021 then
7022 Error_Pragma_Ref
7023 ("cannot apply pragma% to non-local entity& declared#",
7024 E1);
7025 end if;
7027 Set_Convention_From_Pragma (E1);
7029 if Prag_Id = Pragma_Import then
7030 Generate_Reference (E1, Id, 'b');
7031 end if;
7032 end if;
7034 <<Continue>>
7035 null;
7036 end loop;
7037 end if;
7038 end Process_Convention;
7040 ----------------------------------------
7041 -- Process_Disable_Enable_Atomic_Sync --
7042 ----------------------------------------
7044 procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id) is
7045 begin
7046 Check_No_Identifiers;
7047 Check_At_Most_N_Arguments (1);
7049 -- Modeled internally as
7050 -- pragma Suppress/Unsuppress (Atomic_Synchronization [,Entity])
7052 Rewrite (N,
7053 Make_Pragma (Loc,
7054 Pragma_Identifier =>
7055 Make_Identifier (Loc, Nam),
7056 Pragma_Argument_Associations => New_List (
7057 Make_Pragma_Argument_Association (Loc,
7058 Expression =>
7059 Make_Identifier (Loc, Name_Atomic_Synchronization)))));
7061 if Present (Arg1) then
7062 Append_To (Pragma_Argument_Associations (N), New_Copy (Arg1));
7063 end if;
7065 Analyze (N);
7066 end Process_Disable_Enable_Atomic_Sync;
7068 -------------------------------------------------
7069 -- Process_Extended_Import_Export_Internal_Arg --
7070 -------------------------------------------------
7072 procedure Process_Extended_Import_Export_Internal_Arg
7073 (Arg_Internal : Node_Id := Empty)
7075 begin
7076 if No (Arg_Internal) then
7077 Error_Pragma ("Internal parameter required for pragma%");
7078 end if;
7080 if Nkind (Arg_Internal) = N_Identifier then
7081 null;
7083 elsif Nkind (Arg_Internal) = N_Operator_Symbol
7084 and then (Prag_Id = Pragma_Import_Function
7085 or else
7086 Prag_Id = Pragma_Export_Function)
7087 then
7088 null;
7090 else
7091 Error_Pragma_Arg
7092 ("wrong form for Internal parameter for pragma%", Arg_Internal);
7093 end if;
7095 Check_Arg_Is_Local_Name (Arg_Internal);
7096 end Process_Extended_Import_Export_Internal_Arg;
7098 --------------------------------------------------
7099 -- Process_Extended_Import_Export_Object_Pragma --
7100 --------------------------------------------------
7102 procedure Process_Extended_Import_Export_Object_Pragma
7103 (Arg_Internal : Node_Id;
7104 Arg_External : Node_Id;
7105 Arg_Size : Node_Id)
7107 Def_Id : Entity_Id;
7109 begin
7110 Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
7111 Def_Id := Entity (Arg_Internal);
7113 if not Ekind_In (Def_Id, E_Constant, E_Variable) then
7114 Error_Pragma_Arg
7115 ("pragma% must designate an object", Arg_Internal);
7116 end if;
7118 if Has_Rep_Pragma (Def_Id, Name_Common_Object)
7119 or else
7120 Has_Rep_Pragma (Def_Id, Name_Psect_Object)
7121 then
7122 Error_Pragma_Arg
7123 ("previous Common/Psect_Object applies, pragma % not permitted",
7124 Arg_Internal);
7125 end if;
7127 if Rep_Item_Too_Late (Def_Id, N) then
7128 raise Pragma_Exit;
7129 end if;
7131 Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
7133 if Present (Arg_Size) then
7134 Check_Arg_Is_External_Name (Arg_Size);
7135 end if;
7137 -- Export_Object case
7139 if Prag_Id = Pragma_Export_Object then
7140 if not Is_Library_Level_Entity (Def_Id) then
7141 Error_Pragma_Arg
7142 ("argument for pragma% must be library level entity",
7143 Arg_Internal);
7144 end if;
7146 if Ekind (Current_Scope) = E_Generic_Package then
7147 Error_Pragma ("pragma& cannot appear in a generic unit");
7148 end if;
7150 if not Size_Known_At_Compile_Time (Etype (Def_Id)) then
7151 Error_Pragma_Arg
7152 ("exported object must have compile time known size",
7153 Arg_Internal);
7154 end if;
7156 if Warn_On_Export_Import and then Is_Exported (Def_Id) then
7157 Error_Msg_N ("??duplicate Export_Object pragma", N);
7158 else
7159 Set_Exported (Def_Id, Arg_Internal);
7160 end if;
7162 -- Import_Object case
7164 else
7165 if Is_Concurrent_Type (Etype (Def_Id)) then
7166 Error_Pragma_Arg
7167 ("cannot use pragma% for task/protected object",
7168 Arg_Internal);
7169 end if;
7171 if Ekind (Def_Id) = E_Constant then
7172 Error_Pragma_Arg
7173 ("cannot import a constant", Arg_Internal);
7174 end if;
7176 if Warn_On_Export_Import
7177 and then Has_Discriminants (Etype (Def_Id))
7178 then
7179 Error_Msg_N
7180 ("imported value must be initialized??", Arg_Internal);
7181 end if;
7183 if Warn_On_Export_Import
7184 and then Is_Access_Type (Etype (Def_Id))
7185 then
7186 Error_Pragma_Arg
7187 ("cannot import object of an access type??", Arg_Internal);
7188 end if;
7190 if Warn_On_Export_Import
7191 and then Is_Imported (Def_Id)
7192 then
7193 Error_Msg_N ("??duplicate Import_Object pragma", N);
7195 -- Check for explicit initialization present. Note that an
7196 -- initialization generated by the code generator, e.g. for an
7197 -- access type, does not count here.
7199 elsif Present (Expression (Parent (Def_Id)))
7200 and then
7201 Comes_From_Source
7202 (Original_Node (Expression (Parent (Def_Id))))
7203 then
7204 Error_Msg_Sloc := Sloc (Def_Id);
7205 Error_Pragma_Arg
7206 ("imported entities cannot be initialized (RM B.1(24))",
7207 "\no initialization allowed for & declared#", Arg1);
7208 else
7209 Set_Imported (Def_Id);
7210 Note_Possible_Modification (Arg_Internal, Sure => False);
7211 end if;
7212 end if;
7213 end Process_Extended_Import_Export_Object_Pragma;
7215 ------------------------------------------------------
7216 -- Process_Extended_Import_Export_Subprogram_Pragma --
7217 ------------------------------------------------------
7219 procedure Process_Extended_Import_Export_Subprogram_Pragma
7220 (Arg_Internal : Node_Id;
7221 Arg_External : Node_Id;
7222 Arg_Parameter_Types : Node_Id;
7223 Arg_Result_Type : Node_Id := Empty;
7224 Arg_Mechanism : Node_Id;
7225 Arg_Result_Mechanism : Node_Id := Empty)
7227 Ent : Entity_Id;
7228 Def_Id : Entity_Id;
7229 Hom_Id : Entity_Id;
7230 Formal : Entity_Id;
7231 Ambiguous : Boolean;
7232 Match : Boolean;
7234 function Same_Base_Type
7235 (Ptype : Node_Id;
7236 Formal : Entity_Id) return Boolean;
7237 -- Determines if Ptype references the type of Formal. Note that only
7238 -- the base types need to match according to the spec. Ptype here is
7239 -- the argument from the pragma, which is either a type name, or an
7240 -- access attribute.
7242 --------------------
7243 -- Same_Base_Type --
7244 --------------------
7246 function Same_Base_Type
7247 (Ptype : Node_Id;
7248 Formal : Entity_Id) return Boolean
7250 Ftyp : constant Entity_Id := Base_Type (Etype (Formal));
7251 Pref : Node_Id;
7253 begin
7254 -- Case where pragma argument is typ'Access
7256 if Nkind (Ptype) = N_Attribute_Reference
7257 and then Attribute_Name (Ptype) = Name_Access
7258 then
7259 Pref := Prefix (Ptype);
7260 Find_Type (Pref);
7262 if not Is_Entity_Name (Pref)
7263 or else Entity (Pref) = Any_Type
7264 then
7265 raise Pragma_Exit;
7266 end if;
7268 -- We have a match if the corresponding argument is of an
7269 -- anonymous access type, and its designated type matches the
7270 -- type of the prefix of the access attribute
7272 return Ekind (Ftyp) = E_Anonymous_Access_Type
7273 and then Base_Type (Entity (Pref)) =
7274 Base_Type (Etype (Designated_Type (Ftyp)));
7276 -- Case where pragma argument is a type name
7278 else
7279 Find_Type (Ptype);
7281 if not Is_Entity_Name (Ptype)
7282 or else Entity (Ptype) = Any_Type
7283 then
7284 raise Pragma_Exit;
7285 end if;
7287 -- We have a match if the corresponding argument is of the type
7288 -- given in the pragma (comparing base types)
7290 return Base_Type (Entity (Ptype)) = Ftyp;
7291 end if;
7292 end Same_Base_Type;
7294 -- Start of processing for
7295 -- Process_Extended_Import_Export_Subprogram_Pragma
7297 begin
7298 Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
7299 Ent := Empty;
7300 Ambiguous := False;
7302 -- Loop through homonyms (overloadings) of the entity
7304 Hom_Id := Entity (Arg_Internal);
7305 while Present (Hom_Id) loop
7306 Def_Id := Get_Base_Subprogram (Hom_Id);
7308 -- We need a subprogram in the current scope
7310 if not Is_Subprogram (Def_Id)
7311 or else Scope (Def_Id) /= Current_Scope
7312 then
7313 null;
7315 else
7316 Match := True;
7318 -- Pragma cannot apply to subprogram body
7320 if Is_Subprogram (Def_Id)
7321 and then Nkind (Parent (Declaration_Node (Def_Id))) =
7322 N_Subprogram_Body
7323 then
7324 Error_Pragma
7325 ("pragma% requires separate spec"
7326 & " and must come before body");
7327 end if;
7329 -- Test result type if given, note that the result type
7330 -- parameter can only be present for the function cases.
7332 if Present (Arg_Result_Type)
7333 and then not Same_Base_Type (Arg_Result_Type, Def_Id)
7334 then
7335 Match := False;
7337 elsif Etype (Def_Id) /= Standard_Void_Type
7338 and then
7339 Nam_In (Pname, Name_Export_Procedure, Name_Import_Procedure)
7340 then
7341 Match := False;
7343 -- Test parameter types if given. Note that this parameter
7344 -- has not been analyzed (and must not be, since it is
7345 -- semantic nonsense), so we get it as the parser left it.
7347 elsif Present (Arg_Parameter_Types) then
7348 Check_Matching_Types : declare
7349 Formal : Entity_Id;
7350 Ptype : Node_Id;
7352 begin
7353 Formal := First_Formal (Def_Id);
7355 if Nkind (Arg_Parameter_Types) = N_Null then
7356 if Present (Formal) then
7357 Match := False;
7358 end if;
7360 -- A list of one type, e.g. (List) is parsed as
7361 -- a parenthesized expression.
7363 elsif Nkind (Arg_Parameter_Types) /= N_Aggregate
7364 and then Paren_Count (Arg_Parameter_Types) = 1
7365 then
7366 if No (Formal)
7367 or else Present (Next_Formal (Formal))
7368 then
7369 Match := False;
7370 else
7371 Match :=
7372 Same_Base_Type (Arg_Parameter_Types, Formal);
7373 end if;
7375 -- A list of more than one type is parsed as a aggregate
7377 elsif Nkind (Arg_Parameter_Types) = N_Aggregate
7378 and then Paren_Count (Arg_Parameter_Types) = 0
7379 then
7380 Ptype := First (Expressions (Arg_Parameter_Types));
7381 while Present (Ptype) or else Present (Formal) loop
7382 if No (Ptype)
7383 or else No (Formal)
7384 or else not Same_Base_Type (Ptype, Formal)
7385 then
7386 Match := False;
7387 exit;
7388 else
7389 Next_Formal (Formal);
7390 Next (Ptype);
7391 end if;
7392 end loop;
7394 -- Anything else is of the wrong form
7396 else
7397 Error_Pragma_Arg
7398 ("wrong form for Parameter_Types parameter",
7399 Arg_Parameter_Types);
7400 end if;
7401 end Check_Matching_Types;
7402 end if;
7404 -- Match is now False if the entry we found did not match
7405 -- either a supplied Parameter_Types or Result_Types argument
7407 if Match then
7408 if No (Ent) then
7409 Ent := Def_Id;
7411 -- Ambiguous case, the flag Ambiguous shows if we already
7412 -- detected this and output the initial messages.
7414 else
7415 if not Ambiguous then
7416 Ambiguous := True;
7417 Error_Msg_Name_1 := Pname;
7418 Error_Msg_N
7419 ("pragma% does not uniquely identify subprogram!",
7421 Error_Msg_Sloc := Sloc (Ent);
7422 Error_Msg_N ("matching subprogram #!", N);
7423 Ent := Empty;
7424 end if;
7426 Error_Msg_Sloc := Sloc (Def_Id);
7427 Error_Msg_N ("matching subprogram #!", N);
7428 end if;
7429 end if;
7430 end if;
7432 Hom_Id := Homonym (Hom_Id);
7433 end loop;
7435 -- See if we found an entry
7437 if No (Ent) then
7438 if not Ambiguous then
7439 if Is_Generic_Subprogram (Entity (Arg_Internal)) then
7440 Error_Pragma
7441 ("pragma% cannot be given for generic subprogram");
7442 else
7443 Error_Pragma
7444 ("pragma% does not identify local subprogram");
7445 end if;
7446 end if;
7448 return;
7449 end if;
7451 -- Import pragmas must be for imported entities
7453 if Prag_Id = Pragma_Import_Function
7454 or else
7455 Prag_Id = Pragma_Import_Procedure
7456 or else
7457 Prag_Id = Pragma_Import_Valued_Procedure
7458 then
7459 if not Is_Imported (Ent) then
7460 Error_Pragma
7461 ("pragma Import or Interface must precede pragma%");
7462 end if;
7464 -- Here we have the Export case which can set the entity as exported
7466 -- But does not do so if the specified external name is null, since
7467 -- that is taken as a signal in DEC Ada 83 (with which we want to be
7468 -- compatible) to request no external name.
7470 elsif Nkind (Arg_External) = N_String_Literal
7471 and then String_Length (Strval (Arg_External)) = 0
7472 then
7473 null;
7475 -- In all other cases, set entity as exported
7477 else
7478 Set_Exported (Ent, Arg_Internal);
7479 end if;
7481 -- Special processing for Valued_Procedure cases
7483 if Prag_Id = Pragma_Import_Valued_Procedure
7484 or else
7485 Prag_Id = Pragma_Export_Valued_Procedure
7486 then
7487 Formal := First_Formal (Ent);
7489 if No (Formal) then
7490 Error_Pragma ("at least one parameter required for pragma%");
7492 elsif Ekind (Formal) /= E_Out_Parameter then
7493 Error_Pragma ("first parameter must have mode out for pragma%");
7495 else
7496 Set_Is_Valued_Procedure (Ent);
7497 end if;
7498 end if;
7500 Set_Extended_Import_Export_External_Name (Ent, Arg_External);
7502 -- Process Result_Mechanism argument if present. We have already
7503 -- checked that this is only allowed for the function case.
7505 if Present (Arg_Result_Mechanism) then
7506 Set_Mechanism_Value (Ent, Arg_Result_Mechanism);
7507 end if;
7509 -- Process Mechanism parameter if present. Note that this parameter
7510 -- is not analyzed, and must not be analyzed since it is semantic
7511 -- nonsense, so we get it in exactly as the parser left it.
7513 if Present (Arg_Mechanism) then
7514 declare
7515 Formal : Entity_Id;
7516 Massoc : Node_Id;
7517 Mname : Node_Id;
7518 Choice : Node_Id;
7520 begin
7521 -- A single mechanism association without a formal parameter
7522 -- name is parsed as a parenthesized expression. All other
7523 -- cases are parsed as aggregates, so we rewrite the single
7524 -- parameter case as an aggregate for consistency.
7526 if Nkind (Arg_Mechanism) /= N_Aggregate
7527 and then Paren_Count (Arg_Mechanism) = 1
7528 then
7529 Rewrite (Arg_Mechanism,
7530 Make_Aggregate (Sloc (Arg_Mechanism),
7531 Expressions => New_List (
7532 Relocate_Node (Arg_Mechanism))));
7533 end if;
7535 -- Case of only mechanism name given, applies to all formals
7537 if Nkind (Arg_Mechanism) /= N_Aggregate then
7538 Formal := First_Formal (Ent);
7539 while Present (Formal) loop
7540 Set_Mechanism_Value (Formal, Arg_Mechanism);
7541 Next_Formal (Formal);
7542 end loop;
7544 -- Case of list of mechanism associations given
7546 else
7547 if Null_Record_Present (Arg_Mechanism) then
7548 Error_Pragma_Arg
7549 ("inappropriate form for Mechanism parameter",
7550 Arg_Mechanism);
7551 end if;
7553 -- Deal with positional ones first
7555 Formal := First_Formal (Ent);
7557 if Present (Expressions (Arg_Mechanism)) then
7558 Mname := First (Expressions (Arg_Mechanism));
7559 while Present (Mname) loop
7560 if No (Formal) then
7561 Error_Pragma_Arg
7562 ("too many mechanism associations", Mname);
7563 end if;
7565 Set_Mechanism_Value (Formal, Mname);
7566 Next_Formal (Formal);
7567 Next (Mname);
7568 end loop;
7569 end if;
7571 -- Deal with named entries
7573 if Present (Component_Associations (Arg_Mechanism)) then
7574 Massoc := First (Component_Associations (Arg_Mechanism));
7575 while Present (Massoc) loop
7576 Choice := First (Choices (Massoc));
7578 if Nkind (Choice) /= N_Identifier
7579 or else Present (Next (Choice))
7580 then
7581 Error_Pragma_Arg
7582 ("incorrect form for mechanism association",
7583 Massoc);
7584 end if;
7586 Formal := First_Formal (Ent);
7587 loop
7588 if No (Formal) then
7589 Error_Pragma_Arg
7590 ("parameter name & not present", Choice);
7591 end if;
7593 if Chars (Choice) = Chars (Formal) then
7594 Set_Mechanism_Value
7595 (Formal, Expression (Massoc));
7597 -- Set entity on identifier (needed by ASIS)
7599 Set_Entity (Choice, Formal);
7601 exit;
7602 end if;
7604 Next_Formal (Formal);
7605 end loop;
7607 Next (Massoc);
7608 end loop;
7609 end if;
7610 end if;
7611 end;
7612 end if;
7613 end Process_Extended_Import_Export_Subprogram_Pragma;
7615 --------------------------
7616 -- Process_Generic_List --
7617 --------------------------
7619 procedure Process_Generic_List is
7620 Arg : Node_Id;
7621 Exp : Node_Id;
7623 begin
7624 Check_No_Identifiers;
7625 Check_At_Least_N_Arguments (1);
7627 -- Check all arguments are names of generic units or instances
7629 Arg := Arg1;
7630 while Present (Arg) loop
7631 Exp := Get_Pragma_Arg (Arg);
7632 Analyze (Exp);
7634 if not Is_Entity_Name (Exp)
7635 or else
7636 (not Is_Generic_Instance (Entity (Exp))
7637 and then
7638 not Is_Generic_Unit (Entity (Exp)))
7639 then
7640 Error_Pragma_Arg
7641 ("pragma% argument must be name of generic unit/instance",
7642 Arg);
7643 end if;
7645 Next (Arg);
7646 end loop;
7647 end Process_Generic_List;
7649 ------------------------------------
7650 -- Process_Import_Predefined_Type --
7651 ------------------------------------
7653 procedure Process_Import_Predefined_Type is
7654 Loc : constant Source_Ptr := Sloc (N);
7655 Elmt : Elmt_Id;
7656 Ftyp : Node_Id := Empty;
7657 Decl : Node_Id;
7658 Def : Node_Id;
7659 Nam : Name_Id;
7661 begin
7662 String_To_Name_Buffer (Strval (Expression (Arg3)));
7663 Nam := Name_Find;
7665 Elmt := First_Elmt (Predefined_Float_Types);
7666 while Present (Elmt) and then Chars (Node (Elmt)) /= Nam loop
7667 Next_Elmt (Elmt);
7668 end loop;
7670 Ftyp := Node (Elmt);
7672 if Present (Ftyp) then
7674 -- Don't build a derived type declaration, because predefined C
7675 -- types have no declaration anywhere, so cannot really be named.
7676 -- Instead build a full type declaration, starting with an
7677 -- appropriate type definition is built
7679 if Is_Floating_Point_Type (Ftyp) then
7680 Def := Make_Floating_Point_Definition (Loc,
7681 Make_Integer_Literal (Loc, Digits_Value (Ftyp)),
7682 Make_Real_Range_Specification (Loc,
7683 Make_Real_Literal (Loc, Realval (Type_Low_Bound (Ftyp))),
7684 Make_Real_Literal (Loc, Realval (Type_High_Bound (Ftyp)))));
7686 -- Should never have a predefined type we cannot handle
7688 else
7689 raise Program_Error;
7690 end if;
7692 -- Build and insert a Full_Type_Declaration, which will be
7693 -- analyzed as soon as this list entry has been analyzed.
7695 Decl := Make_Full_Type_Declaration (Loc,
7696 Make_Defining_Identifier (Loc, Chars (Expression (Arg2))),
7697 Type_Definition => Def);
7699 Insert_After (N, Decl);
7700 Mark_Rewrite_Insertion (Decl);
7702 else
7703 Error_Pragma_Arg ("no matching type found for pragma%",
7704 Arg2);
7705 end if;
7706 end Process_Import_Predefined_Type;
7708 ---------------------------------
7709 -- Process_Import_Or_Interface --
7710 ---------------------------------
7712 procedure Process_Import_Or_Interface is
7713 C : Convention_Id;
7714 Def_Id : Entity_Id;
7715 Hom_Id : Entity_Id;
7717 begin
7718 -- In Relaxed_RM_Semantics, support old Ada 83 style:
7719 -- pragma Import (Entity, "external name");
7721 if Relaxed_RM_Semantics
7722 and then Arg_Count = 2
7723 and then Prag_Id = Pragma_Import
7724 and then Nkind (Expression (Arg2)) = N_String_Literal
7725 then
7726 C := Convention_C;
7727 Def_Id := Get_Pragma_Arg (Arg1);
7728 Analyze (Def_Id);
7730 if not Is_Entity_Name (Def_Id) then
7731 Error_Pragma_Arg ("entity name required", Arg1);
7732 end if;
7734 Def_Id := Entity (Def_Id);
7735 Kill_Size_Check_Code (Def_Id);
7736 Note_Possible_Modification (Get_Pragma_Arg (Arg1), Sure => False);
7738 else
7739 Process_Convention (C, Def_Id);
7740 Kill_Size_Check_Code (Def_Id);
7741 Note_Possible_Modification (Get_Pragma_Arg (Arg2), Sure => False);
7742 end if;
7744 if Ekind_In (Def_Id, E_Variable, E_Constant) then
7746 -- We do not permit Import to apply to a renaming declaration
7748 if Present (Renamed_Object (Def_Id)) then
7749 Error_Pragma_Arg
7750 ("pragma% not allowed for object renaming", Arg2);
7752 -- User initialization is not allowed for imported object, but
7753 -- the object declaration may contain a default initialization,
7754 -- that will be discarded. Note that an explicit initialization
7755 -- only counts if it comes from source, otherwise it is simply
7756 -- the code generator making an implicit initialization explicit.
7758 elsif Present (Expression (Parent (Def_Id)))
7759 and then Comes_From_Source
7760 (Original_Node (Expression (Parent (Def_Id))))
7761 then
7762 -- Set imported flag to prevent cascaded errors
7764 Set_Is_Imported (Def_Id);
7766 Error_Msg_Sloc := Sloc (Def_Id);
7767 Error_Pragma_Arg
7768 ("no initialization allowed for declaration of& #",
7769 "\imported entities cannot be initialized (RM B.1(24))",
7770 Arg2);
7772 else
7773 -- If the pragma comes from an aspect specification the
7774 -- Is_Imported flag has already been set.
7776 if not From_Aspect_Specification (N) then
7777 Set_Imported (Def_Id);
7778 end if;
7780 Process_Interface_Name (Def_Id, Arg3, Arg4);
7782 -- Note that we do not set Is_Public here. That's because we
7783 -- only want to set it if there is no address clause, and we
7784 -- don't know that yet, so we delay that processing till
7785 -- freeze time.
7787 -- pragma Import completes deferred constants
7789 if Ekind (Def_Id) = E_Constant then
7790 Set_Has_Completion (Def_Id);
7791 end if;
7793 -- It is not possible to import a constant of an unconstrained
7794 -- array type (e.g. string) because there is no simple way to
7795 -- write a meaningful subtype for it.
7797 if Is_Array_Type (Etype (Def_Id))
7798 and then not Is_Constrained (Etype (Def_Id))
7799 then
7800 Error_Msg_NE
7801 ("imported constant& must have a constrained subtype",
7802 N, Def_Id);
7803 end if;
7804 end if;
7806 elsif Is_Subprogram_Or_Generic_Subprogram (Def_Id) then
7808 -- If the name is overloaded, pragma applies to all of the denoted
7809 -- entities in the same declarative part, unless the pragma comes
7810 -- from an aspect specification or was generated by the compiler
7811 -- (such as for pragma Provide_Shift_Operators).
7813 Hom_Id := Def_Id;
7814 while Present (Hom_Id) loop
7816 Def_Id := Get_Base_Subprogram (Hom_Id);
7818 -- Ignore inherited subprograms because the pragma will apply
7819 -- to the parent operation, which is the one called.
7821 if Is_Overloadable (Def_Id)
7822 and then Present (Alias (Def_Id))
7823 then
7824 null;
7826 -- If it is not a subprogram, it must be in an outer scope and
7827 -- pragma does not apply.
7829 elsif not Is_Subprogram_Or_Generic_Subprogram (Def_Id) then
7830 null;
7832 -- The pragma does not apply to primitives of interfaces
7834 elsif Is_Dispatching_Operation (Def_Id)
7835 and then Present (Find_Dispatching_Type (Def_Id))
7836 and then Is_Interface (Find_Dispatching_Type (Def_Id))
7837 then
7838 null;
7840 -- Verify that the homonym is in the same declarative part (not
7841 -- just the same scope). If the pragma comes from an aspect
7842 -- specification we know that it is part of the declaration.
7844 elsif Parent (Unit_Declaration_Node (Def_Id)) /= Parent (N)
7845 and then Nkind (Parent (N)) /= N_Compilation_Unit_Aux
7846 and then not From_Aspect_Specification (N)
7847 then
7848 exit;
7850 else
7851 -- If the pragma comes from an aspect specification the
7852 -- Is_Imported flag has already been set.
7854 if not From_Aspect_Specification (N) then
7855 Set_Imported (Def_Id);
7856 end if;
7858 -- Reject an Import applied to an abstract subprogram
7860 if Is_Subprogram (Def_Id)
7861 and then Is_Abstract_Subprogram (Def_Id)
7862 then
7863 Error_Msg_Sloc := Sloc (Def_Id);
7864 Error_Msg_NE
7865 ("cannot import abstract subprogram& declared#",
7866 Arg2, Def_Id);
7867 end if;
7869 -- Special processing for Convention_Intrinsic
7871 if C = Convention_Intrinsic then
7873 -- Link_Name argument not allowed for intrinsic
7875 Check_No_Link_Name;
7877 Set_Is_Intrinsic_Subprogram (Def_Id);
7879 -- If no external name is present, then check that this
7880 -- is a valid intrinsic subprogram. If an external name
7881 -- is present, then this is handled by the back end.
7883 if No (Arg3) then
7884 Check_Intrinsic_Subprogram
7885 (Def_Id, Get_Pragma_Arg (Arg2));
7886 end if;
7887 end if;
7889 -- Verify that the subprogram does not have a completion
7890 -- through a renaming declaration. For other completions the
7891 -- pragma appears as a too late representation.
7893 declare
7894 Decl : constant Node_Id := Unit_Declaration_Node (Def_Id);
7896 begin
7897 if Present (Decl)
7898 and then Nkind (Decl) = N_Subprogram_Declaration
7899 and then Present (Corresponding_Body (Decl))
7900 and then Nkind (Unit_Declaration_Node
7901 (Corresponding_Body (Decl))) =
7902 N_Subprogram_Renaming_Declaration
7903 then
7904 Error_Msg_Sloc := Sloc (Def_Id);
7905 Error_Msg_NE
7906 ("cannot import&, renaming already provided for "
7907 & "declaration #", N, Def_Id);
7908 end if;
7909 end;
7911 -- If the pragma comes from an aspect specification, there
7912 -- must be an Import aspect specified as well. In the rare
7913 -- case where Import is set to False, the suprogram needs to
7914 -- have a local completion.
7916 declare
7917 Imp_Aspect : constant Node_Id :=
7918 Find_Aspect (Def_Id, Aspect_Import);
7919 Expr : Node_Id;
7921 begin
7922 if Present (Imp_Aspect)
7923 and then Present (Expression (Imp_Aspect))
7924 then
7925 Expr := Expression (Imp_Aspect);
7926 Analyze_And_Resolve (Expr, Standard_Boolean);
7928 if Is_Entity_Name (Expr)
7929 and then Entity (Expr) = Standard_True
7930 then
7931 Set_Has_Completion (Def_Id);
7932 end if;
7934 -- If there is no expression, the default is True, as for
7935 -- all boolean aspects. Same for the older pragma.
7937 else
7938 Set_Has_Completion (Def_Id);
7939 end if;
7940 end;
7942 Process_Interface_Name (Def_Id, Arg3, Arg4);
7943 end if;
7945 if Is_Compilation_Unit (Hom_Id) then
7947 -- Its possible homonyms are not affected by the pragma.
7948 -- Such homonyms might be present in the context of other
7949 -- units being compiled.
7951 exit;
7953 elsif From_Aspect_Specification (N) then
7954 exit;
7956 -- If the pragma was created by the compiler, then we don't
7957 -- want it to apply to other homonyms. This kind of case can
7958 -- occur when using pragma Provide_Shift_Operators, which
7959 -- generates implicit shift and rotate operators with Import
7960 -- pragmas that might apply to earlier explicit or implicit
7961 -- declarations marked with Import (for example, coming from
7962 -- an earlier pragma Provide_Shift_Operators for another type),
7963 -- and we don't generally want other homonyms being treated
7964 -- as imported or the pragma flagged as an illegal duplicate.
7966 elsif not Comes_From_Source (N) then
7967 exit;
7969 else
7970 Hom_Id := Homonym (Hom_Id);
7971 end if;
7972 end loop;
7974 -- When the convention is Java or CIL, we also allow Import to
7975 -- be given for packages, generic packages, exceptions, record
7976 -- components, and access to subprograms.
7978 elsif (C = Convention_Java or else C = Convention_CIL)
7979 and then
7980 (Is_Package_Or_Generic_Package (Def_Id)
7981 or else Ekind (Def_Id) = E_Exception
7982 or else Ekind (Def_Id) = E_Access_Subprogram_Type
7983 or else Nkind (Parent (Def_Id)) = N_Component_Declaration)
7984 then
7985 Set_Imported (Def_Id);
7986 Set_Is_Public (Def_Id);
7987 Process_Interface_Name (Def_Id, Arg3, Arg4);
7989 -- Import a CPP class
7991 elsif C = Convention_CPP
7992 and then (Is_Record_Type (Def_Id)
7993 or else Ekind (Def_Id) = E_Incomplete_Type)
7994 then
7995 if Ekind (Def_Id) = E_Incomplete_Type then
7996 if Present (Full_View (Def_Id)) then
7997 Def_Id := Full_View (Def_Id);
7999 else
8000 Error_Msg_N
8001 ("cannot import 'C'P'P type before full declaration seen",
8002 Get_Pragma_Arg (Arg2));
8004 -- Although we have reported the error we decorate it as
8005 -- CPP_Class to avoid reporting spurious errors
8007 Set_Is_CPP_Class (Def_Id);
8008 return;
8009 end if;
8010 end if;
8012 -- Types treated as CPP classes must be declared limited (note:
8013 -- this used to be a warning but there is no real benefit to it
8014 -- since we did effectively intend to treat the type as limited
8015 -- anyway).
8017 if not Is_Limited_Type (Def_Id) then
8018 Error_Msg_N
8019 ("imported 'C'P'P type must be limited",
8020 Get_Pragma_Arg (Arg2));
8021 end if;
8023 if Etype (Def_Id) /= Def_Id
8024 and then not Is_CPP_Class (Root_Type (Def_Id))
8025 then
8026 Error_Msg_N ("root type must be a 'C'P'P type", Arg1);
8027 end if;
8029 Set_Is_CPP_Class (Def_Id);
8031 -- Imported CPP types must not have discriminants (because C++
8032 -- classes do not have discriminants).
8034 if Has_Discriminants (Def_Id) then
8035 Error_Msg_N
8036 ("imported 'C'P'P type cannot have discriminants",
8037 First (Discriminant_Specifications
8038 (Declaration_Node (Def_Id))));
8039 end if;
8041 -- Check that components of imported CPP types do not have default
8042 -- expressions. For private types this check is performed when the
8043 -- full view is analyzed (see Process_Full_View).
8045 if not Is_Private_Type (Def_Id) then
8046 Check_CPP_Type_Has_No_Defaults (Def_Id);
8047 end if;
8049 -- Import a CPP exception
8051 elsif C = Convention_CPP
8052 and then Ekind (Def_Id) = E_Exception
8053 then
8054 if No (Arg3) then
8055 Error_Pragma_Arg
8056 ("'External_'Name arguments is required for 'Cpp exception",
8057 Arg3);
8058 else
8059 -- As only a string is allowed, Check_Arg_Is_External_Name
8060 -- isn't called.
8062 Check_Arg_Is_OK_Static_Expression (Arg3, Standard_String);
8063 end if;
8065 if Present (Arg4) then
8066 Error_Pragma_Arg
8067 ("Link_Name argument not allowed for imported Cpp exception",
8068 Arg4);
8069 end if;
8071 -- Do not call Set_Interface_Name as the name of the exception
8072 -- shouldn't be modified (and in particular it shouldn't be
8073 -- the External_Name). For exceptions, the External_Name is the
8074 -- name of the RTTI structure.
8076 -- ??? Emit an error if pragma Import/Export_Exception is present
8078 elsif Nkind (Parent (Def_Id)) = N_Incomplete_Type_Declaration then
8079 Check_No_Link_Name;
8080 Check_Arg_Count (3);
8081 Check_Arg_Is_OK_Static_Expression (Arg3, Standard_String);
8083 Process_Import_Predefined_Type;
8085 else
8086 Error_Pragma_Arg
8087 ("second argument of pragma% must be object, subprogram "
8088 & "or incomplete type",
8089 Arg2);
8090 end if;
8092 -- If this pragma applies to a compilation unit, then the unit, which
8093 -- is a subprogram, does not require (or allow) a body. We also do
8094 -- not need to elaborate imported procedures.
8096 if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
8097 declare
8098 Cunit : constant Node_Id := Parent (Parent (N));
8099 begin
8100 Set_Body_Required (Cunit, False);
8101 end;
8102 end if;
8103 end Process_Import_Or_Interface;
8105 --------------------
8106 -- Process_Inline --
8107 --------------------
8109 procedure Process_Inline (Status : Inline_Status) is
8110 Assoc : Node_Id;
8111 Decl : Node_Id;
8112 Subp_Id : Node_Id;
8113 Subp : Entity_Id;
8114 Applies : Boolean;
8116 procedure Make_Inline (Subp : Entity_Id);
8117 -- Subp is the defining unit name of the subprogram declaration. Set
8118 -- the flag, as well as the flag in the corresponding body, if there
8119 -- is one present.
8121 procedure Set_Inline_Flags (Subp : Entity_Id);
8122 -- Sets Is_Inlined and Has_Pragma_Inline flags for Subp and also
8123 -- Has_Pragma_Inline_Always for the Inline_Always case.
8125 function Inlining_Not_Possible (Subp : Entity_Id) return Boolean;
8126 -- Returns True if it can be determined at this stage that inlining
8127 -- is not possible, for example if the body is available and contains
8128 -- exception handlers, we prevent inlining, since otherwise we can
8129 -- get undefined symbols at link time. This function also emits a
8130 -- warning if front-end inlining is enabled and the pragma appears
8131 -- too late.
8133 -- ??? is business with link symbols still valid, or does it relate
8134 -- to front end ZCX which is being phased out ???
8136 ---------------------------
8137 -- Inlining_Not_Possible --
8138 ---------------------------
8140 function Inlining_Not_Possible (Subp : Entity_Id) return Boolean is
8141 Decl : constant Node_Id := Unit_Declaration_Node (Subp);
8142 Stats : Node_Id;
8144 begin
8145 if Nkind (Decl) = N_Subprogram_Body then
8146 Stats := Handled_Statement_Sequence (Decl);
8147 return Present (Exception_Handlers (Stats))
8148 or else Present (At_End_Proc (Stats));
8150 elsif Nkind (Decl) = N_Subprogram_Declaration
8151 and then Present (Corresponding_Body (Decl))
8152 then
8153 if Front_End_Inlining
8154 and then Analyzed (Corresponding_Body (Decl))
8155 then
8156 Error_Msg_N ("pragma appears too late, ignored??", N);
8157 return True;
8159 -- If the subprogram is a renaming as body, the body is just a
8160 -- call to the renamed subprogram, and inlining is trivially
8161 -- possible.
8163 elsif
8164 Nkind (Unit_Declaration_Node (Corresponding_Body (Decl))) =
8165 N_Subprogram_Renaming_Declaration
8166 then
8167 return False;
8169 else
8170 Stats :=
8171 Handled_Statement_Sequence
8172 (Unit_Declaration_Node (Corresponding_Body (Decl)));
8174 return
8175 Present (Exception_Handlers (Stats))
8176 or else Present (At_End_Proc (Stats));
8177 end if;
8179 else
8180 -- If body is not available, assume the best, the check is
8181 -- performed again when compiling enclosing package bodies.
8183 return False;
8184 end if;
8185 end Inlining_Not_Possible;
8187 -----------------
8188 -- Make_Inline --
8189 -----------------
8191 procedure Make_Inline (Subp : Entity_Id) is
8192 Kind : constant Entity_Kind := Ekind (Subp);
8193 Inner_Subp : Entity_Id := Subp;
8195 begin
8196 -- Ignore if bad type, avoid cascaded error
8198 if Etype (Subp) = Any_Type then
8199 Applies := True;
8200 return;
8202 -- Ignore if all inlining is suppressed
8204 elsif Suppress_All_Inlining then
8205 Applies := True;
8206 return;
8208 -- If inlining is not possible, for now do not treat as an error
8210 elsif Status /= Suppressed
8211 and then Inlining_Not_Possible (Subp)
8212 then
8213 Applies := True;
8214 return;
8216 -- Here we have a candidate for inlining, but we must exclude
8217 -- derived operations. Otherwise we would end up trying to inline
8218 -- a phantom declaration, and the result would be to drag in a
8219 -- body which has no direct inlining associated with it. That
8220 -- would not only be inefficient but would also result in the
8221 -- backend doing cross-unit inlining in cases where it was
8222 -- definitely inappropriate to do so.
8224 -- However, a simple Comes_From_Source test is insufficient, since
8225 -- we do want to allow inlining of generic instances which also do
8226 -- not come from source. We also need to recognize specs generated
8227 -- by the front-end for bodies that carry the pragma. Finally,
8228 -- predefined operators do not come from source but are not
8229 -- inlineable either.
8231 elsif Is_Generic_Instance (Subp)
8232 or else Nkind (Parent (Parent (Subp))) = N_Subprogram_Declaration
8233 then
8234 null;
8236 elsif not Comes_From_Source (Subp)
8237 and then Scope (Subp) /= Standard_Standard
8238 then
8239 Applies := True;
8240 return;
8241 end if;
8243 -- The referenced entity must either be the enclosing entity, or
8244 -- an entity declared within the current open scope.
8246 if Present (Scope (Subp))
8247 and then Scope (Subp) /= Current_Scope
8248 and then Subp /= Current_Scope
8249 then
8250 Error_Pragma_Arg
8251 ("argument of% must be entity in current scope", Assoc);
8252 return;
8253 end if;
8255 -- Processing for procedure, operator or function. If subprogram
8256 -- is aliased (as for an instance) indicate that the renamed
8257 -- entity (if declared in the same unit) is inlined.
8259 if Is_Subprogram (Subp) then
8260 Inner_Subp := Ultimate_Alias (Inner_Subp);
8262 if In_Same_Source_Unit (Subp, Inner_Subp) then
8263 Set_Inline_Flags (Inner_Subp);
8265 Decl := Parent (Parent (Inner_Subp));
8267 if Nkind (Decl) = N_Subprogram_Declaration
8268 and then Present (Corresponding_Body (Decl))
8269 then
8270 Set_Inline_Flags (Corresponding_Body (Decl));
8272 elsif Is_Generic_Instance (Subp) then
8274 -- Indicate that the body needs to be created for
8275 -- inlining subsequent calls. The instantiation node
8276 -- follows the declaration of the wrapper package
8277 -- created for it.
8279 if Scope (Subp) /= Standard_Standard
8280 and then
8281 Need_Subprogram_Instance_Body
8282 (Next (Unit_Declaration_Node (Scope (Alias (Subp)))),
8283 Subp)
8284 then
8285 null;
8286 end if;
8288 -- Inline is a program unit pragma (RM 10.1.5) and cannot
8289 -- appear in a formal part to apply to a formal subprogram.
8290 -- Do not apply check within an instance or a formal package
8291 -- the test will have been applied to the original generic.
8293 elsif Nkind (Decl) in N_Formal_Subprogram_Declaration
8294 and then List_Containing (Decl) = List_Containing (N)
8295 and then not In_Instance
8296 then
8297 Error_Msg_N
8298 ("Inline cannot apply to a formal subprogram", N);
8300 -- If Subp is a renaming, it is the renamed entity that
8301 -- will appear in any call, and be inlined. However, for
8302 -- ASIS uses it is convenient to indicate that the renaming
8303 -- itself is an inlined subprogram, so that some gnatcheck
8304 -- rules can be applied in the absence of expansion.
8306 elsif Nkind (Decl) = N_Subprogram_Renaming_Declaration then
8307 Set_Inline_Flags (Subp);
8308 end if;
8309 end if;
8311 Applies := True;
8313 -- For a generic subprogram set flag as well, for use at the point
8314 -- of instantiation, to determine whether the body should be
8315 -- generated.
8317 elsif Is_Generic_Subprogram (Subp) then
8318 Set_Inline_Flags (Subp);
8319 Applies := True;
8321 -- Literals are by definition inlined
8323 elsif Kind = E_Enumeration_Literal then
8324 null;
8326 -- Anything else is an error
8328 else
8329 Error_Pragma_Arg
8330 ("expect subprogram name for pragma%", Assoc);
8331 end if;
8332 end Make_Inline;
8334 ----------------------
8335 -- Set_Inline_Flags --
8336 ----------------------
8338 procedure Set_Inline_Flags (Subp : Entity_Id) is
8339 begin
8340 -- First set the Has_Pragma_XXX flags and issue the appropriate
8341 -- errors and warnings for suspicious combinations.
8343 if Prag_Id = Pragma_No_Inline then
8344 if Has_Pragma_Inline_Always (Subp) then
8345 Error_Msg_N
8346 ("Inline_Always and No_Inline are mutually exclusive", N);
8347 elsif Has_Pragma_Inline (Subp) then
8348 Error_Msg_NE
8349 ("Inline and No_Inline both specified for& ??",
8350 N, Entity (Subp_Id));
8351 end if;
8353 Set_Has_Pragma_No_Inline (Subp);
8354 else
8355 if Prag_Id = Pragma_Inline_Always then
8356 if Has_Pragma_No_Inline (Subp) then
8357 Error_Msg_N
8358 ("Inline_Always and No_Inline are mutually exclusive",
8360 end if;
8362 Set_Has_Pragma_Inline_Always (Subp);
8363 else
8364 if Has_Pragma_No_Inline (Subp) then
8365 Error_Msg_NE
8366 ("Inline and No_Inline both specified for& ??",
8367 N, Entity (Subp_Id));
8368 end if;
8369 end if;
8371 if not Has_Pragma_Inline (Subp) then
8372 Set_Has_Pragma_Inline (Subp);
8373 end if;
8374 end if;
8376 -- Then adjust the Is_Inlined flag. It can never be set if the
8377 -- subprogram is subject to pragma No_Inline.
8379 case Status is
8380 when Suppressed =>
8381 Set_Is_Inlined (Subp, False);
8382 when Disabled =>
8383 null;
8384 when Enabled =>
8385 if not Has_Pragma_No_Inline (Subp) then
8386 Set_Is_Inlined (Subp, True);
8387 end if;
8388 end case;
8389 end Set_Inline_Flags;
8391 -- Start of processing for Process_Inline
8393 begin
8394 Check_No_Identifiers;
8395 Check_At_Least_N_Arguments (1);
8397 if Status = Enabled then
8398 Inline_Processing_Required := True;
8399 end if;
8401 Assoc := Arg1;
8402 while Present (Assoc) loop
8403 Subp_Id := Get_Pragma_Arg (Assoc);
8404 Analyze (Subp_Id);
8405 Applies := False;
8407 if Is_Entity_Name (Subp_Id) then
8408 Subp := Entity (Subp_Id);
8410 if Subp = Any_Id then
8412 -- If previous error, avoid cascaded errors
8414 Check_Error_Detected;
8415 Applies := True;
8417 else
8418 Make_Inline (Subp);
8420 -- For the pragma case, climb homonym chain. This is
8421 -- what implements allowing the pragma in the renaming
8422 -- case, with the result applying to the ancestors, and
8423 -- also allows Inline to apply to all previous homonyms.
8425 if not From_Aspect_Specification (N) then
8426 while Present (Homonym (Subp))
8427 and then Scope (Homonym (Subp)) = Current_Scope
8428 loop
8429 Make_Inline (Homonym (Subp));
8430 Subp := Homonym (Subp);
8431 end loop;
8432 end if;
8433 end if;
8434 end if;
8436 if not Applies then
8437 Error_Pragma_Arg
8438 ("inappropriate argument for pragma%", Assoc);
8439 end if;
8441 Next (Assoc);
8442 end loop;
8443 end Process_Inline;
8445 ----------------------------
8446 -- Process_Interface_Name --
8447 ----------------------------
8449 procedure Process_Interface_Name
8450 (Subprogram_Def : Entity_Id;
8451 Ext_Arg : Node_Id;
8452 Link_Arg : Node_Id)
8454 Ext_Nam : Node_Id;
8455 Link_Nam : Node_Id;
8456 String_Val : String_Id;
8458 procedure Check_Form_Of_Interface_Name
8459 (SN : Node_Id;
8460 Ext_Name_Case : Boolean);
8461 -- SN is a string literal node for an interface name. This routine
8462 -- performs some minimal checks that the name is reasonable. In
8463 -- particular that no spaces or other obviously incorrect characters
8464 -- appear. This is only a warning, since any characters are allowed.
8465 -- Ext_Name_Case is True for an External_Name, False for a Link_Name.
8467 ----------------------------------
8468 -- Check_Form_Of_Interface_Name --
8469 ----------------------------------
8471 procedure Check_Form_Of_Interface_Name
8472 (SN : Node_Id;
8473 Ext_Name_Case : Boolean)
8475 S : constant String_Id := Strval (Expr_Value_S (SN));
8476 SL : constant Nat := String_Length (S);
8477 C : Char_Code;
8479 begin
8480 if SL = 0 then
8481 Error_Msg_N ("interface name cannot be null string", SN);
8482 end if;
8484 for J in 1 .. SL loop
8485 C := Get_String_Char (S, J);
8487 -- Look for dubious character and issue unconditional warning.
8488 -- Definitely dubious if not in character range.
8490 if not In_Character_Range (C)
8492 -- For all cases except CLI target,
8493 -- commas, spaces and slashes are dubious (in CLI, we use
8494 -- commas and backslashes in external names to specify
8495 -- assembly version and public key, while slashes and spaces
8496 -- can be used in names to mark nested classes and
8497 -- valuetypes).
8499 or else ((not Ext_Name_Case or else VM_Target /= CLI_Target)
8500 and then (Get_Character (C) = ','
8501 or else
8502 Get_Character (C) = '\'))
8503 or else (VM_Target /= CLI_Target
8504 and then (Get_Character (C) = ' '
8505 or else
8506 Get_Character (C) = '/'))
8507 then
8508 Error_Msg
8509 ("??interface name contains illegal character",
8510 Sloc (SN) + Source_Ptr (J));
8511 end if;
8512 end loop;
8513 end Check_Form_Of_Interface_Name;
8515 -- Start of processing for Process_Interface_Name
8517 begin
8518 if No (Link_Arg) then
8519 if No (Ext_Arg) then
8520 if VM_Target = CLI_Target
8521 and then Ekind (Subprogram_Def) = E_Package
8522 and then Nkind (Parent (Subprogram_Def)) =
8523 N_Package_Specification
8524 and then Present (Generic_Parent (Parent (Subprogram_Def)))
8525 then
8526 Set_Interface_Name
8527 (Subprogram_Def,
8528 Interface_Name
8529 (Generic_Parent (Parent (Subprogram_Def))));
8530 end if;
8532 return;
8534 elsif Chars (Ext_Arg) = Name_Link_Name then
8535 Ext_Nam := Empty;
8536 Link_Nam := Expression (Ext_Arg);
8538 else
8539 Check_Optional_Identifier (Ext_Arg, Name_External_Name);
8540 Ext_Nam := Expression (Ext_Arg);
8541 Link_Nam := Empty;
8542 end if;
8544 else
8545 Check_Optional_Identifier (Ext_Arg, Name_External_Name);
8546 Check_Optional_Identifier (Link_Arg, Name_Link_Name);
8547 Ext_Nam := Expression (Ext_Arg);
8548 Link_Nam := Expression (Link_Arg);
8549 end if;
8551 -- Check expressions for external name and link name are static
8553 if Present (Ext_Nam) then
8554 Check_Arg_Is_OK_Static_Expression (Ext_Nam, Standard_String);
8555 Check_Form_Of_Interface_Name (Ext_Nam, Ext_Name_Case => True);
8557 -- Verify that external name is not the name of a local entity,
8558 -- which would hide the imported one and could lead to run-time
8559 -- surprises. The problem can only arise for entities declared in
8560 -- a package body (otherwise the external name is fully qualified
8561 -- and will not conflict).
8563 declare
8564 Nam : Name_Id;
8565 E : Entity_Id;
8566 Par : Node_Id;
8568 begin
8569 if Prag_Id = Pragma_Import then
8570 String_To_Name_Buffer (Strval (Expr_Value_S (Ext_Nam)));
8571 Nam := Name_Find;
8572 E := Entity_Id (Get_Name_Table_Int (Nam));
8574 if Nam /= Chars (Subprogram_Def)
8575 and then Present (E)
8576 and then not Is_Overloadable (E)
8577 and then Is_Immediately_Visible (E)
8578 and then not Is_Imported (E)
8579 and then Ekind (Scope (E)) = E_Package
8580 then
8581 Par := Parent (E);
8582 while Present (Par) loop
8583 if Nkind (Par) = N_Package_Body then
8584 Error_Msg_Sloc := Sloc (E);
8585 Error_Msg_NE
8586 ("imported entity is hidden by & declared#",
8587 Ext_Arg, E);
8588 exit;
8589 end if;
8591 Par := Parent (Par);
8592 end loop;
8593 end if;
8594 end if;
8595 end;
8596 end if;
8598 if Present (Link_Nam) then
8599 Check_Arg_Is_OK_Static_Expression (Link_Nam, Standard_String);
8600 Check_Form_Of_Interface_Name (Link_Nam, Ext_Name_Case => False);
8601 end if;
8603 -- If there is no link name, just set the external name
8605 if No (Link_Nam) then
8606 Link_Nam := Adjust_External_Name_Case (Expr_Value_S (Ext_Nam));
8608 -- For the Link_Name case, the given literal is preceded by an
8609 -- asterisk, which indicates to GCC that the given name should be
8610 -- taken literally, and in particular that no prepending of
8611 -- underlines should occur, even in systems where this is the
8612 -- normal default.
8614 else
8615 Start_String;
8617 if VM_Target = No_VM then
8618 Store_String_Char (Get_Char_Code ('*'));
8619 end if;
8621 String_Val := Strval (Expr_Value_S (Link_Nam));
8622 Store_String_Chars (String_Val);
8623 Link_Nam :=
8624 Make_String_Literal (Sloc (Link_Nam),
8625 Strval => End_String);
8626 end if;
8628 -- Set the interface name. If the entity is a generic instance, use
8629 -- its alias, which is the callable entity.
8631 if Is_Generic_Instance (Subprogram_Def) then
8632 Set_Encoded_Interface_Name
8633 (Alias (Get_Base_Subprogram (Subprogram_Def)), Link_Nam);
8634 else
8635 Set_Encoded_Interface_Name
8636 (Get_Base_Subprogram (Subprogram_Def), Link_Nam);
8637 end if;
8639 -- We allow duplicated export names in CIL/Java, as they are always
8640 -- enclosed in a namespace that differentiates them, and overloaded
8641 -- entities are supported by the VM.
8643 if Convention (Subprogram_Def) /= Convention_CIL
8644 and then
8645 Convention (Subprogram_Def) /= Convention_Java
8646 then
8647 Check_Duplicated_Export_Name (Link_Nam);
8648 end if;
8649 end Process_Interface_Name;
8651 -----------------------------------------
8652 -- Process_Interrupt_Or_Attach_Handler --
8653 -----------------------------------------
8655 procedure Process_Interrupt_Or_Attach_Handler is
8656 Arg1_X : constant Node_Id := Get_Pragma_Arg (Arg1);
8657 Handler_Proc : constant Entity_Id := Entity (Arg1_X);
8658 Proc_Scope : constant Entity_Id := Scope (Handler_Proc);
8660 begin
8661 Set_Is_Interrupt_Handler (Handler_Proc);
8663 -- If the pragma is not associated with a handler procedure within a
8664 -- protected type, then it must be for a nonprotected procedure for
8665 -- the AAMP target, in which case we don't associate a representation
8666 -- item with the procedure's scope.
8668 if Ekind (Proc_Scope) = E_Protected_Type then
8669 if Prag_Id = Pragma_Interrupt_Handler
8670 or else
8671 Prag_Id = Pragma_Attach_Handler
8672 then
8673 Record_Rep_Item (Proc_Scope, N);
8674 end if;
8675 end if;
8676 end Process_Interrupt_Or_Attach_Handler;
8678 --------------------------------------------------
8679 -- Process_Restrictions_Or_Restriction_Warnings --
8680 --------------------------------------------------
8682 -- Note: some of the simple identifier cases were handled in par-prag,
8683 -- but it is harmless (and more straightforward) to simply handle all
8684 -- cases here, even if it means we repeat a bit of work in some cases.
8686 procedure Process_Restrictions_Or_Restriction_Warnings
8687 (Warn : Boolean)
8689 Arg : Node_Id;
8690 R_Id : Restriction_Id;
8691 Id : Name_Id;
8692 Expr : Node_Id;
8693 Val : Uint;
8695 begin
8696 -- Ignore all Restrictions pragmas in CodePeer mode
8698 if CodePeer_Mode then
8699 return;
8700 end if;
8702 Check_Ada_83_Warning;
8703 Check_At_Least_N_Arguments (1);
8704 Check_Valid_Configuration_Pragma;
8706 Arg := Arg1;
8707 while Present (Arg) loop
8708 Id := Chars (Arg);
8709 Expr := Get_Pragma_Arg (Arg);
8711 -- Case of no restriction identifier present
8713 if Id = No_Name then
8714 if Nkind (Expr) /= N_Identifier then
8715 Error_Pragma_Arg
8716 ("invalid form for restriction", Arg);
8717 end if;
8719 R_Id :=
8720 Get_Restriction_Id
8721 (Process_Restriction_Synonyms (Expr));
8723 if R_Id not in All_Boolean_Restrictions then
8724 Error_Msg_Name_1 := Pname;
8725 Error_Msg_N
8726 ("invalid restriction identifier&", Get_Pragma_Arg (Arg));
8728 -- Check for possible misspelling
8730 for J in Restriction_Id loop
8731 declare
8732 Rnm : constant String := Restriction_Id'Image (J);
8734 begin
8735 Name_Buffer (1 .. Rnm'Length) := Rnm;
8736 Name_Len := Rnm'Length;
8737 Set_Casing (All_Lower_Case);
8739 if Is_Bad_Spelling_Of (Chars (Expr), Name_Enter) then
8740 Set_Casing
8741 (Identifier_Casing (Current_Source_File));
8742 Error_Msg_String (1 .. Rnm'Length) :=
8743 Name_Buffer (1 .. Name_Len);
8744 Error_Msg_Strlen := Rnm'Length;
8745 Error_Msg_N -- CODEFIX
8746 ("\possible misspelling of ""~""",
8747 Get_Pragma_Arg (Arg));
8748 exit;
8749 end if;
8750 end;
8751 end loop;
8753 raise Pragma_Exit;
8754 end if;
8756 if Implementation_Restriction (R_Id) then
8757 Check_Restriction (No_Implementation_Restrictions, Arg);
8758 end if;
8760 -- Special processing for No_Elaboration_Code restriction
8762 if R_Id = No_Elaboration_Code then
8764 -- Restriction is only recognized within a configuration
8765 -- pragma file, or within a unit of the main extended
8766 -- program. Note: the test for Main_Unit is needed to
8767 -- properly include the case of configuration pragma files.
8769 if not (Current_Sem_Unit = Main_Unit
8770 or else In_Extended_Main_Source_Unit (N))
8771 then
8772 return;
8774 -- Don't allow in a subunit unless already specified in
8775 -- body or spec.
8777 elsif Nkind (Parent (N)) = N_Compilation_Unit
8778 and then Nkind (Unit (Parent (N))) = N_Subunit
8779 and then not Restriction_Active (No_Elaboration_Code)
8780 then
8781 Error_Msg_N
8782 ("invalid specification of ""No_Elaboration_Code""",
8784 Error_Msg_N
8785 ("\restriction cannot be specified in a subunit", N);
8786 Error_Msg_N
8787 ("\unless also specified in body or spec", N);
8788 return;
8790 -- If we accept a No_Elaboration_Code restriction, then it
8791 -- needs to be added to the configuration restriction set so
8792 -- that we get proper application to other units in the main
8793 -- extended source as required.
8795 else
8796 Add_To_Config_Boolean_Restrictions (No_Elaboration_Code);
8797 end if;
8798 end if;
8800 -- If this is a warning, then set the warning unless we already
8801 -- have a real restriction active (we never want a warning to
8802 -- override a real restriction).
8804 if Warn then
8805 if not Restriction_Active (R_Id) then
8806 Set_Restriction (R_Id, N);
8807 Restriction_Warnings (R_Id) := True;
8808 end if;
8810 -- If real restriction case, then set it and make sure that the
8811 -- restriction warning flag is off, since a real restriction
8812 -- always overrides a warning.
8814 else
8815 Set_Restriction (R_Id, N);
8816 Restriction_Warnings (R_Id) := False;
8817 end if;
8819 -- Check for obsolescent restrictions in Ada 2005 mode
8821 if not Warn
8822 and then Ada_Version >= Ada_2005
8823 and then (R_Id = No_Asynchronous_Control
8824 or else
8825 R_Id = No_Unchecked_Deallocation
8826 or else
8827 R_Id = No_Unchecked_Conversion)
8828 then
8829 Check_Restriction (No_Obsolescent_Features, N);
8830 end if;
8832 -- A very special case that must be processed here: pragma
8833 -- Restrictions (No_Exceptions) turns off all run-time
8834 -- checking. This is a bit dubious in terms of the formal
8835 -- language definition, but it is what is intended by RM
8836 -- H.4(12). Restriction_Warnings never affects generated code
8837 -- so this is done only in the real restriction case.
8839 -- Atomic_Synchronization is not a real check, so it is not
8840 -- affected by this processing).
8842 -- Ignore the effect of pragma Restrictions (No_Exceptions) on
8843 -- run-time checks in CodePeer and GNATprove modes: we want to
8844 -- generate checks for analysis purposes, as set respectively
8845 -- by -gnatC and -gnatd.F
8847 if not Warn
8848 and then not (CodePeer_Mode or GNATprove_Mode)
8849 and then R_Id = No_Exceptions
8850 then
8851 for J in Scope_Suppress.Suppress'Range loop
8852 if J /= Atomic_Synchronization then
8853 Scope_Suppress.Suppress (J) := True;
8854 end if;
8855 end loop;
8856 end if;
8858 -- Case of No_Dependence => unit-name. Note that the parser
8859 -- already made the necessary entry in the No_Dependence table.
8861 elsif Id = Name_No_Dependence then
8862 if not OK_No_Dependence_Unit_Name (Expr) then
8863 raise Pragma_Exit;
8864 end if;
8866 -- Case of No_Specification_Of_Aspect => aspect-identifier
8868 elsif Id = Name_No_Specification_Of_Aspect then
8869 declare
8870 A_Id : Aspect_Id;
8872 begin
8873 if Nkind (Expr) /= N_Identifier then
8874 A_Id := No_Aspect;
8875 else
8876 A_Id := Get_Aspect_Id (Chars (Expr));
8877 end if;
8879 if A_Id = No_Aspect then
8880 Error_Pragma_Arg ("invalid restriction name", Arg);
8881 else
8882 Set_Restriction_No_Specification_Of_Aspect (Expr, Warn);
8883 end if;
8884 end;
8886 -- Case of No_Use_Of_Attribute => attribute-identifier
8888 elsif Id = Name_No_Use_Of_Attribute then
8889 if Nkind (Expr) /= N_Identifier
8890 or else not Is_Attribute_Name (Chars (Expr))
8891 then
8892 Error_Msg_N ("unknown attribute name??", Expr);
8894 else
8895 Set_Restriction_No_Use_Of_Attribute (Expr, Warn);
8896 end if;
8898 -- Case of No_Use_Of_Entity => fully-qualified-name. Note that the
8899 -- parser already processed this case commpletely, including error
8900 -- checking and making an entry in the No_Use_Of_Entity table.
8902 elsif Id = Name_No_Use_Of_Entity then
8903 null;
8905 -- Case of No_Use_Of_Pragma => pragma-identifier
8907 elsif Id = Name_No_Use_Of_Pragma then
8908 if Nkind (Expr) /= N_Identifier
8909 or else not Is_Pragma_Name (Chars (Expr))
8910 then
8911 Error_Msg_N ("unknown pragma name??", Expr);
8913 else
8914 Set_Restriction_No_Use_Of_Pragma (Expr, Warn);
8915 end if;
8917 -- All other cases of restriction identifier present
8919 else
8920 R_Id := Get_Restriction_Id (Process_Restriction_Synonyms (Arg));
8921 Analyze_And_Resolve (Expr, Any_Integer);
8923 if R_Id not in All_Parameter_Restrictions then
8924 Error_Pragma_Arg
8925 ("invalid restriction parameter identifier", Arg);
8927 elsif not Is_OK_Static_Expression (Expr) then
8928 Flag_Non_Static_Expr
8929 ("value must be static expression!", Expr);
8930 raise Pragma_Exit;
8932 elsif not Is_Integer_Type (Etype (Expr))
8933 or else Expr_Value (Expr) < 0
8934 then
8935 Error_Pragma_Arg
8936 ("value must be non-negative integer", Arg);
8937 end if;
8939 -- Restriction pragma is active
8941 Val := Expr_Value (Expr);
8943 if not UI_Is_In_Int_Range (Val) then
8944 Error_Pragma_Arg
8945 ("pragma ignored, value too large??", Arg);
8946 end if;
8948 -- Warning case. If the real restriction is active, then we
8949 -- ignore the request, since warning never overrides a real
8950 -- restriction. Otherwise we set the proper warning. Note that
8951 -- this circuit sets the warning again if it is already set,
8952 -- which is what we want, since the constant may have changed.
8954 if Warn then
8955 if not Restriction_Active (R_Id) then
8956 Set_Restriction
8957 (R_Id, N, Integer (UI_To_Int (Val)));
8958 Restriction_Warnings (R_Id) := True;
8959 end if;
8961 -- Real restriction case, set restriction and make sure warning
8962 -- flag is off since real restriction always overrides warning.
8964 else
8965 Set_Restriction (R_Id, N, Integer (UI_To_Int (Val)));
8966 Restriction_Warnings (R_Id) := False;
8967 end if;
8968 end if;
8970 Next (Arg);
8971 end loop;
8972 end Process_Restrictions_Or_Restriction_Warnings;
8974 ---------------------------------
8975 -- Process_Suppress_Unsuppress --
8976 ---------------------------------
8978 -- Note: this procedure makes entries in the check suppress data
8979 -- structures managed by Sem. See spec of package Sem for full
8980 -- details on how we handle recording of check suppression.
8982 procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean) is
8983 C : Check_Id;
8984 E_Id : Node_Id;
8985 E : Entity_Id;
8987 In_Package_Spec : constant Boolean :=
8988 Is_Package_Or_Generic_Package (Current_Scope)
8989 and then not In_Package_Body (Current_Scope);
8991 procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id);
8992 -- Used to suppress a single check on the given entity
8994 --------------------------------
8995 -- Suppress_Unsuppress_Echeck --
8996 --------------------------------
8998 procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id) is
8999 begin
9000 -- Check for error of trying to set atomic synchronization for
9001 -- a non-atomic variable.
9003 if C = Atomic_Synchronization
9004 and then not (Is_Atomic (E) or else Has_Atomic_Components (E))
9005 then
9006 Error_Msg_N
9007 ("pragma & requires atomic type or variable",
9008 Pragma_Identifier (Original_Node (N)));
9009 end if;
9011 Set_Checks_May_Be_Suppressed (E);
9013 if In_Package_Spec then
9014 Push_Global_Suppress_Stack_Entry
9015 (Entity => E,
9016 Check => C,
9017 Suppress => Suppress_Case);
9018 else
9019 Push_Local_Suppress_Stack_Entry
9020 (Entity => E,
9021 Check => C,
9022 Suppress => Suppress_Case);
9023 end if;
9025 -- If this is a first subtype, and the base type is distinct,
9026 -- then also set the suppress flags on the base type.
9028 if Is_First_Subtype (E) and then Etype (E) /= E then
9029 Suppress_Unsuppress_Echeck (Etype (E), C);
9030 end if;
9031 end Suppress_Unsuppress_Echeck;
9033 -- Start of processing for Process_Suppress_Unsuppress
9035 begin
9036 -- Ignore pragma Suppress/Unsuppress in CodePeer and GNATprove modes
9037 -- on user code: we want to generate checks for analysis purposes, as
9038 -- set respectively by -gnatC and -gnatd.F
9040 if (CodePeer_Mode or GNATprove_Mode)
9041 and then Comes_From_Source (N)
9042 then
9043 return;
9044 end if;
9046 -- Suppress/Unsuppress can appear as a configuration pragma, or in a
9047 -- declarative part or a package spec (RM 11.5(5)).
9049 if not Is_Configuration_Pragma then
9050 Check_Is_In_Decl_Part_Or_Package_Spec;
9051 end if;
9053 Check_At_Least_N_Arguments (1);
9054 Check_At_Most_N_Arguments (2);
9055 Check_No_Identifier (Arg1);
9056 Check_Arg_Is_Identifier (Arg1);
9058 C := Get_Check_Id (Chars (Get_Pragma_Arg (Arg1)));
9060 if C = No_Check_Id then
9061 Error_Pragma_Arg
9062 ("argument of pragma% is not valid check name", Arg1);
9063 end if;
9065 -- Warn that suppress of Elaboration_Check has no effect in SPARK
9067 if C = Elaboration_Check and then SPARK_Mode = On then
9068 Error_Pragma_Arg
9069 ("Suppress of Elaboration_Check ignored in SPARK??",
9070 "\elaboration checking rules are statically enforced "
9071 & "(SPARK RM 7.7)", Arg1);
9072 end if;
9074 -- One-argument case
9076 if Arg_Count = 1 then
9078 -- Make an entry in the local scope suppress table. This is the
9079 -- table that directly shows the current value of the scope
9080 -- suppress check for any check id value.
9082 if C = All_Checks then
9084 -- For All_Checks, we set all specific predefined checks with
9085 -- the exception of Elaboration_Check, which is handled
9086 -- specially because of not wanting All_Checks to have the
9087 -- effect of deactivating static elaboration order processing.
9088 -- Atomic_Synchronization is also not affected, since this is
9089 -- not a real check.
9091 for J in Scope_Suppress.Suppress'Range loop
9092 if J /= Elaboration_Check
9093 and then
9094 J /= Atomic_Synchronization
9095 then
9096 Scope_Suppress.Suppress (J) := Suppress_Case;
9097 end if;
9098 end loop;
9100 -- If not All_Checks, and predefined check, then set appropriate
9101 -- scope entry. Note that we will set Elaboration_Check if this
9102 -- is explicitly specified. Atomic_Synchronization is allowed
9103 -- only if internally generated and entity is atomic.
9105 elsif C in Predefined_Check_Id
9106 and then (not Comes_From_Source (N)
9107 or else C /= Atomic_Synchronization)
9108 then
9109 Scope_Suppress.Suppress (C) := Suppress_Case;
9110 end if;
9112 -- Also make an entry in the Local_Entity_Suppress table
9114 Push_Local_Suppress_Stack_Entry
9115 (Entity => Empty,
9116 Check => C,
9117 Suppress => Suppress_Case);
9119 -- Case of two arguments present, where the check is suppressed for
9120 -- a specified entity (given as the second argument of the pragma)
9122 else
9123 -- This is obsolescent in Ada 2005 mode
9125 if Ada_Version >= Ada_2005 then
9126 Check_Restriction (No_Obsolescent_Features, Arg2);
9127 end if;
9129 Check_Optional_Identifier (Arg2, Name_On);
9130 E_Id := Get_Pragma_Arg (Arg2);
9131 Analyze (E_Id);
9133 if not Is_Entity_Name (E_Id) then
9134 Error_Pragma_Arg
9135 ("second argument of pragma% must be entity name", Arg2);
9136 end if;
9138 E := Entity (E_Id);
9140 if E = Any_Id then
9141 return;
9142 end if;
9144 -- Enforce RM 11.5(7) which requires that for a pragma that
9145 -- appears within a package spec, the named entity must be
9146 -- within the package spec. We allow the package name itself
9147 -- to be mentioned since that makes sense, although it is not
9148 -- strictly allowed by 11.5(7).
9150 if In_Package_Spec
9151 and then E /= Current_Scope
9152 and then Scope (E) /= Current_Scope
9153 then
9154 Error_Pragma_Arg
9155 ("entity in pragma% is not in package spec (RM 11.5(7))",
9156 Arg2);
9157 end if;
9159 -- Loop through homonyms. As noted below, in the case of a package
9160 -- spec, only homonyms within the package spec are considered.
9162 loop
9163 Suppress_Unsuppress_Echeck (E, C);
9165 if Is_Generic_Instance (E)
9166 and then Is_Subprogram (E)
9167 and then Present (Alias (E))
9168 then
9169 Suppress_Unsuppress_Echeck (Alias (E), C);
9170 end if;
9172 -- Move to next homonym if not aspect spec case
9174 exit when From_Aspect_Specification (N);
9175 E := Homonym (E);
9176 exit when No (E);
9178 -- If we are within a package specification, the pragma only
9179 -- applies to homonyms in the same scope.
9181 exit when In_Package_Spec
9182 and then Scope (E) /= Current_Scope;
9183 end loop;
9184 end if;
9185 end Process_Suppress_Unsuppress;
9187 ------------------
9188 -- Set_Exported --
9189 ------------------
9191 procedure Set_Exported (E : Entity_Id; Arg : Node_Id) is
9192 begin
9193 if Is_Imported (E) then
9194 Error_Pragma_Arg
9195 ("cannot export entity& that was previously imported", Arg);
9197 elsif Present (Address_Clause (E))
9198 and then not Relaxed_RM_Semantics
9199 then
9200 Error_Pragma_Arg
9201 ("cannot export entity& that has an address clause", Arg);
9202 end if;
9204 Set_Is_Exported (E);
9206 -- Generate a reference for entity explicitly, because the
9207 -- identifier may be overloaded and name resolution will not
9208 -- generate one.
9210 Generate_Reference (E, Arg);
9212 -- Deal with exporting non-library level entity
9214 if not Is_Library_Level_Entity (E) then
9216 -- Not allowed at all for subprograms
9218 if Is_Subprogram (E) then
9219 Error_Pragma_Arg ("local subprogram& cannot be exported", Arg);
9221 -- Otherwise set public and statically allocated
9223 else
9224 Set_Is_Public (E);
9225 Set_Is_Statically_Allocated (E);
9227 -- Warn if the corresponding W flag is set
9229 if Warn_On_Export_Import
9231 -- Only do this for something that was in the source. Not
9232 -- clear if this can be False now (there used for sure to be
9233 -- cases on some systems where it was False), but anyway the
9234 -- test is harmless if not needed, so it is retained.
9236 and then Comes_From_Source (Arg)
9237 then
9238 Error_Msg_NE
9239 ("?x?& has been made static as a result of Export",
9240 Arg, E);
9241 Error_Msg_N
9242 ("\?x?this usage is non-standard and non-portable",
9243 Arg);
9244 end if;
9245 end if;
9246 end if;
9248 if Warn_On_Export_Import and then Is_Type (E) then
9249 Error_Msg_NE ("exporting a type has no effect?x?", Arg, E);
9250 end if;
9252 if Warn_On_Export_Import and Inside_A_Generic then
9253 Error_Msg_NE
9254 ("all instances of& will have the same external name?x?",
9255 Arg, E);
9256 end if;
9257 end Set_Exported;
9259 ----------------------------------------------
9260 -- Set_Extended_Import_Export_External_Name --
9261 ----------------------------------------------
9263 procedure Set_Extended_Import_Export_External_Name
9264 (Internal_Ent : Entity_Id;
9265 Arg_External : Node_Id)
9267 Old_Name : constant Node_Id := Interface_Name (Internal_Ent);
9268 New_Name : Node_Id;
9270 begin
9271 if No (Arg_External) then
9272 return;
9273 end if;
9275 Check_Arg_Is_External_Name (Arg_External);
9277 if Nkind (Arg_External) = N_String_Literal then
9278 if String_Length (Strval (Arg_External)) = 0 then
9279 return;
9280 else
9281 New_Name := Adjust_External_Name_Case (Arg_External);
9282 end if;
9284 elsif Nkind (Arg_External) = N_Identifier then
9285 New_Name := Get_Default_External_Name (Arg_External);
9287 -- Check_Arg_Is_External_Name should let through only identifiers and
9288 -- string literals or static string expressions (which are folded to
9289 -- string literals).
9291 else
9292 raise Program_Error;
9293 end if;
9295 -- If we already have an external name set (by a prior normal Import
9296 -- or Export pragma), then the external names must match
9298 if Present (Interface_Name (Internal_Ent)) then
9300 -- Ignore mismatching names in CodePeer mode, to support some
9301 -- old compilers which would export the same procedure under
9302 -- different names, e.g:
9303 -- procedure P;
9304 -- pragma Export_Procedure (P, "a");
9305 -- pragma Export_Procedure (P, "b");
9307 if CodePeer_Mode then
9308 return;
9309 end if;
9311 Check_Matching_Internal_Names : declare
9312 S1 : constant String_Id := Strval (Old_Name);
9313 S2 : constant String_Id := Strval (New_Name);
9315 procedure Mismatch;
9316 pragma No_Return (Mismatch);
9317 -- Called if names do not match
9319 --------------
9320 -- Mismatch --
9321 --------------
9323 procedure Mismatch is
9324 begin
9325 Error_Msg_Sloc := Sloc (Old_Name);
9326 Error_Pragma_Arg
9327 ("external name does not match that given #",
9328 Arg_External);
9329 end Mismatch;
9331 -- Start of processing for Check_Matching_Internal_Names
9333 begin
9334 if String_Length (S1) /= String_Length (S2) then
9335 Mismatch;
9337 else
9338 for J in 1 .. String_Length (S1) loop
9339 if Get_String_Char (S1, J) /= Get_String_Char (S2, J) then
9340 Mismatch;
9341 end if;
9342 end loop;
9343 end if;
9344 end Check_Matching_Internal_Names;
9346 -- Otherwise set the given name
9348 else
9349 Set_Encoded_Interface_Name (Internal_Ent, New_Name);
9350 Check_Duplicated_Export_Name (New_Name);
9351 end if;
9352 end Set_Extended_Import_Export_External_Name;
9354 ------------------
9355 -- Set_Imported --
9356 ------------------
9358 procedure Set_Imported (E : Entity_Id) is
9359 begin
9360 -- Error message if already imported or exported
9362 if Is_Exported (E) or else Is_Imported (E) then
9364 -- Error if being set Exported twice
9366 if Is_Exported (E) then
9367 Error_Msg_NE ("entity& was previously exported", N, E);
9369 -- Ignore error in CodePeer mode where we treat all imported
9370 -- subprograms as unknown.
9372 elsif CodePeer_Mode then
9373 goto OK;
9375 -- OK if Import/Interface case
9377 elsif Import_Interface_Present (N) then
9378 goto OK;
9380 -- Error if being set Imported twice
9382 else
9383 Error_Msg_NE ("entity& was previously imported", N, E);
9384 end if;
9386 Error_Msg_Name_1 := Pname;
9387 Error_Msg_N
9388 ("\(pragma% applies to all previous entities)", N);
9390 Error_Msg_Sloc := Sloc (E);
9391 Error_Msg_NE ("\import not allowed for& declared#", N, E);
9393 -- Here if not previously imported or exported, OK to import
9395 else
9396 Set_Is_Imported (E);
9398 -- For subprogram, set Import_Pragma field
9400 if Is_Subprogram (E) then
9401 Set_Import_Pragma (E, N);
9402 end if;
9404 -- If the entity is an object that is not at the library level,
9405 -- then it is statically allocated. We do not worry about objects
9406 -- with address clauses in this context since they are not really
9407 -- imported in the linker sense.
9409 if Is_Object (E)
9410 and then not Is_Library_Level_Entity (E)
9411 and then No (Address_Clause (E))
9412 then
9413 Set_Is_Statically_Allocated (E);
9414 end if;
9415 end if;
9417 <<OK>> null;
9418 end Set_Imported;
9420 -------------------------
9421 -- Set_Mechanism_Value --
9422 -------------------------
9424 -- Note: the mechanism name has not been analyzed (and cannot indeed be
9425 -- analyzed, since it is semantic nonsense), so we get it in the exact
9426 -- form created by the parser.
9428 procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id) is
9429 procedure Bad_Mechanism;
9430 pragma No_Return (Bad_Mechanism);
9431 -- Signal bad mechanism name
9433 -------------------------
9434 -- Bad_Mechanism_Value --
9435 -------------------------
9437 procedure Bad_Mechanism is
9438 begin
9439 Error_Pragma_Arg ("unrecognized mechanism name", Mech_Name);
9440 end Bad_Mechanism;
9442 -- Start of processing for Set_Mechanism_Value
9444 begin
9445 if Mechanism (Ent) /= Default_Mechanism then
9446 Error_Msg_NE
9447 ("mechanism for & has already been set", Mech_Name, Ent);
9448 end if;
9450 -- MECHANISM_NAME ::= value | reference
9452 if Nkind (Mech_Name) = N_Identifier then
9453 if Chars (Mech_Name) = Name_Value then
9454 Set_Mechanism (Ent, By_Copy);
9455 return;
9457 elsif Chars (Mech_Name) = Name_Reference then
9458 Set_Mechanism (Ent, By_Reference);
9459 return;
9461 elsif Chars (Mech_Name) = Name_Copy then
9462 Error_Pragma_Arg
9463 ("bad mechanism name, Value assumed", Mech_Name);
9465 else
9466 Bad_Mechanism;
9467 end if;
9469 else
9470 Bad_Mechanism;
9471 end if;
9472 end Set_Mechanism_Value;
9474 --------------------------
9475 -- Set_Rational_Profile --
9476 --------------------------
9478 -- The Rational profile includes Implicit_Packing, Use_Vads_Size, and
9479 -- and extension to the semantics of renaming declarations.
9481 procedure Set_Rational_Profile is
9482 begin
9483 Implicit_Packing := True;
9484 Overriding_Renamings := True;
9485 Use_VADS_Size := True;
9486 end Set_Rational_Profile;
9488 ---------------------------
9489 -- Set_Ravenscar_Profile --
9490 ---------------------------
9492 -- The tasks to be done here are
9494 -- Set required policies
9496 -- pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
9497 -- pragma Locking_Policy (Ceiling_Locking)
9499 -- Set Detect_Blocking mode
9501 -- Set required restrictions (see System.Rident for detailed list)
9503 -- Set the No_Dependence rules
9504 -- No_Dependence => Ada.Asynchronous_Task_Control
9505 -- No_Dependence => Ada.Calendar
9506 -- No_Dependence => Ada.Execution_Time.Group_Budget
9507 -- No_Dependence => Ada.Execution_Time.Timers
9508 -- No_Dependence => Ada.Task_Attributes
9509 -- No_Dependence => System.Multiprocessors.Dispatching_Domains
9511 procedure Set_Ravenscar_Profile (N : Node_Id) is
9512 Prefix_Entity : Entity_Id;
9513 Selector_Entity : Entity_Id;
9514 Prefix_Node : Node_Id;
9515 Node : Node_Id;
9517 begin
9518 -- pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
9520 if Task_Dispatching_Policy /= ' '
9521 and then Task_Dispatching_Policy /= 'F'
9522 then
9523 Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
9524 Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
9526 -- Set the FIFO_Within_Priorities policy, but always preserve
9527 -- System_Location since we like the error message with the run time
9528 -- name.
9530 else
9531 Task_Dispatching_Policy := 'F';
9533 if Task_Dispatching_Policy_Sloc /= System_Location then
9534 Task_Dispatching_Policy_Sloc := Loc;
9535 end if;
9536 end if;
9538 -- pragma Locking_Policy (Ceiling_Locking)
9540 if Locking_Policy /= ' '
9541 and then Locking_Policy /= 'C'
9542 then
9543 Error_Msg_Sloc := Locking_Policy_Sloc;
9544 Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
9546 -- Set the Ceiling_Locking policy, but preserve System_Location since
9547 -- we like the error message with the run time name.
9549 else
9550 Locking_Policy := 'C';
9552 if Locking_Policy_Sloc /= System_Location then
9553 Locking_Policy_Sloc := Loc;
9554 end if;
9555 end if;
9557 -- pragma Detect_Blocking
9559 Detect_Blocking := True;
9561 -- Set the corresponding restrictions
9563 Set_Profile_Restrictions
9564 (Ravenscar, N, Warn => Treat_Restrictions_As_Warnings);
9566 -- Set the No_Dependence restrictions
9568 -- The following No_Dependence restrictions:
9569 -- No_Dependence => Ada.Asynchronous_Task_Control
9570 -- No_Dependence => Ada.Calendar
9571 -- No_Dependence => Ada.Task_Attributes
9572 -- are already set by previous call to Set_Profile_Restrictions.
9574 -- Set the following restrictions which were added to Ada 2005:
9575 -- No_Dependence => Ada.Execution_Time.Group_Budget
9576 -- No_Dependence => Ada.Execution_Time.Timers
9578 if Ada_Version >= Ada_2005 then
9579 Name_Buffer (1 .. 3) := "ada";
9580 Name_Len := 3;
9582 Prefix_Entity := Make_Identifier (Loc, Name_Find);
9584 Name_Buffer (1 .. 14) := "execution_time";
9585 Name_Len := 14;
9587 Selector_Entity := Make_Identifier (Loc, Name_Find);
9589 Prefix_Node :=
9590 Make_Selected_Component
9591 (Sloc => Loc,
9592 Prefix => Prefix_Entity,
9593 Selector_Name => Selector_Entity);
9595 Name_Buffer (1 .. 13) := "group_budgets";
9596 Name_Len := 13;
9598 Selector_Entity := Make_Identifier (Loc, Name_Find);
9600 Node :=
9601 Make_Selected_Component
9602 (Sloc => Loc,
9603 Prefix => Prefix_Node,
9604 Selector_Name => Selector_Entity);
9606 Set_Restriction_No_Dependence
9607 (Unit => Node,
9608 Warn => Treat_Restrictions_As_Warnings,
9609 Profile => Ravenscar);
9611 Name_Buffer (1 .. 6) := "timers";
9612 Name_Len := 6;
9614 Selector_Entity := Make_Identifier (Loc, Name_Find);
9616 Node :=
9617 Make_Selected_Component
9618 (Sloc => Loc,
9619 Prefix => Prefix_Node,
9620 Selector_Name => Selector_Entity);
9622 Set_Restriction_No_Dependence
9623 (Unit => Node,
9624 Warn => Treat_Restrictions_As_Warnings,
9625 Profile => Ravenscar);
9626 end if;
9628 -- Set the following restrictions which was added to Ada 2012 (see
9629 -- AI-0171):
9630 -- No_Dependence => System.Multiprocessors.Dispatching_Domains
9632 if Ada_Version >= Ada_2012 then
9633 Name_Buffer (1 .. 6) := "system";
9634 Name_Len := 6;
9636 Prefix_Entity := Make_Identifier (Loc, Name_Find);
9638 Name_Buffer (1 .. 15) := "multiprocessors";
9639 Name_Len := 15;
9641 Selector_Entity := Make_Identifier (Loc, Name_Find);
9643 Prefix_Node :=
9644 Make_Selected_Component
9645 (Sloc => Loc,
9646 Prefix => Prefix_Entity,
9647 Selector_Name => Selector_Entity);
9649 Name_Buffer (1 .. 19) := "dispatching_domains";
9650 Name_Len := 19;
9652 Selector_Entity := Make_Identifier (Loc, Name_Find);
9654 Node :=
9655 Make_Selected_Component
9656 (Sloc => Loc,
9657 Prefix => Prefix_Node,
9658 Selector_Name => Selector_Entity);
9660 Set_Restriction_No_Dependence
9661 (Unit => Node,
9662 Warn => Treat_Restrictions_As_Warnings,
9663 Profile => Ravenscar);
9664 end if;
9665 end Set_Ravenscar_Profile;
9667 -- Start of processing for Analyze_Pragma
9669 begin
9670 -- The following code is a defense against recursion. Not clear that
9671 -- this can happen legitimately, but perhaps some error situations
9672 -- can cause it, and we did see this recursion during testing.
9674 if Analyzed (N) then
9675 return;
9676 else
9677 Set_Analyzed (N, True);
9678 end if;
9680 -- Deal with unrecognized pragma
9682 Pname := Pragma_Name (N);
9684 if not Is_Pragma_Name (Pname) then
9685 if Warn_On_Unrecognized_Pragma then
9686 Error_Msg_Name_1 := Pname;
9687 Error_Msg_N ("?g?unrecognized pragma%!", Pragma_Identifier (N));
9689 for PN in First_Pragma_Name .. Last_Pragma_Name loop
9690 if Is_Bad_Spelling_Of (Pname, PN) then
9691 Error_Msg_Name_1 := PN;
9692 Error_Msg_N -- CODEFIX
9693 ("\?g?possible misspelling of %!", Pragma_Identifier (N));
9694 exit;
9695 end if;
9696 end loop;
9697 end if;
9699 return;
9700 end if;
9702 -- Here to start processing for recognized pragma
9704 Prag_Id := Get_Pragma_Id (Pname);
9705 Pname := Original_Aspect_Name (N);
9707 -- Capture setting of Opt.Uneval_Old
9709 case Opt.Uneval_Old is
9710 when 'A' =>
9711 Set_Uneval_Old_Accept (N);
9712 when 'E' =>
9713 null;
9714 when 'W' =>
9715 Set_Uneval_Old_Warn (N);
9716 when others =>
9717 raise Program_Error;
9718 end case;
9720 -- Check applicable policy. We skip this if Is_Checked or Is_Ignored
9721 -- is already set, indicating that we have already checked the policy
9722 -- at the right point. This happens for example in the case of a pragma
9723 -- that is derived from an Aspect.
9725 if Is_Ignored (N) or else Is_Checked (N) then
9726 null;
9728 -- For a pragma that is a rewriting of another pragma, copy the
9729 -- Is_Checked/Is_Ignored status from the rewritten pragma.
9731 elsif Is_Rewrite_Substitution (N)
9732 and then Nkind (Original_Node (N)) = N_Pragma
9733 and then Original_Node (N) /= N
9734 then
9735 Set_Is_Ignored (N, Is_Ignored (Original_Node (N)));
9736 Set_Is_Checked (N, Is_Checked (Original_Node (N)));
9738 -- Otherwise query the applicable policy at this point
9740 else
9741 Check_Applicable_Policy (N);
9743 -- If pragma is disabled, rewrite as NULL and skip analysis
9745 if Is_Disabled (N) then
9746 Rewrite (N, Make_Null_Statement (Loc));
9747 Analyze (N);
9748 raise Pragma_Exit;
9749 end if;
9750 end if;
9752 -- Preset arguments
9754 Arg_Count := 0;
9755 Arg1 := Empty;
9756 Arg2 := Empty;
9757 Arg3 := Empty;
9758 Arg4 := Empty;
9760 if Present (Pragma_Argument_Associations (N)) then
9761 Arg_Count := List_Length (Pragma_Argument_Associations (N));
9762 Arg1 := First (Pragma_Argument_Associations (N));
9764 if Present (Arg1) then
9765 Arg2 := Next (Arg1);
9767 if Present (Arg2) then
9768 Arg3 := Next (Arg2);
9770 if Present (Arg3) then
9771 Arg4 := Next (Arg3);
9772 end if;
9773 end if;
9774 end if;
9775 end if;
9777 Check_Restriction_No_Use_Of_Pragma (N);
9779 -- An enumeration type defines the pragmas that are supported by the
9780 -- implementation. Get_Pragma_Id (in package Prag) transforms a name
9781 -- into the corresponding enumeration value for the following case.
9783 case Prag_Id is
9785 -----------------
9786 -- Abort_Defer --
9787 -----------------
9789 -- pragma Abort_Defer;
9791 when Pragma_Abort_Defer =>
9792 GNAT_Pragma;
9793 Check_Arg_Count (0);
9795 -- The only required semantic processing is to check the
9796 -- placement. This pragma must appear at the start of the
9797 -- statement sequence of a handled sequence of statements.
9799 if Nkind (Parent (N)) /= N_Handled_Sequence_Of_Statements
9800 or else N /= First (Statements (Parent (N)))
9801 then
9802 Pragma_Misplaced;
9803 end if;
9805 --------------------
9806 -- Abstract_State --
9807 --------------------
9809 -- pragma Abstract_State (ABSTRACT_STATE_LIST);
9811 -- ABSTRACT_STATE_LIST ::=
9812 -- null
9813 -- | STATE_NAME_WITH_OPTIONS
9814 -- | (STATE_NAME_WITH_OPTIONS {, STATE_NAME_WITH_OPTIONS} )
9816 -- STATE_NAME_WITH_OPTIONS ::=
9817 -- STATE_NAME
9818 -- | (STATE_NAME with OPTION_LIST)
9820 -- OPTION_LIST ::= OPTION {, OPTION}
9822 -- OPTION ::=
9823 -- SIMPLE_OPTION
9824 -- | NAME_VALUE_OPTION
9826 -- SIMPLE_OPTION ::= Ghost
9828 -- NAME_VALUE_OPTION ::=
9829 -- Part_Of => ABSTRACT_STATE
9830 -- | External [=> EXTERNAL_PROPERTY_LIST]
9832 -- EXTERNAL_PROPERTY_LIST ::=
9833 -- EXTERNAL_PROPERTY
9834 -- | (EXTERNAL_PROPERTY {, EXTERNAL_PROPERTY} )
9836 -- EXTERNAL_PROPERTY ::=
9837 -- Async_Readers [=> boolean_EXPRESSION]
9838 -- | Async_Writers [=> boolean_EXPRESSION]
9839 -- | Effective_Reads [=> boolean_EXPRESSION]
9840 -- | Effective_Writes [=> boolean_EXPRESSION]
9841 -- others => boolean_EXPRESSION
9843 -- STATE_NAME ::= defining_identifier
9845 -- ABSTRACT_STATE ::= name
9847 when Pragma_Abstract_State => Abstract_State : declare
9848 Missing_Parentheses : Boolean := False;
9849 -- Flag set when a state declaration with options is not properly
9850 -- parenthesized.
9852 -- Flags used to verify the consistency of states
9854 Non_Null_Seen : Boolean := False;
9855 Null_Seen : Boolean := False;
9857 procedure Analyze_Abstract_State
9858 (State : Node_Id;
9859 Pack_Id : Entity_Id);
9860 -- Verify the legality of a single state declaration. Create and
9861 -- decorate a state abstraction entity and introduce it into the
9862 -- visibility chain. Pack_Id denotes the entity or the related
9863 -- package where pragma Abstract_State appears.
9865 ----------------------------
9866 -- Analyze_Abstract_State --
9867 ----------------------------
9869 procedure Analyze_Abstract_State
9870 (State : Node_Id;
9871 Pack_Id : Entity_Id)
9873 -- Flags used to verify the consistency of options
9875 AR_Seen : Boolean := False;
9876 AW_Seen : Boolean := False;
9877 ER_Seen : Boolean := False;
9878 EW_Seen : Boolean := False;
9879 External_Seen : Boolean := False;
9880 Others_Seen : Boolean := False;
9881 Part_Of_Seen : Boolean := False;
9883 -- Flags used to store the static value of all external states'
9884 -- expressions.
9886 AR_Val : Boolean := False;
9887 AW_Val : Boolean := False;
9888 ER_Val : Boolean := False;
9889 EW_Val : Boolean := False;
9891 State_Id : Entity_Id := Empty;
9892 -- The entity to be generated for the current state declaration
9894 procedure Analyze_External_Option (Opt : Node_Id);
9895 -- Verify the legality of option External
9897 procedure Analyze_External_Property
9898 (Prop : Node_Id;
9899 Expr : Node_Id := Empty);
9900 -- Verify the legailty of a single external property. Prop
9901 -- denotes the external property. Expr is the expression used
9902 -- to set the property.
9904 procedure Analyze_Part_Of_Option (Opt : Node_Id);
9905 -- Verify the legality of option Part_Of
9907 procedure Check_Duplicate_Option
9908 (Opt : Node_Id;
9909 Status : in out Boolean);
9910 -- Flag Status denotes whether a particular option has been
9911 -- seen while processing a state. This routine verifies that
9912 -- Opt is not a duplicate option and sets the flag Status
9913 -- (SPARK RM 7.1.4(1)).
9915 procedure Check_Duplicate_Property
9916 (Prop : Node_Id;
9917 Status : in out Boolean);
9918 -- Flag Status denotes whether a particular property has been
9919 -- seen while processing option External. This routine verifies
9920 -- that Prop is not a duplicate property and sets flag Status.
9921 -- Opt is not a duplicate property and sets the flag Status.
9922 -- (SPARK RM 7.1.4(2))
9924 procedure Create_Abstract_State
9925 (Nam : Name_Id;
9926 Decl : Node_Id;
9927 Loc : Source_Ptr;
9928 Is_Null : Boolean);
9929 -- Generate an abstract state entity with name Nam and enter it
9930 -- into visibility. Decl is the "declaration" of the state as
9931 -- it appears in pragma Abstract_State. Loc is the location of
9932 -- the related state "declaration". Flag Is_Null should be set
9933 -- when the associated Abstract_State pragma defines a null
9934 -- state.
9936 -----------------------------
9937 -- Analyze_External_Option --
9938 -----------------------------
9940 procedure Analyze_External_Option (Opt : Node_Id) is
9941 Errors : constant Nat := Serious_Errors_Detected;
9942 Prop : Node_Id;
9943 Props : Node_Id := Empty;
9945 begin
9946 Check_Duplicate_Option (Opt, External_Seen);
9948 if Nkind (Opt) = N_Component_Association then
9949 Props := Expression (Opt);
9950 end if;
9952 -- External state with properties
9954 if Present (Props) then
9956 -- Multiple properties appear as an aggregate
9958 if Nkind (Props) = N_Aggregate then
9960 -- Simple property form
9962 Prop := First (Expressions (Props));
9963 while Present (Prop) loop
9964 Analyze_External_Property (Prop);
9965 Next (Prop);
9966 end loop;
9968 -- Property with expression form
9970 Prop := First (Component_Associations (Props));
9971 while Present (Prop) loop
9972 Analyze_External_Property
9973 (Prop => First (Choices (Prop)),
9974 Expr => Expression (Prop));
9976 Next (Prop);
9977 end loop;
9979 -- Single property
9981 else
9982 Analyze_External_Property (Props);
9983 end if;
9985 -- An external state defined without any properties defaults
9986 -- all properties to True.
9988 else
9989 AR_Val := True;
9990 AW_Val := True;
9991 ER_Val := True;
9992 EW_Val := True;
9993 end if;
9995 -- Once all external properties have been processed, verify
9996 -- their mutual interaction. Do not perform the check when
9997 -- at least one of the properties is illegal as this will
9998 -- produce a bogus error.
10000 if Errors = Serious_Errors_Detected then
10001 Check_External_Properties
10002 (State, AR_Val, AW_Val, ER_Val, EW_Val);
10003 end if;
10004 end Analyze_External_Option;
10006 -------------------------------
10007 -- Analyze_External_Property --
10008 -------------------------------
10010 procedure Analyze_External_Property
10011 (Prop : Node_Id;
10012 Expr : Node_Id := Empty)
10014 Expr_Val : Boolean;
10016 begin
10017 -- Check the placement of "others" (if available)
10019 if Nkind (Prop) = N_Others_Choice then
10020 if Others_Seen then
10021 SPARK_Msg_N
10022 ("only one others choice allowed in option External",
10023 Prop);
10024 else
10025 Others_Seen := True;
10026 end if;
10028 elsif Others_Seen then
10029 SPARK_Msg_N
10030 ("others must be the last property in option External",
10031 Prop);
10033 -- The only remaining legal options are the four predefined
10034 -- external properties.
10036 elsif Nkind (Prop) = N_Identifier
10037 and then Nam_In (Chars (Prop), Name_Async_Readers,
10038 Name_Async_Writers,
10039 Name_Effective_Reads,
10040 Name_Effective_Writes)
10041 then
10042 null;
10044 -- Otherwise the construct is not a valid property
10046 else
10047 SPARK_Msg_N ("invalid external state property", Prop);
10048 return;
10049 end if;
10051 -- Ensure that the expression of the external state property
10052 -- is static Boolean (if applicable) (SPARK RM 7.1.2(5)).
10054 if Present (Expr) then
10055 Analyze_And_Resolve (Expr, Standard_Boolean);
10057 if Is_OK_Static_Expression (Expr) then
10058 Expr_Val := Is_True (Expr_Value (Expr));
10059 else
10060 SPARK_Msg_N
10061 ("expression of external state property must be "
10062 & "static", Expr);
10063 end if;
10065 -- The lack of expression defaults the property to True
10067 else
10068 Expr_Val := True;
10069 end if;
10071 -- Named properties
10073 if Nkind (Prop) = N_Identifier then
10074 if Chars (Prop) = Name_Async_Readers then
10075 Check_Duplicate_Property (Prop, AR_Seen);
10076 AR_Val := Expr_Val;
10078 elsif Chars (Prop) = Name_Async_Writers then
10079 Check_Duplicate_Property (Prop, AW_Seen);
10080 AW_Val := Expr_Val;
10082 elsif Chars (Prop) = Name_Effective_Reads then
10083 Check_Duplicate_Property (Prop, ER_Seen);
10084 ER_Val := Expr_Val;
10086 else
10087 Check_Duplicate_Property (Prop, EW_Seen);
10088 EW_Val := Expr_Val;
10089 end if;
10091 -- The handling of property "others" must take into account
10092 -- all other named properties that have been encountered so
10093 -- far. Only those that have not been seen are affected by
10094 -- "others".
10096 else
10097 if not AR_Seen then
10098 AR_Val := Expr_Val;
10099 end if;
10101 if not AW_Seen then
10102 AW_Val := Expr_Val;
10103 end if;
10105 if not ER_Seen then
10106 ER_Val := Expr_Val;
10107 end if;
10109 if not EW_Seen then
10110 EW_Val := Expr_Val;
10111 end if;
10112 end if;
10113 end Analyze_External_Property;
10115 ----------------------------
10116 -- Analyze_Part_Of_Option --
10117 ----------------------------
10119 procedure Analyze_Part_Of_Option (Opt : Node_Id) is
10120 Encaps : constant Node_Id := Expression (Opt);
10121 Encaps_Id : Entity_Id;
10122 Legal : Boolean;
10124 begin
10125 Check_Duplicate_Option (Opt, Part_Of_Seen);
10127 Analyze_Part_Of
10128 (Item_Id => State_Id,
10129 State => Encaps,
10130 Indic => First (Choices (Opt)),
10131 Legal => Legal);
10133 -- The Part_Of indicator turns an abstract state into a
10134 -- constituent of the encapsulating state.
10136 if Legal then
10137 Encaps_Id := Entity (Encaps);
10139 Append_Elmt (State_Id, Part_Of_Constituents (Encaps_Id));
10140 Set_Encapsulating_State (State_Id, Encaps_Id);
10141 end if;
10142 end Analyze_Part_Of_Option;
10144 ----------------------------
10145 -- Check_Duplicate_Option --
10146 ----------------------------
10148 procedure Check_Duplicate_Option
10149 (Opt : Node_Id;
10150 Status : in out Boolean)
10152 begin
10153 if Status then
10154 SPARK_Msg_N ("duplicate state option", Opt);
10155 end if;
10157 Status := True;
10158 end Check_Duplicate_Option;
10160 ------------------------------
10161 -- Check_Duplicate_Property --
10162 ------------------------------
10164 procedure Check_Duplicate_Property
10165 (Prop : Node_Id;
10166 Status : in out Boolean)
10168 begin
10169 if Status then
10170 SPARK_Msg_N ("duplicate external property", Prop);
10171 end if;
10173 Status := True;
10174 end Check_Duplicate_Property;
10176 ---------------------------
10177 -- Create_Abstract_State --
10178 ---------------------------
10180 procedure Create_Abstract_State
10181 (Nam : Name_Id;
10182 Decl : Node_Id;
10183 Loc : Source_Ptr;
10184 Is_Null : Boolean)
10186 begin
10187 -- The abstract state may be semi-declared when the related
10188 -- package was withed through a limited with clause. In that
10189 -- case reuse the entity to fully declare the state.
10191 if Present (Decl) and then Present (Entity (Decl)) then
10192 State_Id := Entity (Decl);
10194 -- Otherwise the elaboration of pragma Abstract_State
10195 -- declares the state.
10197 else
10198 State_Id := Make_Defining_Identifier (Loc, Nam);
10200 if Present (Decl) then
10201 Set_Entity (Decl, State_Id);
10202 end if;
10203 end if;
10205 -- Null states never come from source
10207 Set_Comes_From_Source (State_Id, not Is_Null);
10208 Set_Parent (State_Id, State);
10209 Set_Ekind (State_Id, E_Abstract_State);
10210 Set_Etype (State_Id, Standard_Void_Type);
10211 Set_Encapsulating_State (State_Id, Empty);
10212 Set_Refinement_Constituents (State_Id, New_Elmt_List);
10213 Set_Part_Of_Constituents (State_Id, New_Elmt_List);
10215 -- An abstract state declared within a Ghost scope becomes
10216 -- Ghost (SPARK RM 6.9(2)).
10218 if Within_Ghost_Scope then
10219 Set_Is_Ghost_Entity (State_Id);
10220 end if;
10222 -- Establish a link between the state declaration and the
10223 -- abstract state entity. Note that a null state remains as
10224 -- N_Null and does not carry any linkages.
10226 if not Is_Null then
10227 if Present (Decl) then
10228 Set_Entity (Decl, State_Id);
10229 Set_Etype (Decl, Standard_Void_Type);
10230 end if;
10232 -- Every non-null state must be defined, nameable and
10233 -- resolvable.
10235 Push_Scope (Pack_Id);
10236 Generate_Definition (State_Id);
10237 Enter_Name (State_Id);
10238 Pop_Scope;
10239 end if;
10240 end Create_Abstract_State;
10242 -- Local variables
10244 Opt : Node_Id;
10245 Opt_Nam : Node_Id;
10247 -- Start of processing for Analyze_Abstract_State
10249 begin
10250 -- A package with a null abstract state is not allowed to
10251 -- declare additional states.
10253 if Null_Seen then
10254 SPARK_Msg_NE
10255 ("package & has null abstract state", State, Pack_Id);
10257 -- Null states appear as internally generated entities
10259 elsif Nkind (State) = N_Null then
10260 Create_Abstract_State
10261 (Nam => New_Internal_Name ('S'),
10262 Decl => Empty,
10263 Loc => Sloc (State),
10264 Is_Null => True);
10265 Null_Seen := True;
10267 -- Catch a case where a null state appears in a list of
10268 -- non-null states.
10270 if Non_Null_Seen then
10271 SPARK_Msg_NE
10272 ("package & has non-null abstract state",
10273 State, Pack_Id);
10274 end if;
10276 -- Simple state declaration
10278 elsif Nkind (State) = N_Identifier then
10279 Create_Abstract_State
10280 (Nam => Chars (State),
10281 Decl => State,
10282 Loc => Sloc (State),
10283 Is_Null => False);
10284 Non_Null_Seen := True;
10286 -- State declaration with various options. This construct
10287 -- appears as an extension aggregate in the tree.
10289 elsif Nkind (State) = N_Extension_Aggregate then
10290 if Nkind (Ancestor_Part (State)) = N_Identifier then
10291 Create_Abstract_State
10292 (Nam => Chars (Ancestor_Part (State)),
10293 Decl => Ancestor_Part (State),
10294 Loc => Sloc (Ancestor_Part (State)),
10295 Is_Null => False);
10296 Non_Null_Seen := True;
10297 else
10298 SPARK_Msg_N
10299 ("state name must be an identifier",
10300 Ancestor_Part (State));
10301 end if;
10303 -- Options External and Ghost appear as expressions
10305 Opt := First (Expressions (State));
10306 while Present (Opt) loop
10307 if Nkind (Opt) = N_Identifier then
10308 if Chars (Opt) = Name_External then
10309 Analyze_External_Option (Opt);
10311 elsif Chars (Opt) = Name_Ghost then
10312 if Present (State_Id) then
10313 Set_Is_Ghost_Entity (State_Id);
10314 end if;
10316 -- Option Part_Of without an encapsulating state is
10317 -- illegal. (SPARK RM 7.1.4(9)).
10319 elsif Chars (Opt) = Name_Part_Of then
10320 SPARK_Msg_N
10321 ("indicator Part_Of must denote an abstract "
10322 & "state", Opt);
10324 -- Do not emit an error message when a previous state
10325 -- declaration with options was not parenthesized as
10326 -- the option is actually another state declaration.
10328 -- with Abstract_State
10329 -- (State_1 with ..., -- missing parentheses
10330 -- (State_2 with ...),
10331 -- State_3) -- ok state declaration
10333 elsif Missing_Parentheses then
10334 null;
10336 -- Otherwise the option is not allowed. Note that it
10337 -- is not possible to distinguish between an option
10338 -- and a state declaration when a previous state with
10339 -- options not properly parentheses.
10341 -- with Abstract_State
10342 -- (State_1 with ..., -- missing parentheses
10343 -- State_2); -- could be an option
10345 else
10346 SPARK_Msg_N
10347 ("simple option not allowed in state declaration",
10348 Opt);
10349 end if;
10351 -- Catch a case where missing parentheses around a state
10352 -- declaration with options cause a subsequent state
10353 -- declaration with options to be treated as an option.
10355 -- with Abstract_State
10356 -- (State_1 with ..., -- missing parentheses
10357 -- (State_2 with ...))
10359 elsif Nkind (Opt) = N_Extension_Aggregate then
10360 Missing_Parentheses := True;
10361 SPARK_Msg_N
10362 ("state declaration must be parenthesized",
10363 Ancestor_Part (State));
10365 -- Otherwise the option is malformed
10367 else
10368 SPARK_Msg_N ("malformed option", Opt);
10369 end if;
10371 Next (Opt);
10372 end loop;
10374 -- Options External and Part_Of appear as component
10375 -- associations.
10377 Opt := First (Component_Associations (State));
10378 while Present (Opt) loop
10379 Opt_Nam := First (Choices (Opt));
10381 if Nkind (Opt_Nam) = N_Identifier then
10382 if Chars (Opt_Nam) = Name_External then
10383 Analyze_External_Option (Opt);
10385 elsif Chars (Opt_Nam) = Name_Part_Of then
10386 Analyze_Part_Of_Option (Opt);
10388 else
10389 SPARK_Msg_N ("invalid state option", Opt);
10390 end if;
10391 else
10392 SPARK_Msg_N ("invalid state option", Opt);
10393 end if;
10395 Next (Opt);
10396 end loop;
10398 -- Any other attempt to declare a state is illegal. This is a
10399 -- syntax error, always report.
10401 else
10402 Error_Msg_N ("malformed abstract state declaration", State);
10403 return;
10404 end if;
10406 -- Guard against a junk state. In such cases no entity is
10407 -- generated and the subsequent checks cannot be applied.
10409 if Present (State_Id) then
10411 -- Verify whether the state does not introduce an illegal
10412 -- hidden state within a package subject to a null abstract
10413 -- state.
10415 Check_No_Hidden_State (State_Id);
10417 -- Check whether the lack of option Part_Of agrees with the
10418 -- placement of the abstract state with respect to the state
10419 -- space.
10421 if not Part_Of_Seen then
10422 Check_Missing_Part_Of (State_Id);
10423 end if;
10425 -- Associate the state with its related package
10427 if No (Abstract_States (Pack_Id)) then
10428 Set_Abstract_States (Pack_Id, New_Elmt_List);
10429 end if;
10431 Append_Elmt (State_Id, Abstract_States (Pack_Id));
10432 end if;
10433 end Analyze_Abstract_State;
10435 -- Local variables
10437 Context : constant Node_Id := Parent (Parent (N));
10438 Pack_Id : Entity_Id;
10439 State : Node_Id;
10441 -- Start of processing for Abstract_State
10443 begin
10444 GNAT_Pragma;
10445 Check_No_Identifiers;
10446 Check_Arg_Count (1);
10447 Ensure_Aggregate_Form (Arg1);
10449 -- Ensure the proper placement of the pragma. Abstract states must
10450 -- be associated with a package declaration.
10452 if not Nkind_In (Context, N_Generic_Package_Declaration,
10453 N_Package_Declaration)
10454 then
10455 Pragma_Misplaced;
10456 return;
10457 end if;
10459 State := Expression (Arg1);
10460 Pack_Id := Defining_Entity (Context);
10462 -- Mark the associated package as Ghost if it is subject to aspect
10463 -- or pragma Ghost as this affects the declaration of an abstract
10464 -- state.
10466 if Is_Subject_To_Ghost (Unit_Declaration_Node (Pack_Id)) then
10467 Set_Is_Ghost_Entity (Pack_Id);
10468 end if;
10470 -- Multiple non-null abstract states appear as an aggregate
10472 if Nkind (State) = N_Aggregate then
10473 State := First (Expressions (State));
10474 while Present (State) loop
10475 Analyze_Abstract_State (State, Pack_Id);
10476 Next (State);
10477 end loop;
10479 -- Various forms of a single abstract state. Note that these may
10480 -- include malformed state declarations.
10482 else
10483 Analyze_Abstract_State (State, Pack_Id);
10484 end if;
10486 -- Save the pragma for retrieval by other tools
10488 Add_Contract_Item (N, Pack_Id);
10490 -- Verify the declaration order of pragmas Abstract_State and
10491 -- Initializes.
10493 Check_Declaration_Order
10494 (First => N,
10495 Second => Get_Pragma (Pack_Id, Pragma_Initializes));
10496 end Abstract_State;
10498 ------------
10499 -- Ada_83 --
10500 ------------
10502 -- pragma Ada_83;
10504 -- Note: this pragma also has some specific processing in Par.Prag
10505 -- because we want to set the Ada version mode during parsing.
10507 when Pragma_Ada_83 =>
10508 GNAT_Pragma;
10509 Check_Arg_Count (0);
10511 -- We really should check unconditionally for proper configuration
10512 -- pragma placement, since we really don't want mixed Ada modes
10513 -- within a single unit, and the GNAT reference manual has always
10514 -- said this was a configuration pragma, but we did not check and
10515 -- are hesitant to add the check now.
10517 -- However, we really cannot tolerate mixing Ada 2005 or Ada 2012
10518 -- with Ada 83 or Ada 95, so we must check if we are in Ada 2005
10519 -- or Ada 2012 mode.
10521 if Ada_Version >= Ada_2005 then
10522 Check_Valid_Configuration_Pragma;
10523 end if;
10525 -- Now set Ada 83 mode
10527 Ada_Version := Ada_83;
10528 Ada_Version_Explicit := Ada_83;
10529 Ada_Version_Pragma := N;
10531 ------------
10532 -- Ada_95 --
10533 ------------
10535 -- pragma Ada_95;
10537 -- Note: this pragma also has some specific processing in Par.Prag
10538 -- because we want to set the Ada 83 version mode during parsing.
10540 when Pragma_Ada_95 =>
10541 GNAT_Pragma;
10542 Check_Arg_Count (0);
10544 -- We really should check unconditionally for proper configuration
10545 -- pragma placement, since we really don't want mixed Ada modes
10546 -- within a single unit, and the GNAT reference manual has always
10547 -- said this was a configuration pragma, but we did not check and
10548 -- are hesitant to add the check now.
10550 -- However, we really cannot tolerate mixing Ada 2005 with Ada 83
10551 -- or Ada 95, so we must check if we are in Ada 2005 mode.
10553 if Ada_Version >= Ada_2005 then
10554 Check_Valid_Configuration_Pragma;
10555 end if;
10557 -- Now set Ada 95 mode
10559 Ada_Version := Ada_95;
10560 Ada_Version_Explicit := Ada_95;
10561 Ada_Version_Pragma := N;
10563 ---------------------
10564 -- Ada_05/Ada_2005 --
10565 ---------------------
10567 -- pragma Ada_05;
10568 -- pragma Ada_05 (LOCAL_NAME);
10570 -- pragma Ada_2005;
10571 -- pragma Ada_2005 (LOCAL_NAME):
10573 -- Note: these pragmas also have some specific processing in Par.Prag
10574 -- because we want to set the Ada 2005 version mode during parsing.
10576 -- The one argument form is used for managing the transition from
10577 -- Ada 95 to Ada 2005 in the run-time library. If an entity is marked
10578 -- as Ada_2005 only, then referencing the entity in Ada_83 or Ada_95
10579 -- mode will generate a warning. In addition, in Ada_83 or Ada_95
10580 -- mode, a preference rule is established which does not choose
10581 -- such an entity unless it is unambiguously specified. This avoids
10582 -- extra subprograms marked this way from generating ambiguities in
10583 -- otherwise legal pre-Ada_2005 programs. The one argument form is
10584 -- intended for exclusive use in the GNAT run-time library.
10586 when Pragma_Ada_05 | Pragma_Ada_2005 => declare
10587 E_Id : Node_Id;
10589 begin
10590 GNAT_Pragma;
10592 if Arg_Count = 1 then
10593 Check_Arg_Is_Local_Name (Arg1);
10594 E_Id := Get_Pragma_Arg (Arg1);
10596 if Etype (E_Id) = Any_Type then
10597 return;
10598 end if;
10600 Set_Is_Ada_2005_Only (Entity (E_Id));
10601 Record_Rep_Item (Entity (E_Id), N);
10603 else
10604 Check_Arg_Count (0);
10606 -- For Ada_2005 we unconditionally enforce the documented
10607 -- configuration pragma placement, since we do not want to
10608 -- tolerate mixed modes in a unit involving Ada 2005. That
10609 -- would cause real difficulties for those cases where there
10610 -- are incompatibilities between Ada 95 and Ada 2005.
10612 Check_Valid_Configuration_Pragma;
10614 -- Now set appropriate Ada mode
10616 Ada_Version := Ada_2005;
10617 Ada_Version_Explicit := Ada_2005;
10618 Ada_Version_Pragma := N;
10619 end if;
10620 end;
10622 ---------------------
10623 -- Ada_12/Ada_2012 --
10624 ---------------------
10626 -- pragma Ada_12;
10627 -- pragma Ada_12 (LOCAL_NAME);
10629 -- pragma Ada_2012;
10630 -- pragma Ada_2012 (LOCAL_NAME):
10632 -- Note: these pragmas also have some specific processing in Par.Prag
10633 -- because we want to set the Ada 2012 version mode during parsing.
10635 -- The one argument form is used for managing the transition from Ada
10636 -- 2005 to Ada 2012 in the run-time library. If an entity is marked
10637 -- as Ada_201 only, then referencing the entity in any pre-Ada_2012
10638 -- mode will generate a warning. In addition, in any pre-Ada_2012
10639 -- mode, a preference rule is established which does not choose
10640 -- such an entity unless it is unambiguously specified. This avoids
10641 -- extra subprograms marked this way from generating ambiguities in
10642 -- otherwise legal pre-Ada_2012 programs. The one argument form is
10643 -- intended for exclusive use in the GNAT run-time library.
10645 when Pragma_Ada_12 | Pragma_Ada_2012 => declare
10646 E_Id : Node_Id;
10648 begin
10649 GNAT_Pragma;
10651 if Arg_Count = 1 then
10652 Check_Arg_Is_Local_Name (Arg1);
10653 E_Id := Get_Pragma_Arg (Arg1);
10655 if Etype (E_Id) = Any_Type then
10656 return;
10657 end if;
10659 Set_Is_Ada_2012_Only (Entity (E_Id));
10660 Record_Rep_Item (Entity (E_Id), N);
10662 else
10663 Check_Arg_Count (0);
10665 -- For Ada_2012 we unconditionally enforce the documented
10666 -- configuration pragma placement, since we do not want to
10667 -- tolerate mixed modes in a unit involving Ada 2012. That
10668 -- would cause real difficulties for those cases where there
10669 -- are incompatibilities between Ada 95 and Ada 2012. We could
10670 -- allow mixing of Ada 2005 and Ada 2012 but it's not worth it.
10672 Check_Valid_Configuration_Pragma;
10674 -- Now set appropriate Ada mode
10676 Ada_Version := Ada_2012;
10677 Ada_Version_Explicit := Ada_2012;
10678 Ada_Version_Pragma := N;
10679 end if;
10680 end;
10682 ----------------------
10683 -- All_Calls_Remote --
10684 ----------------------
10686 -- pragma All_Calls_Remote [(library_package_NAME)];
10688 when Pragma_All_Calls_Remote => All_Calls_Remote : declare
10689 Lib_Entity : Entity_Id;
10691 begin
10692 Check_Ada_83_Warning;
10693 Check_Valid_Library_Unit_Pragma;
10695 if Nkind (N) = N_Null_Statement then
10696 return;
10697 end if;
10699 Lib_Entity := Find_Lib_Unit_Name;
10701 -- This pragma should only apply to a RCI unit (RM E.2.3(23))
10703 if Present (Lib_Entity)
10704 and then not Debug_Flag_U
10705 then
10706 if not Is_Remote_Call_Interface (Lib_Entity) then
10707 Error_Pragma ("pragma% only apply to rci unit");
10709 -- Set flag for entity of the library unit
10711 else
10712 Set_Has_All_Calls_Remote (Lib_Entity);
10713 end if;
10715 end if;
10716 end All_Calls_Remote;
10718 ---------------------------
10719 -- Allow_Integer_Address --
10720 ---------------------------
10722 -- pragma Allow_Integer_Address;
10724 when Pragma_Allow_Integer_Address =>
10725 GNAT_Pragma;
10726 Check_Valid_Configuration_Pragma;
10727 Check_Arg_Count (0);
10729 -- If Address is a private type, then set the flag to allow
10730 -- integer address values. If Address is not private, then this
10731 -- pragma has no purpose, so it is simply ignored. Not clear if
10732 -- there are any such targets now.
10734 if Opt.Address_Is_Private then
10735 Opt.Allow_Integer_Address := True;
10736 end if;
10738 --------------
10739 -- Annotate --
10740 --------------
10742 -- pragma Annotate
10743 -- (IDENTIFIER [, IDENTIFIER {, ARG}] [,Entity => local_NAME]);
10744 -- ARG ::= NAME | EXPRESSION
10746 -- The first two arguments are by convention intended to refer to an
10747 -- external tool and a tool-specific function. These arguments are
10748 -- not analyzed.
10750 when Pragma_Annotate => Annotate : declare
10751 Arg : Node_Id;
10752 Exp : Node_Id;
10754 begin
10755 GNAT_Pragma;
10756 Check_At_Least_N_Arguments (1);
10758 -- See if last argument is Entity => local_Name, and if so process
10759 -- and then remove it for remaining processing.
10761 declare
10762 Last_Arg : constant Node_Id :=
10763 Last (Pragma_Argument_Associations (N));
10765 begin
10766 if Nkind (Last_Arg) = N_Pragma_Argument_Association
10767 and then Chars (Last_Arg) = Name_Entity
10768 then
10769 Check_Arg_Is_Local_Name (Last_Arg);
10770 Arg_Count := Arg_Count - 1;
10772 -- Not allowed in compiler units (bootstrap issues)
10774 Check_Compiler_Unit ("Entity for pragma Annotate", N);
10775 end if;
10776 end;
10778 -- Continue processing with last argument removed for now
10780 Check_Arg_Is_Identifier (Arg1);
10781 Check_No_Identifiers;
10782 Store_Note (N);
10784 -- Second parameter is optional, it is never analyzed
10786 if No (Arg2) then
10787 null;
10789 -- Here if we have a second parameter
10791 else
10792 -- Second parameter must be identifier
10794 Check_Arg_Is_Identifier (Arg2);
10796 -- Process remaining parameters if any
10798 Arg := Next (Arg2);
10799 while Present (Arg) loop
10800 Exp := Get_Pragma_Arg (Arg);
10801 Analyze (Exp);
10803 if Is_Entity_Name (Exp) then
10804 null;
10806 -- For string literals, we assume Standard_String as the
10807 -- type, unless the string contains wide or wide_wide
10808 -- characters.
10810 elsif Nkind (Exp) = N_String_Literal then
10811 if Has_Wide_Wide_Character (Exp) then
10812 Resolve (Exp, Standard_Wide_Wide_String);
10813 elsif Has_Wide_Character (Exp) then
10814 Resolve (Exp, Standard_Wide_String);
10815 else
10816 Resolve (Exp, Standard_String);
10817 end if;
10819 elsif Is_Overloaded (Exp) then
10820 Error_Pragma_Arg
10821 ("ambiguous argument for pragma%", Exp);
10823 else
10824 Resolve (Exp);
10825 end if;
10827 Next (Arg);
10828 end loop;
10829 end if;
10830 end Annotate;
10832 -------------------------------------------------
10833 -- Assert/Assert_And_Cut/Assume/Loop_Invariant --
10834 -------------------------------------------------
10836 -- pragma Assert
10837 -- ( [Check => ] Boolean_EXPRESSION
10838 -- [, [Message =>] Static_String_EXPRESSION]);
10840 -- pragma Assert_And_Cut
10841 -- ( [Check => ] Boolean_EXPRESSION
10842 -- [, [Message =>] Static_String_EXPRESSION]);
10844 -- pragma Assume
10845 -- ( [Check => ] Boolean_EXPRESSION
10846 -- [, [Message =>] Static_String_EXPRESSION]);
10848 -- pragma Loop_Invariant
10849 -- ( [Check => ] Boolean_EXPRESSION
10850 -- [, [Message =>] Static_String_EXPRESSION]);
10852 when Pragma_Assert |
10853 Pragma_Assert_And_Cut |
10854 Pragma_Assume |
10855 Pragma_Loop_Invariant =>
10856 Assert : declare
10857 function Contains_Loop_Entry (Expr : Node_Id) return Boolean;
10858 -- Determine whether expression Expr contains a Loop_Entry
10859 -- attribute reference.
10861 -------------------------
10862 -- Contains_Loop_Entry --
10863 -------------------------
10865 function Contains_Loop_Entry (Expr : Node_Id) return Boolean is
10866 Has_Loop_Entry : Boolean := False;
10868 function Process (N : Node_Id) return Traverse_Result;
10869 -- Process function for traversal to look for Loop_Entry
10871 -------------
10872 -- Process --
10873 -------------
10875 function Process (N : Node_Id) return Traverse_Result is
10876 begin
10877 if Nkind (N) = N_Attribute_Reference
10878 and then Attribute_Name (N) = Name_Loop_Entry
10879 then
10880 Has_Loop_Entry := True;
10881 return Abandon;
10882 else
10883 return OK;
10884 end if;
10885 end Process;
10887 procedure Traverse is new Traverse_Proc (Process);
10889 -- Start of processing for Contains_Loop_Entry
10891 begin
10892 Traverse (Expr);
10893 return Has_Loop_Entry;
10894 end Contains_Loop_Entry;
10896 -- Local variables
10898 Expr : Node_Id;
10899 Newa : List_Id;
10901 -- Start of processing for Assert
10903 begin
10904 -- Assert is an Ada 2005 RM-defined pragma
10906 if Prag_Id = Pragma_Assert then
10907 Ada_2005_Pragma;
10909 -- The remaining ones are GNAT pragmas
10911 else
10912 GNAT_Pragma;
10913 end if;
10915 Check_At_Least_N_Arguments (1);
10916 Check_At_Most_N_Arguments (2);
10917 Check_Arg_Order ((Name_Check, Name_Message));
10918 Check_Optional_Identifier (Arg1, Name_Check);
10919 Expr := Get_Pragma_Arg (Arg1);
10921 -- Special processing for Loop_Invariant, Loop_Variant or for
10922 -- other cases where a Loop_Entry attribute is present. If the
10923 -- assertion pragma contains attribute Loop_Entry, ensure that
10924 -- the related pragma is within a loop.
10926 if Prag_Id = Pragma_Loop_Invariant
10927 or else Prag_Id = Pragma_Loop_Variant
10928 or else Contains_Loop_Entry (Expr)
10929 then
10930 Check_Loop_Pragma_Placement;
10932 -- Perform preanalysis to deal with embedded Loop_Entry
10933 -- attributes.
10935 Preanalyze_Assert_Expression (Expression (Arg1), Any_Boolean);
10936 end if;
10938 -- Implement Assert[_And_Cut]/Assume/Loop_Invariant by generating
10939 -- a corresponding Check pragma:
10941 -- pragma Check (name, condition [, msg]);
10943 -- Where name is the identifier matching the pragma name. So
10944 -- rewrite pragma in this manner, transfer the message argument
10945 -- if present, and analyze the result
10947 -- Note: When dealing with a semantically analyzed tree, the
10948 -- information that a Check node N corresponds to a source Assert,
10949 -- Assume, or Assert_And_Cut pragma can be retrieved from the
10950 -- pragma kind of Original_Node(N).
10952 Newa := New_List (
10953 Make_Pragma_Argument_Association (Loc,
10954 Expression => Make_Identifier (Loc, Pname)),
10955 Make_Pragma_Argument_Association (Sloc (Expr),
10956 Expression => Expr));
10958 if Arg_Count > 1 then
10959 Check_Optional_Identifier (Arg2, Name_Message);
10961 -- Provide semantic annnotations for optional argument, for
10962 -- ASIS use, before rewriting.
10964 Preanalyze_And_Resolve (Expression (Arg2), Standard_String);
10965 Append_To (Newa, New_Copy_Tree (Arg2));
10966 end if;
10968 -- Rewrite as Check pragma
10970 Rewrite (N,
10971 Make_Pragma (Loc,
10972 Chars => Name_Check,
10973 Pragma_Argument_Associations => Newa));
10974 Analyze (N);
10975 end Assert;
10977 ----------------------
10978 -- Assertion_Policy --
10979 ----------------------
10981 -- pragma Assertion_Policy (POLICY_IDENTIFIER);
10983 -- The following form is Ada 2012 only, but we allow it in all modes
10985 -- Pragma Assertion_Policy (
10986 -- ASSERTION_KIND => POLICY_IDENTIFIER
10987 -- {, ASSERTION_KIND => POLICY_IDENTIFIER});
10989 -- ASSERTION_KIND ::= RM_ASSERTION_KIND | ID_ASSERTION_KIND
10991 -- RM_ASSERTION_KIND ::= Assert |
10992 -- Static_Predicate |
10993 -- Dynamic_Predicate |
10994 -- Pre |
10995 -- Pre'Class |
10996 -- Post |
10997 -- Post'Class |
10998 -- Type_Invariant |
10999 -- Type_Invariant'Class
11001 -- ID_ASSERTION_KIND ::= Assert_And_Cut |
11002 -- Assume |
11003 -- Contract_Cases |
11004 -- Debug |
11005 -- Default_Initial_Condition |
11006 -- Ghost |
11007 -- Initial_Condition |
11008 -- Loop_Invariant |
11009 -- Loop_Variant |
11010 -- Postcondition |
11011 -- Precondition |
11012 -- Predicate |
11013 -- Refined_Post |
11014 -- Statement_Assertions
11016 -- Note: The RM_ASSERTION_KIND list is language-defined, and the
11017 -- ID_ASSERTION_KIND list contains implementation-defined additions
11018 -- recognized by GNAT. The effect is to control the behavior of
11019 -- identically named aspects and pragmas, depending on the specified
11020 -- policy identifier:
11022 -- POLICY_IDENTIFIER ::= Check | Disable | Ignore
11024 -- Note: Check and Ignore are language-defined. Disable is a GNAT
11025 -- implementation defined addition that results in totally ignoring
11026 -- the corresponding assertion. If Disable is specified, then the
11027 -- argument of the assertion is not even analyzed. This is useful
11028 -- when the aspect/pragma argument references entities in a with'ed
11029 -- package that is replaced by a dummy package in the final build.
11031 -- Note: the attribute forms Pre'Class, Post'Class, Invariant'Class,
11032 -- and Type_Invariant'Class were recognized by the parser and
11033 -- transformed into references to the special internal identifiers
11034 -- _Pre, _Post, _Invariant, and _Type_Invariant, so no special
11035 -- processing is required here.
11037 when Pragma_Assertion_Policy => Assertion_Policy : declare
11038 Arg : Node_Id;
11039 Kind : Name_Id;
11040 LocP : Source_Ptr;
11041 Policy : Node_Id;
11043 begin
11044 Ada_2005_Pragma;
11046 -- This can always appear as a configuration pragma
11048 if Is_Configuration_Pragma then
11049 null;
11051 -- It can also appear in a declarative part or package spec in Ada
11052 -- 2012 mode. We allow this in other modes, but in that case we
11053 -- consider that we have an Ada 2012 pragma on our hands.
11055 else
11056 Check_Is_In_Decl_Part_Or_Package_Spec;
11057 Ada_2012_Pragma;
11058 end if;
11060 -- One argument case with no identifier (first form above)
11062 if Arg_Count = 1
11063 and then (Nkind (Arg1) /= N_Pragma_Argument_Association
11064 or else Chars (Arg1) = No_Name)
11065 then
11066 Check_Arg_Is_One_Of
11067 (Arg1, Name_Check, Name_Disable, Name_Ignore);
11069 -- Treat one argument Assertion_Policy as equivalent to:
11071 -- pragma Check_Policy (Assertion, policy)
11073 -- So rewrite pragma in that manner and link on to the chain
11074 -- of Check_Policy pragmas, marking the pragma as analyzed.
11076 Policy := Get_Pragma_Arg (Arg1);
11078 Rewrite (N,
11079 Make_Pragma (Loc,
11080 Chars => Name_Check_Policy,
11081 Pragma_Argument_Associations => New_List (
11082 Make_Pragma_Argument_Association (Loc,
11083 Expression => Make_Identifier (Loc, Name_Assertion)),
11085 Make_Pragma_Argument_Association (Loc,
11086 Expression =>
11087 Make_Identifier (Sloc (Policy), Chars (Policy))))));
11088 Analyze (N);
11090 -- Here if we have two or more arguments
11092 else
11093 Check_At_Least_N_Arguments (1);
11094 Ada_2012_Pragma;
11096 -- Loop through arguments
11098 Arg := Arg1;
11099 while Present (Arg) loop
11100 LocP := Sloc (Arg);
11102 -- Kind must be specified
11104 if Nkind (Arg) /= N_Pragma_Argument_Association
11105 or else Chars (Arg) = No_Name
11106 then
11107 Error_Pragma_Arg
11108 ("missing assertion kind for pragma%", Arg);
11109 end if;
11111 -- Check Kind and Policy have allowed forms
11113 Kind := Chars (Arg);
11115 if not Is_Valid_Assertion_Kind (Kind) then
11116 Error_Pragma_Arg
11117 ("invalid assertion kind for pragma%", Arg);
11118 end if;
11120 Check_Arg_Is_One_Of
11121 (Arg, Name_Check, Name_Disable, Name_Ignore);
11123 -- Rewrite the Assertion_Policy pragma as a series of
11124 -- Check_Policy pragmas of the form:
11126 -- Check_Policy (Kind, Policy);
11128 -- Note: the insertion of the pragmas cannot be done with
11129 -- Insert_Action because in the configuration case, there
11130 -- are no scopes on the scope stack and the mechanism will
11131 -- fail.
11133 Insert_Before_And_Analyze (N,
11134 Make_Pragma (LocP,
11135 Chars => Name_Check_Policy,
11136 Pragma_Argument_Associations => New_List (
11137 Make_Pragma_Argument_Association (LocP,
11138 Expression => Make_Identifier (LocP, Kind)),
11139 Make_Pragma_Argument_Association (LocP,
11140 Expression => Get_Pragma_Arg (Arg)))));
11142 Arg := Next (Arg);
11143 end loop;
11145 -- Rewrite the Assertion_Policy pragma as null since we have
11146 -- now inserted all the equivalent Check pragmas.
11148 Rewrite (N, Make_Null_Statement (Loc));
11149 Analyze (N);
11150 end if;
11151 end Assertion_Policy;
11153 ------------------------------
11154 -- Assume_No_Invalid_Values --
11155 ------------------------------
11157 -- pragma Assume_No_Invalid_Values (On | Off);
11159 when Pragma_Assume_No_Invalid_Values =>
11160 GNAT_Pragma;
11161 Check_Valid_Configuration_Pragma;
11162 Check_Arg_Count (1);
11163 Check_No_Identifiers;
11164 Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
11166 if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
11167 Assume_No_Invalid_Values := True;
11168 else
11169 Assume_No_Invalid_Values := False;
11170 end if;
11172 --------------------------
11173 -- Attribute_Definition --
11174 --------------------------
11176 -- pragma Attribute_Definition
11177 -- ([Attribute =>] ATTRIBUTE_DESIGNATOR,
11178 -- [Entity =>] LOCAL_NAME,
11179 -- [Expression =>] EXPRESSION | NAME);
11181 when Pragma_Attribute_Definition => Attribute_Definition : declare
11182 Attribute_Designator : constant Node_Id := Get_Pragma_Arg (Arg1);
11183 Aname : Name_Id;
11185 begin
11186 GNAT_Pragma;
11187 Check_Arg_Count (3);
11188 Check_Optional_Identifier (Arg1, "attribute");
11189 Check_Optional_Identifier (Arg2, "entity");
11190 Check_Optional_Identifier (Arg3, "expression");
11192 if Nkind (Attribute_Designator) /= N_Identifier then
11193 Error_Msg_N ("attribute name expected", Attribute_Designator);
11194 return;
11195 end if;
11197 Check_Arg_Is_Local_Name (Arg2);
11199 -- If the attribute is not recognized, then issue a warning (not
11200 -- an error), and ignore the pragma.
11202 Aname := Chars (Attribute_Designator);
11204 if not Is_Attribute_Name (Aname) then
11205 Bad_Attribute (Attribute_Designator, Aname, Warn => True);
11206 return;
11207 end if;
11209 -- Otherwise, rewrite the pragma as an attribute definition clause
11211 Rewrite (N,
11212 Make_Attribute_Definition_Clause (Loc,
11213 Name => Get_Pragma_Arg (Arg2),
11214 Chars => Aname,
11215 Expression => Get_Pragma_Arg (Arg3)));
11216 Analyze (N);
11217 end Attribute_Definition;
11219 ------------------------------------------------------------------
11220 -- Async_Readers/Async_Writers/Effective_Reads/Effective_Writes --
11221 ------------------------------------------------------------------
11223 -- pragma Asynch_Readers ( object_LOCAL_NAME [, FLAG] );
11224 -- pragma Asynch_Writers ( object_LOCAL_NAME [, FLAG] );
11225 -- pragma Effective_Reads ( object_LOCAL_NAME [, FLAG] );
11226 -- pragma Effective_Writes ( object_LOCAL_NAME [, FLAG] );
11228 -- FLAG ::= boolean_EXPRESSION
11230 when Pragma_Async_Readers |
11231 Pragma_Async_Writers |
11232 Pragma_Effective_Reads |
11233 Pragma_Effective_Writes =>
11234 Async_Effective : declare
11235 Duplic : Node_Id;
11236 Expr : Node_Id;
11237 Obj : Node_Id;
11238 Obj_Id : Entity_Id;
11240 begin
11241 GNAT_Pragma;
11242 Check_No_Identifiers;
11243 Check_At_Least_N_Arguments (1);
11244 Check_At_Most_N_Arguments (2);
11245 Check_Arg_Is_Local_Name (Arg1);
11246 Error_Msg_Name_1 := Pname;
11248 Obj := Get_Pragma_Arg (Arg1);
11249 Expr := Get_Pragma_Arg (Arg2);
11251 -- Perform minimal verification to ensure that the argument is at
11252 -- least a variable. Subsequent finer grained checks will be done
11253 -- at the end of the declarative region the contains the pragma.
11255 if Is_Entity_Name (Obj)
11256 and then Present (Entity (Obj))
11257 and then Ekind (Entity (Obj)) = E_Variable
11258 then
11259 Obj_Id := Entity (Obj);
11261 -- Detect a duplicate pragma. Note that it is not efficient to
11262 -- examine preceding statements as Boolean aspects may appear
11263 -- anywhere between the related object declaration and its
11264 -- freeze point. As an alternative, inspect the contents of the
11265 -- variable contract.
11267 Duplic := Get_Pragma (Obj_Id, Prag_Id);
11269 if Present (Duplic) then
11270 Error_Msg_Sloc := Sloc (Duplic);
11271 Error_Msg_N ("pragma % duplicates pragma declared #", N);
11273 -- No duplicate detected
11275 else
11276 if Present (Expr) then
11277 Preanalyze_And_Resolve (Expr, Standard_Boolean);
11278 end if;
11280 -- Chain the pragma on the contract for further processing
11282 Add_Contract_Item (N, Obj_Id);
11283 end if;
11284 else
11285 Error_Pragma ("pragma % must apply to a volatile object");
11286 end if;
11287 end Async_Effective;
11289 ------------------
11290 -- Asynchronous --
11291 ------------------
11293 -- pragma Asynchronous (LOCAL_NAME);
11295 when Pragma_Asynchronous => Asynchronous : declare
11296 Nm : Entity_Id;
11297 C_Ent : Entity_Id;
11298 L : List_Id;
11299 S : Node_Id;
11300 N : Node_Id;
11301 Formal : Entity_Id;
11303 procedure Process_Async_Pragma;
11304 -- Common processing for procedure and access-to-procedure case
11306 --------------------------
11307 -- Process_Async_Pragma --
11308 --------------------------
11310 procedure Process_Async_Pragma is
11311 begin
11312 if No (L) then
11313 Set_Is_Asynchronous (Nm);
11314 return;
11315 end if;
11317 -- The formals should be of mode IN (RM E.4.1(6))
11319 S := First (L);
11320 while Present (S) loop
11321 Formal := Defining_Identifier (S);
11323 if Nkind (Formal) = N_Defining_Identifier
11324 and then Ekind (Formal) /= E_In_Parameter
11325 then
11326 Error_Pragma_Arg
11327 ("pragma% procedure can only have IN parameter",
11328 Arg1);
11329 end if;
11331 Next (S);
11332 end loop;
11334 Set_Is_Asynchronous (Nm);
11335 end Process_Async_Pragma;
11337 -- Start of processing for pragma Asynchronous
11339 begin
11340 Check_Ada_83_Warning;
11341 Check_No_Identifiers;
11342 Check_Arg_Count (1);
11343 Check_Arg_Is_Local_Name (Arg1);
11345 if Debug_Flag_U then
11346 return;
11347 end if;
11349 C_Ent := Cunit_Entity (Current_Sem_Unit);
11350 Analyze (Get_Pragma_Arg (Arg1));
11351 Nm := Entity (Get_Pragma_Arg (Arg1));
11353 if not Is_Remote_Call_Interface (C_Ent)
11354 and then not Is_Remote_Types (C_Ent)
11355 then
11356 -- This pragma should only appear in an RCI or Remote Types
11357 -- unit (RM E.4.1(4)).
11359 Error_Pragma
11360 ("pragma% not in Remote_Call_Interface or Remote_Types unit");
11361 end if;
11363 if Ekind (Nm) = E_Procedure
11364 and then Nkind (Parent (Nm)) = N_Procedure_Specification
11365 then
11366 if not Is_Remote_Call_Interface (Nm) then
11367 Error_Pragma_Arg
11368 ("pragma% cannot be applied on non-remote procedure",
11369 Arg1);
11370 end if;
11372 L := Parameter_Specifications (Parent (Nm));
11373 Process_Async_Pragma;
11374 return;
11376 elsif Ekind (Nm) = E_Function then
11377 Error_Pragma_Arg
11378 ("pragma% cannot be applied to function", Arg1);
11380 elsif Is_Remote_Access_To_Subprogram_Type (Nm) then
11381 if Is_Record_Type (Nm) then
11383 -- A record type that is the Equivalent_Type for a remote
11384 -- access-to-subprogram type.
11386 N := Declaration_Node (Corresponding_Remote_Type (Nm));
11388 else
11389 -- A non-expanded RAS type (distribution is not enabled)
11391 N := Declaration_Node (Nm);
11392 end if;
11394 if Nkind (N) = N_Full_Type_Declaration
11395 and then Nkind (Type_Definition (N)) =
11396 N_Access_Procedure_Definition
11397 then
11398 L := Parameter_Specifications (Type_Definition (N));
11399 Process_Async_Pragma;
11401 if Is_Asynchronous (Nm)
11402 and then Expander_Active
11403 and then Get_PCS_Name /= Name_No_DSA
11404 then
11405 RACW_Type_Is_Asynchronous (Underlying_RACW_Type (Nm));
11406 end if;
11408 else
11409 Error_Pragma_Arg
11410 ("pragma% cannot reference access-to-function type",
11411 Arg1);
11412 end if;
11414 -- Only other possibility is Access-to-class-wide type
11416 elsif Is_Access_Type (Nm)
11417 and then Is_Class_Wide_Type (Designated_Type (Nm))
11418 then
11419 Check_First_Subtype (Arg1);
11420 Set_Is_Asynchronous (Nm);
11421 if Expander_Active then
11422 RACW_Type_Is_Asynchronous (Nm);
11423 end if;
11425 else
11426 Error_Pragma_Arg ("inappropriate argument for pragma%", Arg1);
11427 end if;
11428 end Asynchronous;
11430 ------------
11431 -- Atomic --
11432 ------------
11434 -- pragma Atomic (LOCAL_NAME);
11436 when Pragma_Atomic =>
11437 Process_Atomic_Independent_Shared_Volatile;
11439 -----------------------
11440 -- Atomic_Components --
11441 -----------------------
11443 -- pragma Atomic_Components (array_LOCAL_NAME);
11445 -- This processing is shared by Volatile_Components
11447 when Pragma_Atomic_Components |
11448 Pragma_Volatile_Components =>
11450 Atomic_Components : declare
11451 E_Id : Node_Id;
11452 E : Entity_Id;
11453 D : Node_Id;
11454 K : Node_Kind;
11456 begin
11457 Check_Ada_83_Warning;
11458 Check_No_Identifiers;
11459 Check_Arg_Count (1);
11460 Check_Arg_Is_Local_Name (Arg1);
11461 E_Id := Get_Pragma_Arg (Arg1);
11463 if Etype (E_Id) = Any_Type then
11464 return;
11465 end if;
11467 E := Entity (E_Id);
11469 Check_Duplicate_Pragma (E);
11471 if Rep_Item_Too_Early (E, N)
11472 or else
11473 Rep_Item_Too_Late (E, N)
11474 then
11475 return;
11476 end if;
11478 D := Declaration_Node (E);
11479 K := Nkind (D);
11481 if (K = N_Full_Type_Declaration and then Is_Array_Type (E))
11482 or else
11483 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
11484 and then Nkind (D) = N_Object_Declaration
11485 and then Nkind (Object_Definition (D)) =
11486 N_Constrained_Array_Definition)
11487 then
11488 -- The flag is set on the object, or on the base type
11490 if Nkind (D) /= N_Object_Declaration then
11491 E := Base_Type (E);
11492 end if;
11494 -- Atomic implies both Independent and Volatile
11496 if Prag_Id = Pragma_Atomic_Components then
11497 Set_Has_Atomic_Components (E);
11498 Set_Has_Independent_Components (E);
11499 end if;
11501 Set_Has_Volatile_Components (E);
11503 else
11504 Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
11505 end if;
11506 end Atomic_Components;
11508 --------------------
11509 -- Attach_Handler --
11510 --------------------
11512 -- pragma Attach_Handler (handler_NAME, EXPRESSION);
11514 when Pragma_Attach_Handler =>
11515 Check_Ada_83_Warning;
11516 Check_No_Identifiers;
11517 Check_Arg_Count (2);
11519 if No_Run_Time_Mode then
11520 Error_Msg_CRT ("Attach_Handler pragma", N);
11521 else
11522 Check_Interrupt_Or_Attach_Handler;
11524 -- The expression that designates the attribute may depend on a
11525 -- discriminant, and is therefore a per-object expression, to
11526 -- be expanded in the init proc. If expansion is enabled, then
11527 -- perform semantic checks on a copy only.
11529 declare
11530 Temp : Node_Id;
11531 Typ : Node_Id;
11532 Parg2 : constant Node_Id := Get_Pragma_Arg (Arg2);
11534 begin
11535 -- In Relaxed_RM_Semantics mode, we allow any static
11536 -- integer value, for compatibility with other compilers.
11538 if Relaxed_RM_Semantics
11539 and then Nkind (Parg2) = N_Integer_Literal
11540 then
11541 Typ := Standard_Integer;
11542 else
11543 Typ := RTE (RE_Interrupt_ID);
11544 end if;
11546 if Expander_Active then
11547 Temp := New_Copy_Tree (Parg2);
11548 Set_Parent (Temp, N);
11549 Preanalyze_And_Resolve (Temp, Typ);
11550 else
11551 Analyze (Parg2);
11552 Resolve (Parg2, Typ);
11553 end if;
11554 end;
11556 Process_Interrupt_Or_Attach_Handler;
11557 end if;
11559 --------------------
11560 -- C_Pass_By_Copy --
11561 --------------------
11563 -- pragma C_Pass_By_Copy ([Max_Size =>] static_integer_EXPRESSION);
11565 when Pragma_C_Pass_By_Copy => C_Pass_By_Copy : declare
11566 Arg : Node_Id;
11567 Val : Uint;
11569 begin
11570 GNAT_Pragma;
11571 Check_Valid_Configuration_Pragma;
11572 Check_Arg_Count (1);
11573 Check_Optional_Identifier (Arg1, "max_size");
11575 Arg := Get_Pragma_Arg (Arg1);
11576 Check_Arg_Is_OK_Static_Expression (Arg, Any_Integer);
11578 Val := Expr_Value (Arg);
11580 if Val <= 0 then
11581 Error_Pragma_Arg
11582 ("maximum size for pragma% must be positive", Arg1);
11584 elsif UI_Is_In_Int_Range (Val) then
11585 Default_C_Record_Mechanism := UI_To_Int (Val);
11587 -- If a giant value is given, Int'Last will do well enough.
11588 -- If sometime someone complains that a record larger than
11589 -- two gigabytes is not copied, we will worry about it then.
11591 else
11592 Default_C_Record_Mechanism := Mechanism_Type'Last;
11593 end if;
11594 end C_Pass_By_Copy;
11596 -----------
11597 -- Check --
11598 -----------
11600 -- pragma Check ([Name =>] CHECK_KIND,
11601 -- [Check =>] Boolean_EXPRESSION
11602 -- [,[Message =>] String_EXPRESSION]);
11604 -- CHECK_KIND ::= IDENTIFIER |
11605 -- Pre'Class |
11606 -- Post'Class |
11607 -- Invariant'Class |
11608 -- Type_Invariant'Class
11610 -- The identifiers Assertions and Statement_Assertions are not
11611 -- allowed, since they have special meaning for Check_Policy.
11613 when Pragma_Check => Check : declare
11614 Expr : Node_Id;
11615 Eloc : Source_Ptr;
11616 Cname : Name_Id;
11617 Str : Node_Id;
11619 begin
11620 GNAT_Pragma;
11621 Check_At_Least_N_Arguments (2);
11622 Check_At_Most_N_Arguments (3);
11623 Check_Optional_Identifier (Arg1, Name_Name);
11624 Check_Optional_Identifier (Arg2, Name_Check);
11626 if Arg_Count = 3 then
11627 Check_Optional_Identifier (Arg3, Name_Message);
11628 Str := Get_Pragma_Arg (Arg3);
11629 end if;
11631 Rewrite_Assertion_Kind (Get_Pragma_Arg (Arg1));
11632 Check_Arg_Is_Identifier (Arg1);
11633 Cname := Chars (Get_Pragma_Arg (Arg1));
11635 -- Check forbidden name Assertions or Statement_Assertions
11637 case Cname is
11638 when Name_Assertions =>
11639 Error_Pragma_Arg
11640 ("""Assertions"" is not allowed as a check kind "
11641 & "for pragma%", Arg1);
11643 when Name_Statement_Assertions =>
11644 Error_Pragma_Arg
11645 ("""Statement_Assertions"" is not allowed as a check kind "
11646 & "for pragma%", Arg1);
11648 when others =>
11649 null;
11650 end case;
11652 -- Check applicable policy. We skip this if Checked/Ignored status
11653 -- is already set (e.g. in the casse of a pragma from an aspect).
11655 if Is_Checked (N) or else Is_Ignored (N) then
11656 null;
11658 -- For a non-source pragma that is a rewriting of another pragma,
11659 -- copy the Is_Checked/Ignored status from the rewritten pragma.
11661 elsif Is_Rewrite_Substitution (N)
11662 and then Nkind (Original_Node (N)) = N_Pragma
11663 and then Original_Node (N) /= N
11664 then
11665 Set_Is_Ignored (N, Is_Ignored (Original_Node (N)));
11666 Set_Is_Checked (N, Is_Checked (Original_Node (N)));
11668 -- Otherwise query the applicable policy at this point
11670 else
11671 case Check_Kind (Cname) is
11672 when Name_Ignore =>
11673 Set_Is_Ignored (N, True);
11674 Set_Is_Checked (N, False);
11676 when Name_Check =>
11677 Set_Is_Ignored (N, False);
11678 Set_Is_Checked (N, True);
11680 -- For disable, rewrite pragma as null statement and skip
11681 -- rest of the analysis of the pragma.
11683 when Name_Disable =>
11684 Rewrite (N, Make_Null_Statement (Loc));
11685 Analyze (N);
11686 raise Pragma_Exit;
11688 -- No other possibilities
11690 when others =>
11691 raise Program_Error;
11692 end case;
11693 end if;
11695 -- If check kind was not Disable, then continue pragma analysis
11697 Expr := Get_Pragma_Arg (Arg2);
11699 -- Deal with SCO generation
11701 case Cname is
11702 when Name_Predicate |
11703 Name_Invariant =>
11705 -- Nothing to do: since checks occur in client units,
11706 -- the SCO for the aspect in the declaration unit is
11707 -- conservatively always enabled.
11709 null;
11711 when others =>
11713 if Is_Checked (N) and then not Split_PPC (N) then
11715 -- Mark aspect/pragma SCO as enabled
11717 Set_SCO_Pragma_Enabled (Loc);
11718 end if;
11719 end case;
11721 -- Deal with analyzing the string argument.
11723 if Arg_Count = 3 then
11725 -- If checks are not on we don't want any expansion (since
11726 -- such expansion would not get properly deleted) but
11727 -- we do want to analyze (to get proper references).
11728 -- The Preanalyze_And_Resolve routine does just what we want
11730 if Is_Ignored (N) then
11731 Preanalyze_And_Resolve (Str, Standard_String);
11733 -- Otherwise we need a proper analysis and expansion
11735 else
11736 Analyze_And_Resolve (Str, Standard_String);
11737 end if;
11738 end if;
11740 -- Now you might think we could just do the same with the Boolean
11741 -- expression if checks are off (and expansion is on) and then
11742 -- rewrite the check as a null statement. This would work but we
11743 -- would lose the useful warnings about an assertion being bound
11744 -- to fail even if assertions are turned off.
11746 -- So instead we wrap the boolean expression in an if statement
11747 -- that looks like:
11749 -- if False and then condition then
11750 -- null;
11751 -- end if;
11753 -- The reason we do this rewriting during semantic analysis rather
11754 -- than as part of normal expansion is that we cannot analyze and
11755 -- expand the code for the boolean expression directly, or it may
11756 -- cause insertion of actions that would escape the attempt to
11757 -- suppress the check code.
11759 -- Note that the Sloc for the if statement corresponds to the
11760 -- argument condition, not the pragma itself. The reason for
11761 -- this is that we may generate a warning if the condition is
11762 -- False at compile time, and we do not want to delete this
11763 -- warning when we delete the if statement.
11765 if Expander_Active and Is_Ignored (N) then
11766 Eloc := Sloc (Expr);
11768 Rewrite (N,
11769 Make_If_Statement (Eloc,
11770 Condition =>
11771 Make_And_Then (Eloc,
11772 Left_Opnd => New_Occurrence_Of (Standard_False, Eloc),
11773 Right_Opnd => Expr),
11774 Then_Statements => New_List (
11775 Make_Null_Statement (Eloc))));
11777 In_Assertion_Expr := In_Assertion_Expr + 1;
11778 Analyze (N);
11779 In_Assertion_Expr := In_Assertion_Expr - 1;
11781 -- Check is active or expansion not active. In these cases we can
11782 -- just go ahead and analyze the boolean with no worries.
11784 else
11785 In_Assertion_Expr := In_Assertion_Expr + 1;
11786 Analyze_And_Resolve (Expr, Any_Boolean);
11787 In_Assertion_Expr := In_Assertion_Expr - 1;
11788 end if;
11789 end Check;
11791 --------------------------
11792 -- Check_Float_Overflow --
11793 --------------------------
11795 -- pragma Check_Float_Overflow;
11797 when Pragma_Check_Float_Overflow =>
11798 GNAT_Pragma;
11799 Check_Valid_Configuration_Pragma;
11800 Check_Arg_Count (0);
11801 Check_Float_Overflow := not Machine_Overflows_On_Target;
11803 ----------------
11804 -- Check_Name --
11805 ----------------
11807 -- pragma Check_Name (check_IDENTIFIER);
11809 when Pragma_Check_Name =>
11810 GNAT_Pragma;
11811 Check_No_Identifiers;
11812 Check_Valid_Configuration_Pragma;
11813 Check_Arg_Count (1);
11814 Check_Arg_Is_Identifier (Arg1);
11816 declare
11817 Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
11819 begin
11820 for J in Check_Names.First .. Check_Names.Last loop
11821 if Check_Names.Table (J) = Nam then
11822 return;
11823 end if;
11824 end loop;
11826 Check_Names.Append (Nam);
11827 end;
11829 ------------------
11830 -- Check_Policy --
11831 ------------------
11833 -- This is the old style syntax, which is still allowed in all modes:
11835 -- pragma Check_Policy ([Name =>] CHECK_KIND
11836 -- [Policy =>] POLICY_IDENTIFIER);
11838 -- POLICY_IDENTIFIER ::= On | Off | Check | Disable | Ignore
11840 -- CHECK_KIND ::= IDENTIFIER |
11841 -- Pre'Class |
11842 -- Post'Class |
11843 -- Type_Invariant'Class |
11844 -- Invariant'Class
11846 -- This is the new style syntax, compatible with Assertion_Policy
11847 -- and also allowed in all modes.
11849 -- Pragma Check_Policy (
11850 -- CHECK_KIND => POLICY_IDENTIFIER
11851 -- {, CHECK_KIND => POLICY_IDENTIFIER});
11853 -- Note: the identifiers Name and Policy are not allowed as
11854 -- Check_Kind values. This avoids ambiguities between the old and
11855 -- new form syntax.
11857 when Pragma_Check_Policy => Check_Policy : declare
11858 Ident : Node_Id;
11859 Kind : Node_Id;
11861 begin
11862 GNAT_Pragma;
11863 Check_At_Least_N_Arguments (1);
11865 -- A Check_Policy pragma can appear either as a configuration
11866 -- pragma, or in a declarative part or a package spec (see RM
11867 -- 11.5(5) for rules for Suppress/Unsuppress which are also
11868 -- followed for Check_Policy).
11870 if not Is_Configuration_Pragma then
11871 Check_Is_In_Decl_Part_Or_Package_Spec;
11872 end if;
11874 -- Figure out if we have the old or new syntax. We have the
11875 -- old syntax if the first argument has no identifier, or the
11876 -- identifier is Name.
11878 if Nkind (Arg1) /= N_Pragma_Argument_Association
11879 or else Nam_In (Chars (Arg1), No_Name, Name_Name)
11880 then
11881 -- Old syntax
11883 Check_Arg_Count (2);
11884 Check_Optional_Identifier (Arg1, Name_Name);
11885 Kind := Get_Pragma_Arg (Arg1);
11886 Rewrite_Assertion_Kind (Kind);
11887 Check_Arg_Is_Identifier (Arg1);
11889 -- Check forbidden check kind
11891 if Nam_In (Chars (Kind), Name_Name, Name_Policy) then
11892 Error_Msg_Name_2 := Chars (Kind);
11893 Error_Pragma_Arg
11894 ("pragma% does not allow% as check name", Arg1);
11895 end if;
11897 -- Check policy
11899 Check_Optional_Identifier (Arg2, Name_Policy);
11900 Check_Arg_Is_One_Of
11901 (Arg2,
11902 Name_On, Name_Off, Name_Check, Name_Disable, Name_Ignore);
11903 Ident := Get_Pragma_Arg (Arg2);
11905 if Chars (Kind) = Name_Ghost then
11907 -- Pragma Check_Policy specifying a Ghost policy cannot
11908 -- occur within a ghost subprogram or package.
11910 if Within_Ghost_Scope then
11911 Error_Pragma
11912 ("pragma % cannot appear within ghost subprogram or "
11913 & "package");
11915 -- The policy identifier of pragma Ghost must be either
11916 -- Check or Ignore (SPARK RM 6.9(7)).
11918 elsif not Nam_In (Chars (Ident), Name_Check,
11919 Name_Ignore)
11920 then
11921 Error_Pragma_Arg
11922 ("argument of pragma % Ghost must be Check or Ignore",
11923 Arg2);
11924 end if;
11925 end if;
11927 -- And chain pragma on the Check_Policy_List for search
11929 Set_Next_Pragma (N, Opt.Check_Policy_List);
11930 Opt.Check_Policy_List := N;
11932 -- For the new syntax, what we do is to convert each argument to
11933 -- an old syntax equivalent. We do that because we want to chain
11934 -- old style Check_Policy pragmas for the search (we don't want
11935 -- to have to deal with multiple arguments in the search).
11937 else
11938 declare
11939 Arg : Node_Id;
11940 Argx : Node_Id;
11941 LocP : Source_Ptr;
11943 begin
11944 Arg := Arg1;
11945 while Present (Arg) loop
11946 LocP := Sloc (Arg);
11947 Argx := Get_Pragma_Arg (Arg);
11949 -- Kind must be specified
11951 if Nkind (Arg) /= N_Pragma_Argument_Association
11952 or else Chars (Arg) = No_Name
11953 then
11954 Error_Pragma_Arg
11955 ("missing assertion kind for pragma%", Arg);
11956 end if;
11958 -- Construct equivalent old form syntax Check_Policy
11959 -- pragma and insert it to get remaining checks.
11961 Insert_Action (N,
11962 Make_Pragma (LocP,
11963 Chars => Name_Check_Policy,
11964 Pragma_Argument_Associations => New_List (
11965 Make_Pragma_Argument_Association (LocP,
11966 Expression =>
11967 Make_Identifier (LocP, Chars (Arg))),
11968 Make_Pragma_Argument_Association (Sloc (Argx),
11969 Expression => Argx))));
11971 Arg := Next (Arg);
11972 end loop;
11974 -- Rewrite original Check_Policy pragma to null, since we
11975 -- have converted it into a series of old syntax pragmas.
11977 Rewrite (N, Make_Null_Statement (Loc));
11978 Analyze (N);
11979 end;
11980 end if;
11981 end Check_Policy;
11983 ---------------------
11984 -- CIL_Constructor --
11985 ---------------------
11987 -- pragma CIL_Constructor ([Entity =>] LOCAL_NAME);
11989 -- Processing for this pragma is shared with Java_Constructor
11991 -------------
11992 -- Comment --
11993 -------------
11995 -- pragma Comment (static_string_EXPRESSION)
11997 -- Processing for pragma Comment shares the circuitry for pragma
11998 -- Ident. The only differences are that Ident enforces a limit of 31
11999 -- characters on its argument, and also enforces limitations on
12000 -- placement for DEC compatibility. Pragma Comment shares neither of
12001 -- these restrictions.
12003 -------------------
12004 -- Common_Object --
12005 -------------------
12007 -- pragma Common_Object (
12008 -- [Internal =>] LOCAL_NAME
12009 -- [, [External =>] EXTERNAL_SYMBOL]
12010 -- [, [Size =>] EXTERNAL_SYMBOL]);
12012 -- Processing for this pragma is shared with Psect_Object
12014 ------------------------
12015 -- Compile_Time_Error --
12016 ------------------------
12018 -- pragma Compile_Time_Error
12019 -- (boolean_EXPRESSION, static_string_EXPRESSION);
12021 when Pragma_Compile_Time_Error =>
12022 GNAT_Pragma;
12023 Process_Compile_Time_Warning_Or_Error;
12025 --------------------------
12026 -- Compile_Time_Warning --
12027 --------------------------
12029 -- pragma Compile_Time_Warning
12030 -- (boolean_EXPRESSION, static_string_EXPRESSION);
12032 when Pragma_Compile_Time_Warning =>
12033 GNAT_Pragma;
12034 Process_Compile_Time_Warning_Or_Error;
12036 ---------------------------
12037 -- Compiler_Unit_Warning --
12038 ---------------------------
12040 -- pragma Compiler_Unit_Warning;
12042 -- Historical note
12044 -- Originally, we had only pragma Compiler_Unit, and it resulted in
12045 -- errors not warnings. This means that we had introduced a big extra
12046 -- inertia to compiler changes, since even if we implemented a new
12047 -- feature, and even if all versions to be used for bootstrapping
12048 -- implemented this new feature, we could not use it, since old
12049 -- compilers would give errors for using this feature in units
12050 -- having Compiler_Unit pragmas.
12052 -- By changing Compiler_Unit to Compiler_Unit_Warning, we solve the
12053 -- problem. We no longer have any units mentioning Compiler_Unit,
12054 -- so old compilers see Compiler_Unit_Warning which is unrecognized,
12055 -- and thus generates a warning which can be ignored. So that deals
12056 -- with the problem of old compilers not implementing the newer form
12057 -- of the pragma.
12059 -- Newer compilers recognize the new pragma, but generate warning
12060 -- messages instead of errors, which again can be ignored in the
12061 -- case of an old compiler which implements a wanted new feature
12062 -- but at the time felt like warning about it for older compilers.
12064 -- We retain Compiler_Unit so that new compilers can be used to build
12065 -- older run-times that use this pragma. That's an unusual case, but
12066 -- it's easy enough to handle, so why not?
12068 when Pragma_Compiler_Unit | Pragma_Compiler_Unit_Warning =>
12069 GNAT_Pragma;
12070 Check_Arg_Count (0);
12072 -- Only recognized in main unit
12074 if Current_Sem_Unit = Main_Unit then
12075 Compiler_Unit := True;
12076 end if;
12078 -----------------------------
12079 -- Complete_Representation --
12080 -----------------------------
12082 -- pragma Complete_Representation;
12084 when Pragma_Complete_Representation =>
12085 GNAT_Pragma;
12086 Check_Arg_Count (0);
12088 if Nkind (Parent (N)) /= N_Record_Representation_Clause then
12089 Error_Pragma
12090 ("pragma & must appear within record representation clause");
12091 end if;
12093 ----------------------------
12094 -- Complex_Representation --
12095 ----------------------------
12097 -- pragma Complex_Representation ([Entity =>] LOCAL_NAME);
12099 when Pragma_Complex_Representation => Complex_Representation : declare
12100 E_Id : Entity_Id;
12101 E : Entity_Id;
12102 Ent : Entity_Id;
12104 begin
12105 GNAT_Pragma;
12106 Check_Arg_Count (1);
12107 Check_Optional_Identifier (Arg1, Name_Entity);
12108 Check_Arg_Is_Local_Name (Arg1);
12109 E_Id := Get_Pragma_Arg (Arg1);
12111 if Etype (E_Id) = Any_Type then
12112 return;
12113 end if;
12115 E := Entity (E_Id);
12117 if not Is_Record_Type (E) then
12118 Error_Pragma_Arg
12119 ("argument for pragma% must be record type", Arg1);
12120 end if;
12122 Ent := First_Entity (E);
12124 if No (Ent)
12125 or else No (Next_Entity (Ent))
12126 or else Present (Next_Entity (Next_Entity (Ent)))
12127 or else not Is_Floating_Point_Type (Etype (Ent))
12128 or else Etype (Ent) /= Etype (Next_Entity (Ent))
12129 then
12130 Error_Pragma_Arg
12131 ("record for pragma% must have two fields of the same "
12132 & "floating-point type", Arg1);
12134 else
12135 Set_Has_Complex_Representation (Base_Type (E));
12137 -- We need to treat the type has having a non-standard
12138 -- representation, for back-end purposes, even though in
12139 -- general a complex will have the default representation
12140 -- of a record with two real components.
12142 Set_Has_Non_Standard_Rep (Base_Type (E));
12143 end if;
12144 end Complex_Representation;
12146 -------------------------
12147 -- Component_Alignment --
12148 -------------------------
12150 -- pragma Component_Alignment (
12151 -- [Form =>] ALIGNMENT_CHOICE
12152 -- [, [Name =>] type_LOCAL_NAME]);
12154 -- ALIGNMENT_CHOICE ::=
12155 -- Component_Size
12156 -- | Component_Size_4
12157 -- | Storage_Unit
12158 -- | Default
12160 when Pragma_Component_Alignment => Component_AlignmentP : declare
12161 Args : Args_List (1 .. 2);
12162 Names : constant Name_List (1 .. 2) := (
12163 Name_Form,
12164 Name_Name);
12166 Form : Node_Id renames Args (1);
12167 Name : Node_Id renames Args (2);
12169 Atype : Component_Alignment_Kind;
12170 Typ : Entity_Id;
12172 begin
12173 GNAT_Pragma;
12174 Gather_Associations (Names, Args);
12176 if No (Form) then
12177 Error_Pragma ("missing Form argument for pragma%");
12178 end if;
12180 Check_Arg_Is_Identifier (Form);
12182 -- Get proper alignment, note that Default = Component_Size on all
12183 -- machines we have so far, and we want to set this value rather
12184 -- than the default value to indicate that it has been explicitly
12185 -- set (and thus will not get overridden by the default component
12186 -- alignment for the current scope)
12188 if Chars (Form) = Name_Component_Size then
12189 Atype := Calign_Component_Size;
12191 elsif Chars (Form) = Name_Component_Size_4 then
12192 Atype := Calign_Component_Size_4;
12194 elsif Chars (Form) = Name_Default then
12195 Atype := Calign_Component_Size;
12197 elsif Chars (Form) = Name_Storage_Unit then
12198 Atype := Calign_Storage_Unit;
12200 else
12201 Error_Pragma_Arg
12202 ("invalid Form parameter for pragma%", Form);
12203 end if;
12205 -- Case with no name, supplied, affects scope table entry
12207 if No (Name) then
12208 Scope_Stack.Table
12209 (Scope_Stack.Last).Component_Alignment_Default := Atype;
12211 -- Case of name supplied
12213 else
12214 Check_Arg_Is_Local_Name (Name);
12215 Find_Type (Name);
12216 Typ := Entity (Name);
12218 if Typ = Any_Type
12219 or else Rep_Item_Too_Early (Typ, N)
12220 then
12221 return;
12222 else
12223 Typ := Underlying_Type (Typ);
12224 end if;
12226 if not Is_Record_Type (Typ)
12227 and then not Is_Array_Type (Typ)
12228 then
12229 Error_Pragma_Arg
12230 ("Name parameter of pragma% must identify record or "
12231 & "array type", Name);
12232 end if;
12234 -- An explicit Component_Alignment pragma overrides an
12235 -- implicit pragma Pack, but not an explicit one.
12237 if not Has_Pragma_Pack (Base_Type (Typ)) then
12238 Set_Is_Packed (Base_Type (Typ), False);
12239 Set_Component_Alignment (Base_Type (Typ), Atype);
12240 end if;
12241 end if;
12242 end Component_AlignmentP;
12244 --------------------
12245 -- Contract_Cases --
12246 --------------------
12248 -- pragma Contract_Cases ((CONTRACT_CASE {, CONTRACT_CASE));
12250 -- CONTRACT_CASE ::= CASE_GUARD => CONSEQUENCE
12252 -- CASE_GUARD ::= boolean_EXPRESSION | others
12254 -- CONSEQUENCE ::= boolean_EXPRESSION
12256 when Pragma_Contract_Cases => Contract_Cases : declare
12257 Subp_Decl : Node_Id;
12259 begin
12260 GNAT_Pragma;
12261 Check_No_Identifiers;
12262 Check_Arg_Count (1);
12263 Ensure_Aggregate_Form (Arg1);
12265 -- The pragma is analyzed at the end of the declarative part which
12266 -- contains the related subprogram. Reset the analyzed flag.
12268 Set_Analyzed (N, False);
12270 -- Ensure the proper placement of the pragma. Contract_Cases must
12271 -- be associated with a subprogram declaration or a body that acts
12272 -- as a spec.
12274 Subp_Decl :=
12275 Find_Related_Subprogram_Or_Body (N, Do_Checks => True);
12277 if Nkind (Subp_Decl) = N_Subprogram_Declaration then
12278 null;
12280 -- Body acts as spec
12282 elsif Nkind (Subp_Decl) = N_Subprogram_Body
12283 and then No (Corresponding_Spec (Subp_Decl))
12284 then
12285 null;
12287 -- Body stub acts as spec
12289 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
12290 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
12291 then
12292 null;
12294 else
12295 Pragma_Misplaced;
12296 return;
12297 end if;
12299 -- When the pragma appears on a subprogram body, perform the full
12300 -- analysis now.
12302 if Nkind (Subp_Decl) = N_Subprogram_Body then
12303 Analyze_Contract_Cases_In_Decl_Part (N);
12305 -- When Contract_Cases applies to a subprogram compilation unit,
12306 -- the corresponding pragma is placed after the unit's declaration
12307 -- node and needs to be analyzed immediately.
12309 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration
12310 and then Nkind (Parent (Subp_Decl)) = N_Compilation_Unit
12311 then
12312 Analyze_Contract_Cases_In_Decl_Part (N);
12313 end if;
12315 -- Chain the pragma on the contract for further processing
12317 Add_Contract_Item (N, Defining_Entity (Subp_Decl));
12318 end Contract_Cases;
12320 ----------------
12321 -- Controlled --
12322 ----------------
12324 -- pragma Controlled (first_subtype_LOCAL_NAME);
12326 when Pragma_Controlled => Controlled : declare
12327 Arg : Node_Id;
12329 begin
12330 Check_No_Identifiers;
12331 Check_Arg_Count (1);
12332 Check_Arg_Is_Local_Name (Arg1);
12333 Arg := Get_Pragma_Arg (Arg1);
12335 if not Is_Entity_Name (Arg)
12336 or else not Is_Access_Type (Entity (Arg))
12337 then
12338 Error_Pragma_Arg ("pragma% requires access type", Arg1);
12339 else
12340 Set_Has_Pragma_Controlled (Base_Type (Entity (Arg)));
12341 end if;
12342 end Controlled;
12344 ----------------
12345 -- Convention --
12346 ----------------
12348 -- pragma Convention ([Convention =>] convention_IDENTIFIER,
12349 -- [Entity =>] LOCAL_NAME);
12351 when Pragma_Convention => Convention : declare
12352 C : Convention_Id;
12353 E : Entity_Id;
12354 pragma Warnings (Off, C);
12355 pragma Warnings (Off, E);
12356 begin
12357 Check_Arg_Order ((Name_Convention, Name_Entity));
12358 Check_Ada_83_Warning;
12359 Check_Arg_Count (2);
12360 Process_Convention (C, E);
12361 end Convention;
12363 ---------------------------
12364 -- Convention_Identifier --
12365 ---------------------------
12367 -- pragma Convention_Identifier ([Name =>] IDENTIFIER,
12368 -- [Convention =>] convention_IDENTIFIER);
12370 when Pragma_Convention_Identifier => Convention_Identifier : declare
12371 Idnam : Name_Id;
12372 Cname : Name_Id;
12374 begin
12375 GNAT_Pragma;
12376 Check_Arg_Order ((Name_Name, Name_Convention));
12377 Check_Arg_Count (2);
12378 Check_Optional_Identifier (Arg1, Name_Name);
12379 Check_Optional_Identifier (Arg2, Name_Convention);
12380 Check_Arg_Is_Identifier (Arg1);
12381 Check_Arg_Is_Identifier (Arg2);
12382 Idnam := Chars (Get_Pragma_Arg (Arg1));
12383 Cname := Chars (Get_Pragma_Arg (Arg2));
12385 if Is_Convention_Name (Cname) then
12386 Record_Convention_Identifier
12387 (Idnam, Get_Convention_Id (Cname));
12388 else
12389 Error_Pragma_Arg
12390 ("second arg for % pragma must be convention", Arg2);
12391 end if;
12392 end Convention_Identifier;
12394 ---------------
12395 -- CPP_Class --
12396 ---------------
12398 -- pragma CPP_Class ([Entity =>] LOCAL_NAME)
12400 when Pragma_CPP_Class => CPP_Class : declare
12401 begin
12402 GNAT_Pragma;
12404 if Warn_On_Obsolescent_Feature then
12405 Error_Msg_N
12406 ("'G'N'A'T pragma cpp'_class is now obsolete and has no "
12407 & "effect; replace it by pragma import?j?", N);
12408 end if;
12410 Check_Arg_Count (1);
12412 Rewrite (N,
12413 Make_Pragma (Loc,
12414 Chars => Name_Import,
12415 Pragma_Argument_Associations => New_List (
12416 Make_Pragma_Argument_Association (Loc,
12417 Expression => Make_Identifier (Loc, Name_CPP)),
12418 New_Copy (First (Pragma_Argument_Associations (N))))));
12419 Analyze (N);
12420 end CPP_Class;
12422 ---------------------
12423 -- CPP_Constructor --
12424 ---------------------
12426 -- pragma CPP_Constructor ([Entity =>] LOCAL_NAME
12427 -- [, [External_Name =>] static_string_EXPRESSION ]
12428 -- [, [Link_Name =>] static_string_EXPRESSION ]);
12430 when Pragma_CPP_Constructor => CPP_Constructor : declare
12431 Elmt : Elmt_Id;
12432 Id : Entity_Id;
12433 Def_Id : Entity_Id;
12434 Tag_Typ : Entity_Id;
12436 begin
12437 GNAT_Pragma;
12438 Check_At_Least_N_Arguments (1);
12439 Check_At_Most_N_Arguments (3);
12440 Check_Optional_Identifier (Arg1, Name_Entity);
12441 Check_Arg_Is_Local_Name (Arg1);
12443 Id := Get_Pragma_Arg (Arg1);
12444 Find_Program_Unit_Name (Id);
12446 -- If we did not find the name, we are done
12448 if Etype (Id) = Any_Type then
12449 return;
12450 end if;
12452 Def_Id := Entity (Id);
12454 -- Check if already defined as constructor
12456 if Is_Constructor (Def_Id) then
12457 Error_Msg_N
12458 ("??duplicate argument for pragma 'C'P'P_Constructor", Arg1);
12459 return;
12460 end if;
12462 if Ekind (Def_Id) = E_Function
12463 and then (Is_CPP_Class (Etype (Def_Id))
12464 or else (Is_Class_Wide_Type (Etype (Def_Id))
12465 and then
12466 Is_CPP_Class (Root_Type (Etype (Def_Id)))))
12467 then
12468 if Scope (Def_Id) /= Scope (Etype (Def_Id)) then
12469 Error_Msg_N
12470 ("'C'P'P constructor must be defined in the scope of "
12471 & "its returned type", Arg1);
12472 end if;
12474 if Arg_Count >= 2 then
12475 Set_Imported (Def_Id);
12476 Set_Is_Public (Def_Id);
12477 Process_Interface_Name (Def_Id, Arg2, Arg3);
12478 end if;
12480 Set_Has_Completion (Def_Id);
12481 Set_Is_Constructor (Def_Id);
12482 Set_Convention (Def_Id, Convention_CPP);
12484 -- Imported C++ constructors are not dispatching primitives
12485 -- because in C++ they don't have a dispatch table slot.
12486 -- However, in Ada the constructor has the profile of a
12487 -- function that returns a tagged type and therefore it has
12488 -- been treated as a primitive operation during semantic
12489 -- analysis. We now remove it from the list of primitive
12490 -- operations of the type.
12492 if Is_Tagged_Type (Etype (Def_Id))
12493 and then not Is_Class_Wide_Type (Etype (Def_Id))
12494 and then Is_Dispatching_Operation (Def_Id)
12495 then
12496 Tag_Typ := Etype (Def_Id);
12498 Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
12499 while Present (Elmt) and then Node (Elmt) /= Def_Id loop
12500 Next_Elmt (Elmt);
12501 end loop;
12503 Remove_Elmt (Primitive_Operations (Tag_Typ), Elmt);
12504 Set_Is_Dispatching_Operation (Def_Id, False);
12505 end if;
12507 -- For backward compatibility, if the constructor returns a
12508 -- class wide type, and we internally change the return type to
12509 -- the corresponding root type.
12511 if Is_Class_Wide_Type (Etype (Def_Id)) then
12512 Set_Etype (Def_Id, Root_Type (Etype (Def_Id)));
12513 end if;
12514 else
12515 Error_Pragma_Arg
12516 ("pragma% requires function returning a 'C'P'P_Class type",
12517 Arg1);
12518 end if;
12519 end CPP_Constructor;
12521 -----------------
12522 -- CPP_Virtual --
12523 -----------------
12525 when Pragma_CPP_Virtual => CPP_Virtual : declare
12526 begin
12527 GNAT_Pragma;
12529 if Warn_On_Obsolescent_Feature then
12530 Error_Msg_N
12531 ("'G'N'A'T pragma Cpp'_Virtual is now obsolete and has no "
12532 & "effect?j?", N);
12533 end if;
12534 end CPP_Virtual;
12536 ----------------
12537 -- CPP_Vtable --
12538 ----------------
12540 when Pragma_CPP_Vtable => CPP_Vtable : declare
12541 begin
12542 GNAT_Pragma;
12544 if Warn_On_Obsolescent_Feature then
12545 Error_Msg_N
12546 ("'G'N'A'T pragma Cpp'_Vtable is now obsolete and has no "
12547 & "effect?j?", N);
12548 end if;
12549 end CPP_Vtable;
12551 ---------
12552 -- CPU --
12553 ---------
12555 -- pragma CPU (EXPRESSION);
12557 when Pragma_CPU => CPU : declare
12558 P : constant Node_Id := Parent (N);
12559 Arg : Node_Id;
12560 Ent : Entity_Id;
12562 begin
12563 Ada_2012_Pragma;
12564 Check_No_Identifiers;
12565 Check_Arg_Count (1);
12567 -- Subprogram case
12569 if Nkind (P) = N_Subprogram_Body then
12570 Check_In_Main_Program;
12572 Arg := Get_Pragma_Arg (Arg1);
12573 Analyze_And_Resolve (Arg, Any_Integer);
12575 Ent := Defining_Unit_Name (Specification (P));
12577 if Nkind (Ent) = N_Defining_Program_Unit_Name then
12578 Ent := Defining_Identifier (Ent);
12579 end if;
12581 -- Must be static
12583 if not Is_OK_Static_Expression (Arg) then
12584 Flag_Non_Static_Expr
12585 ("main subprogram affinity is not static!", Arg);
12586 raise Pragma_Exit;
12588 -- If constraint error, then we already signalled an error
12590 elsif Raises_Constraint_Error (Arg) then
12591 null;
12593 -- Otherwise check in range
12595 else
12596 declare
12597 CPU_Id : constant Entity_Id := RTE (RE_CPU_Range);
12598 -- This is the entity System.Multiprocessors.CPU_Range;
12600 Val : constant Uint := Expr_Value (Arg);
12602 begin
12603 if Val < Expr_Value (Type_Low_Bound (CPU_Id))
12604 or else
12605 Val > Expr_Value (Type_High_Bound (CPU_Id))
12606 then
12607 Error_Pragma_Arg
12608 ("main subprogram CPU is out of range", Arg1);
12609 end if;
12610 end;
12611 end if;
12613 Set_Main_CPU
12614 (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
12616 -- Task case
12618 elsif Nkind (P) = N_Task_Definition then
12619 Arg := Get_Pragma_Arg (Arg1);
12620 Ent := Defining_Identifier (Parent (P));
12622 -- The expression must be analyzed in the special manner
12623 -- described in "Handling of Default and Per-Object
12624 -- Expressions" in sem.ads.
12626 Preanalyze_Spec_Expression (Arg, RTE (RE_CPU_Range));
12628 -- Anything else is incorrect
12630 else
12631 Pragma_Misplaced;
12632 end if;
12634 -- Check duplicate pragma before we chain the pragma in the Rep
12635 -- Item chain of Ent.
12637 Check_Duplicate_Pragma (Ent);
12638 Record_Rep_Item (Ent, N);
12639 end CPU;
12641 -----------
12642 -- Debug --
12643 -----------
12645 -- pragma Debug ([boolean_EXPRESSION,] PROCEDURE_CALL_STATEMENT);
12647 when Pragma_Debug => Debug : declare
12648 Cond : Node_Id;
12649 Call : Node_Id;
12651 begin
12652 GNAT_Pragma;
12654 -- The condition for executing the call is that the expander
12655 -- is active and that we are not ignoring this debug pragma.
12657 Cond :=
12658 New_Occurrence_Of
12659 (Boolean_Literals
12660 (Expander_Active and then not Is_Ignored (N)),
12661 Loc);
12663 if not Is_Ignored (N) then
12664 Set_SCO_Pragma_Enabled (Loc);
12665 end if;
12667 if Arg_Count = 2 then
12668 Cond :=
12669 Make_And_Then (Loc,
12670 Left_Opnd => Relocate_Node (Cond),
12671 Right_Opnd => Get_Pragma_Arg (Arg1));
12672 Call := Get_Pragma_Arg (Arg2);
12673 else
12674 Call := Get_Pragma_Arg (Arg1);
12675 end if;
12677 if Nkind_In (Call,
12678 N_Indexed_Component,
12679 N_Function_Call,
12680 N_Identifier,
12681 N_Expanded_Name,
12682 N_Selected_Component)
12683 then
12684 -- If this pragma Debug comes from source, its argument was
12685 -- parsed as a name form (which is syntactically identical).
12686 -- In a generic context a parameterless call will be left as
12687 -- an expanded name (if global) or selected_component if local.
12688 -- Change it to a procedure call statement now.
12690 Change_Name_To_Procedure_Call_Statement (Call);
12692 elsif Nkind (Call) = N_Procedure_Call_Statement then
12694 -- Already in the form of a procedure call statement: nothing
12695 -- to do (could happen in case of an internally generated
12696 -- pragma Debug).
12698 null;
12700 else
12701 -- All other cases: diagnose error
12703 Error_Msg
12704 ("argument of pragma ""Debug"" is not procedure call",
12705 Sloc (Call));
12706 return;
12707 end if;
12709 -- Rewrite into a conditional with an appropriate condition. We
12710 -- wrap the procedure call in a block so that overhead from e.g.
12711 -- use of the secondary stack does not generate execution overhead
12712 -- for suppressed conditions.
12714 -- Normally the analysis that follows will freeze the subprogram
12715 -- being called. However, if the call is to a null procedure,
12716 -- we want to freeze it before creating the block, because the
12717 -- analysis that follows may be done with expansion disabled, in
12718 -- which case the body will not be generated, leading to spurious
12719 -- errors.
12721 if Nkind (Call) = N_Procedure_Call_Statement
12722 and then Is_Entity_Name (Name (Call))
12723 then
12724 Analyze (Name (Call));
12725 Freeze_Before (N, Entity (Name (Call)));
12726 end if;
12728 Rewrite (N,
12729 Make_Implicit_If_Statement (N,
12730 Condition => Cond,
12731 Then_Statements => New_List (
12732 Make_Block_Statement (Loc,
12733 Handled_Statement_Sequence =>
12734 Make_Handled_Sequence_Of_Statements (Loc,
12735 Statements => New_List (Relocate_Node (Call)))))));
12736 Analyze (N);
12738 -- Ignore pragma Debug in GNATprove mode. Do this rewriting
12739 -- after analysis of the normally rewritten node, to capture all
12740 -- references to entities, which avoids issuing wrong warnings
12741 -- about unused entities.
12743 if GNATprove_Mode then
12744 Rewrite (N, Make_Null_Statement (Loc));
12745 end if;
12746 end Debug;
12748 ------------------
12749 -- Debug_Policy --
12750 ------------------
12752 -- pragma Debug_Policy (On | Off | Check | Disable | Ignore)
12754 when Pragma_Debug_Policy =>
12755 GNAT_Pragma;
12756 Check_Arg_Count (1);
12757 Check_No_Identifiers;
12758 Check_Arg_Is_Identifier (Arg1);
12760 -- Exactly equivalent to pragma Check_Policy (Debug, arg), so
12761 -- rewrite it that way, and let the rest of the checking come
12762 -- from analyzing the rewritten pragma.
12764 Rewrite (N,
12765 Make_Pragma (Loc,
12766 Chars => Name_Check_Policy,
12767 Pragma_Argument_Associations => New_List (
12768 Make_Pragma_Argument_Association (Loc,
12769 Expression => Make_Identifier (Loc, Name_Debug)),
12771 Make_Pragma_Argument_Association (Loc,
12772 Expression => Get_Pragma_Arg (Arg1)))));
12773 Analyze (N);
12775 -------------------------------
12776 -- Default_Initial_Condition --
12777 -------------------------------
12779 -- pragma Default_Initial_Condition [ (null | boolean_EXPRESSION) ];
12781 when Pragma_Default_Initial_Condition => Default_Init_Cond : declare
12782 Discard : Boolean;
12783 Stmt : Node_Id;
12784 Typ : Entity_Id;
12786 begin
12787 GNAT_Pragma;
12788 Check_No_Identifiers;
12789 Check_At_Most_N_Arguments (1);
12791 Stmt := Prev (N);
12792 while Present (Stmt) loop
12794 -- Skip prior pragmas, but check for duplicates
12796 if Nkind (Stmt) = N_Pragma then
12797 if Pragma_Name (Stmt) = Pname then
12798 Error_Msg_Name_1 := Pname;
12799 Error_Msg_Sloc := Sloc (Stmt);
12800 Error_Msg_N ("pragma % duplicates pragma declared#", N);
12801 end if;
12803 -- Skip internally generated code
12805 elsif not Comes_From_Source (Stmt) then
12806 null;
12808 -- The associated private type [extension] has been found, stop
12809 -- the search.
12811 elsif Nkind_In (Stmt, N_Private_Extension_Declaration,
12812 N_Private_Type_Declaration)
12813 then
12814 Typ := Defining_Entity (Stmt);
12815 exit;
12817 -- The pragma does not apply to a legal construct, issue an
12818 -- error and stop the analysis.
12820 else
12821 Pragma_Misplaced;
12822 return;
12823 end if;
12825 Stmt := Prev (Stmt);
12826 end loop;
12828 Set_Has_Default_Init_Cond (Typ);
12829 Set_Has_Inherited_Default_Init_Cond (Typ, False);
12831 -- Chain the pragma on the rep item chain for further processing
12833 Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
12834 end Default_Init_Cond;
12836 ----------------------------------
12837 -- Default_Scalar_Storage_Order --
12838 ----------------------------------
12840 -- pragma Default_Scalar_Storage_Order
12841 -- (High_Order_First | Low_Order_First);
12843 when Pragma_Default_Scalar_Storage_Order => DSSO : declare
12844 Default : Character;
12846 begin
12847 GNAT_Pragma;
12848 Check_Arg_Count (1);
12850 -- Default_Scalar_Storage_Order can appear as a configuration
12851 -- pragma, or in a declarative part of a package spec.
12853 if not Is_Configuration_Pragma then
12854 Check_Is_In_Decl_Part_Or_Package_Spec;
12855 end if;
12857 Check_No_Identifiers;
12858 Check_Arg_Is_One_Of
12859 (Arg1, Name_High_Order_First, Name_Low_Order_First);
12860 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
12861 Default := Fold_Upper (Name_Buffer (1));
12863 if not Support_Nondefault_SSO_On_Target
12864 and then (Ttypes.Bytes_Big_Endian /= (Default = 'H'))
12865 then
12866 if Warn_On_Unrecognized_Pragma then
12867 Error_Msg_N
12868 ("non-default Scalar_Storage_Order not supported "
12869 & "on target?g?", N);
12870 Error_Msg_N
12871 ("\pragma Default_Scalar_Storage_Order ignored?g?", N);
12872 end if;
12874 -- Here set the specified default
12876 else
12877 Opt.Default_SSO := Default;
12878 end if;
12879 end DSSO;
12881 --------------------------
12882 -- Default_Storage_Pool --
12883 --------------------------
12885 -- pragma Default_Storage_Pool (storage_pool_NAME | null);
12887 when Pragma_Default_Storage_Pool =>
12888 Ada_2012_Pragma;
12889 Check_Arg_Count (1);
12891 -- Default_Storage_Pool can appear as a configuration pragma, or
12892 -- in a declarative part of a package spec.
12894 if not Is_Configuration_Pragma then
12895 Check_Is_In_Decl_Part_Or_Package_Spec;
12896 end if;
12898 -- Case of Default_Storage_Pool (null);
12900 if Nkind (Expression (Arg1)) = N_Null then
12901 Analyze (Expression (Arg1));
12903 -- This is an odd case, this is not really an expression, so
12904 -- we don't have a type for it. So just set the type to Empty.
12906 Set_Etype (Expression (Arg1), Empty);
12908 -- Case of Default_Storage_Pool (storage_pool_NAME);
12910 else
12911 -- If it's a configuration pragma, then the only allowed
12912 -- argument is "null".
12914 if Is_Configuration_Pragma then
12915 Error_Pragma_Arg ("NULL expected", Arg1);
12916 end if;
12918 -- The expected type for a non-"null" argument is
12919 -- Root_Storage_Pool'Class, and the pool must be a variable.
12921 Analyze_And_Resolve
12922 (Get_Pragma_Arg (Arg1),
12923 Typ => Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
12925 if not Is_Variable (Expression (Arg1)) then
12926 Error_Pragma_Arg
12927 ("default storage pool must be a variable", Arg1);
12928 end if;
12929 end if;
12931 -- Finally, record the pool name (or null). Freeze.Freeze_Entity
12932 -- for an access type will use this information to set the
12933 -- appropriate attributes of the access type.
12935 Default_Pool := Expression (Arg1);
12937 -------------
12938 -- Depends --
12939 -------------
12941 -- pragma Depends (DEPENDENCY_RELATION);
12943 -- DEPENDENCY_RELATION ::=
12944 -- null
12945 -- | DEPENDENCY_CLAUSE {, DEPENDENCY_CLAUSE}
12947 -- DEPENDENCY_CLAUSE ::=
12948 -- OUTPUT_LIST =>[+] INPUT_LIST
12949 -- | NULL_DEPENDENCY_CLAUSE
12951 -- NULL_DEPENDENCY_CLAUSE ::= null => INPUT_LIST
12953 -- OUTPUT_LIST ::= OUTPUT | (OUTPUT {, OUTPUT})
12955 -- INPUT_LIST ::= null | INPUT | (INPUT {, INPUT})
12957 -- OUTPUT ::= NAME | FUNCTION_RESULT
12958 -- INPUT ::= NAME
12960 -- where FUNCTION_RESULT is a function Result attribute_reference
12962 when Pragma_Depends => Depends : declare
12963 Subp_Decl : Node_Id;
12965 begin
12966 GNAT_Pragma;
12967 Check_Arg_Count (1);
12968 Ensure_Aggregate_Form (Arg1);
12970 -- Ensure the proper placement of the pragma. Depends must be
12971 -- associated with a subprogram declaration or a body that acts
12972 -- as a spec.
12974 Subp_Decl :=
12975 Find_Related_Subprogram_Or_Body (N, Do_Checks => True);
12977 if Nkind (Subp_Decl) = N_Subprogram_Declaration then
12978 null;
12980 -- Body acts as spec
12982 elsif Nkind (Subp_Decl) = N_Subprogram_Body
12983 and then No (Corresponding_Spec (Subp_Decl))
12984 then
12985 null;
12987 -- Body stub acts as spec
12989 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
12990 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
12991 then
12992 null;
12994 else
12995 Pragma_Misplaced;
12996 return;
12997 end if;
12999 -- When the pragma appears on a subprogram body, perform the full
13000 -- analysis now.
13002 if Nkind (Subp_Decl) = N_Subprogram_Body then
13003 Analyze_Depends_In_Decl_Part (N);
13005 -- When Depends applies to a subprogram compilation unit, the
13006 -- corresponding pragma is placed after the unit's declaration
13007 -- node and needs to be analyzed immediately.
13009 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration
13010 and then Nkind (Parent (Subp_Decl)) = N_Compilation_Unit
13011 then
13012 Analyze_Depends_In_Decl_Part (N);
13013 end if;
13015 -- Chain the pragma on the contract for further processing
13017 Add_Contract_Item (N, Defining_Entity (Subp_Decl));
13018 end Depends;
13020 ---------------------
13021 -- Detect_Blocking --
13022 ---------------------
13024 -- pragma Detect_Blocking;
13026 when Pragma_Detect_Blocking =>
13027 Ada_2005_Pragma;
13028 Check_Arg_Count (0);
13029 Check_Valid_Configuration_Pragma;
13030 Detect_Blocking := True;
13032 ------------------------------------
13033 -- Disable_Atomic_Synchronization --
13034 ------------------------------------
13036 -- pragma Disable_Atomic_Synchronization [(Entity)];
13038 when Pragma_Disable_Atomic_Synchronization =>
13039 GNAT_Pragma;
13040 Process_Disable_Enable_Atomic_Sync (Name_Suppress);
13042 -------------------
13043 -- Discard_Names --
13044 -------------------
13046 -- pragma Discard_Names [([On =>] LOCAL_NAME)];
13048 when Pragma_Discard_Names => Discard_Names : declare
13049 E : Entity_Id;
13050 E_Id : Entity_Id;
13052 begin
13053 Check_Ada_83_Warning;
13055 -- Deal with configuration pragma case
13057 if Arg_Count = 0 and then Is_Configuration_Pragma then
13058 Global_Discard_Names := True;
13059 return;
13061 -- Otherwise, check correct appropriate context
13063 else
13064 Check_Is_In_Decl_Part_Or_Package_Spec;
13066 if Arg_Count = 0 then
13068 -- If there is no parameter, then from now on this pragma
13069 -- applies to any enumeration, exception or tagged type
13070 -- defined in the current declarative part, and recursively
13071 -- to any nested scope.
13073 Set_Discard_Names (Current_Scope);
13074 return;
13076 else
13077 Check_Arg_Count (1);
13078 Check_Optional_Identifier (Arg1, Name_On);
13079 Check_Arg_Is_Local_Name (Arg1);
13081 E_Id := Get_Pragma_Arg (Arg1);
13083 if Etype (E_Id) = Any_Type then
13084 return;
13085 else
13086 E := Entity (E_Id);
13087 end if;
13089 if (Is_First_Subtype (E)
13090 and then
13091 (Is_Enumeration_Type (E) or else Is_Tagged_Type (E)))
13092 or else Ekind (E) = E_Exception
13093 then
13094 Set_Discard_Names (E);
13095 Record_Rep_Item (E, N);
13097 else
13098 Error_Pragma_Arg
13099 ("inappropriate entity for pragma%", Arg1);
13100 end if;
13102 end if;
13103 end if;
13104 end Discard_Names;
13106 ------------------------
13107 -- Dispatching_Domain --
13108 ------------------------
13110 -- pragma Dispatching_Domain (EXPRESSION);
13112 when Pragma_Dispatching_Domain => Dispatching_Domain : declare
13113 P : constant Node_Id := Parent (N);
13114 Arg : Node_Id;
13115 Ent : Entity_Id;
13117 begin
13118 Ada_2012_Pragma;
13119 Check_No_Identifiers;
13120 Check_Arg_Count (1);
13122 -- This pragma is born obsolete, but not the aspect
13124 if not From_Aspect_Specification (N) then
13125 Check_Restriction
13126 (No_Obsolescent_Features, Pragma_Identifier (N));
13127 end if;
13129 if Nkind (P) = N_Task_Definition then
13130 Arg := Get_Pragma_Arg (Arg1);
13131 Ent := Defining_Identifier (Parent (P));
13133 -- The expression must be analyzed in the special manner
13134 -- described in "Handling of Default and Per-Object
13135 -- Expressions" in sem.ads.
13137 Preanalyze_Spec_Expression (Arg, RTE (RE_Dispatching_Domain));
13139 -- Check duplicate pragma before we chain the pragma in the Rep
13140 -- Item chain of Ent.
13142 Check_Duplicate_Pragma (Ent);
13143 Record_Rep_Item (Ent, N);
13145 -- Anything else is incorrect
13147 else
13148 Pragma_Misplaced;
13149 end if;
13150 end Dispatching_Domain;
13152 ---------------
13153 -- Elaborate --
13154 ---------------
13156 -- pragma Elaborate (library_unit_NAME {, library_unit_NAME});
13158 when Pragma_Elaborate => Elaborate : declare
13159 Arg : Node_Id;
13160 Citem : Node_Id;
13162 begin
13163 -- Pragma must be in context items list of a compilation unit
13165 if not Is_In_Context_Clause then
13166 Pragma_Misplaced;
13167 end if;
13169 -- Must be at least one argument
13171 if Arg_Count = 0 then
13172 Error_Pragma ("pragma% requires at least one argument");
13173 end if;
13175 -- In Ada 83 mode, there can be no items following it in the
13176 -- context list except other pragmas and implicit with clauses
13177 -- (e.g. those added by use of Rtsfind). In Ada 95 mode, this
13178 -- placement rule does not apply.
13180 if Ada_Version = Ada_83 and then Comes_From_Source (N) then
13181 Citem := Next (N);
13182 while Present (Citem) loop
13183 if Nkind (Citem) = N_Pragma
13184 or else (Nkind (Citem) = N_With_Clause
13185 and then Implicit_With (Citem))
13186 then
13187 null;
13188 else
13189 Error_Pragma
13190 ("(Ada 83) pragma% must be at end of context clause");
13191 end if;
13193 Next (Citem);
13194 end loop;
13195 end if;
13197 -- Finally, the arguments must all be units mentioned in a with
13198 -- clause in the same context clause. Note we already checked (in
13199 -- Par.Prag) that the arguments are all identifiers or selected
13200 -- components.
13202 Arg := Arg1;
13203 Outer : while Present (Arg) loop
13204 Citem := First (List_Containing (N));
13205 Inner : while Citem /= N loop
13206 if Nkind (Citem) = N_With_Clause
13207 and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
13208 then
13209 Set_Elaborate_Present (Citem, True);
13210 Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
13211 Generate_Reference (Entity (Name (Citem)), Citem);
13213 -- With the pragma present, elaboration calls on
13214 -- subprograms from the named unit need no further
13215 -- checks, as long as the pragma appears in the current
13216 -- compilation unit. If the pragma appears in some unit
13217 -- in the context, there might still be a need for an
13218 -- Elaborate_All_Desirable from the current compilation
13219 -- to the named unit, so we keep the check enabled.
13221 if In_Extended_Main_Source_Unit (N) then
13223 -- This does not apply in SPARK mode, where we allow
13224 -- pragma Elaborate, but we don't trust it to be right
13225 -- so we will still insist on the Elaborate_All.
13227 if SPARK_Mode /= On then
13228 Set_Suppress_Elaboration_Warnings
13229 (Entity (Name (Citem)));
13230 end if;
13231 end if;
13233 exit Inner;
13234 end if;
13236 Next (Citem);
13237 end loop Inner;
13239 if Citem = N then
13240 Error_Pragma_Arg
13241 ("argument of pragma% is not withed unit", Arg);
13242 end if;
13244 Next (Arg);
13245 end loop Outer;
13247 -- Give a warning if operating in static mode with one of the
13248 -- gnatwl/-gnatwE (elaboration warnings enabled) switches set.
13250 if Elab_Warnings
13251 and not Dynamic_Elaboration_Checks
13253 -- pragma Elaborate not allowed in SPARK mode anyway. We
13254 -- already complained about it, no point in generating any
13255 -- further complaint.
13257 and SPARK_Mode /= On
13258 then
13259 Error_Msg_N
13260 ("?l?use of pragma Elaborate may not be safe", N);
13261 Error_Msg_N
13262 ("?l?use pragma Elaborate_All instead if possible", N);
13263 end if;
13264 end Elaborate;
13266 -------------------
13267 -- Elaborate_All --
13268 -------------------
13270 -- pragma Elaborate_All (library_unit_NAME {, library_unit_NAME});
13272 when Pragma_Elaborate_All => Elaborate_All : declare
13273 Arg : Node_Id;
13274 Citem : Node_Id;
13276 begin
13277 Check_Ada_83_Warning;
13279 -- Pragma must be in context items list of a compilation unit
13281 if not Is_In_Context_Clause then
13282 Pragma_Misplaced;
13283 end if;
13285 -- Must be at least one argument
13287 if Arg_Count = 0 then
13288 Error_Pragma ("pragma% requires at least one argument");
13289 end if;
13291 -- Note: unlike pragma Elaborate, pragma Elaborate_All does not
13292 -- have to appear at the end of the context clause, but may
13293 -- appear mixed in with other items, even in Ada 83 mode.
13295 -- Final check: the arguments must all be units mentioned in
13296 -- a with clause in the same context clause. Note that we
13297 -- already checked (in Par.Prag) that all the arguments are
13298 -- either identifiers or selected components.
13300 Arg := Arg1;
13301 Outr : while Present (Arg) loop
13302 Citem := First (List_Containing (N));
13303 Innr : while Citem /= N loop
13304 if Nkind (Citem) = N_With_Clause
13305 and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
13306 then
13307 Set_Elaborate_All_Present (Citem, True);
13308 Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
13310 -- Suppress warnings and elaboration checks on the named
13311 -- unit if the pragma is in the current compilation, as
13312 -- for pragma Elaborate.
13314 if In_Extended_Main_Source_Unit (N) then
13315 Set_Suppress_Elaboration_Warnings
13316 (Entity (Name (Citem)));
13317 end if;
13318 exit Innr;
13319 end if;
13321 Next (Citem);
13322 end loop Innr;
13324 if Citem = N then
13325 Set_Error_Posted (N);
13326 Error_Pragma_Arg
13327 ("argument of pragma% is not withed unit", Arg);
13328 end if;
13330 Next (Arg);
13331 end loop Outr;
13332 end Elaborate_All;
13334 --------------------
13335 -- Elaborate_Body --
13336 --------------------
13338 -- pragma Elaborate_Body [( library_unit_NAME )];
13340 when Pragma_Elaborate_Body => Elaborate_Body : declare
13341 Cunit_Node : Node_Id;
13342 Cunit_Ent : Entity_Id;
13344 begin
13345 Check_Ada_83_Warning;
13346 Check_Valid_Library_Unit_Pragma;
13348 if Nkind (N) = N_Null_Statement then
13349 return;
13350 end if;
13352 Cunit_Node := Cunit (Current_Sem_Unit);
13353 Cunit_Ent := Cunit_Entity (Current_Sem_Unit);
13355 if Nkind_In (Unit (Cunit_Node), N_Package_Body,
13356 N_Subprogram_Body)
13357 then
13358 Error_Pragma ("pragma% must refer to a spec, not a body");
13359 else
13360 Set_Body_Required (Cunit_Node, True);
13361 Set_Has_Pragma_Elaborate_Body (Cunit_Ent);
13363 -- If we are in dynamic elaboration mode, then we suppress
13364 -- elaboration warnings for the unit, since it is definitely
13365 -- fine NOT to do dynamic checks at the first level (and such
13366 -- checks will be suppressed because no elaboration boolean
13367 -- is created for Elaborate_Body packages).
13369 -- But in the static model of elaboration, Elaborate_Body is
13370 -- definitely NOT good enough to ensure elaboration safety on
13371 -- its own, since the body may WITH other units that are not
13372 -- safe from an elaboration point of view, so a client must
13373 -- still do an Elaborate_All on such units.
13375 -- Debug flag -gnatdD restores the old behavior of 3.13, where
13376 -- Elaborate_Body always suppressed elab warnings.
13378 if Dynamic_Elaboration_Checks or Debug_Flag_DD then
13379 Set_Suppress_Elaboration_Warnings (Cunit_Ent);
13380 end if;
13381 end if;
13382 end Elaborate_Body;
13384 ------------------------
13385 -- Elaboration_Checks --
13386 ------------------------
13388 -- pragma Elaboration_Checks (Static | Dynamic);
13390 when Pragma_Elaboration_Checks =>
13391 GNAT_Pragma;
13392 Check_Arg_Count (1);
13393 Check_Arg_Is_One_Of (Arg1, Name_Static, Name_Dynamic);
13395 -- Set flag accordingly (ignore attempt at dynamic elaboration
13396 -- checks in SPARK mode).
13398 Dynamic_Elaboration_Checks :=
13399 (Chars (Get_Pragma_Arg (Arg1)) = Name_Dynamic)
13400 and then SPARK_Mode /= On;
13402 ---------------
13403 -- Eliminate --
13404 ---------------
13406 -- pragma Eliminate (
13407 -- [Unit_Name =>] IDENTIFIER | SELECTED_COMPONENT,
13408 -- [,[Entity =>] IDENTIFIER |
13409 -- SELECTED_COMPONENT |
13410 -- STRING_LITERAL]
13411 -- [, OVERLOADING_RESOLUTION]);
13413 -- OVERLOADING_RESOLUTION ::= PARAMETER_AND_RESULT_TYPE_PROFILE |
13414 -- SOURCE_LOCATION
13416 -- PARAMETER_AND_RESULT_TYPE_PROFILE ::= PROCEDURE_PROFILE |
13417 -- FUNCTION_PROFILE
13419 -- PROCEDURE_PROFILE ::= Parameter_Types => PARAMETER_TYPES
13421 -- FUNCTION_PROFILE ::= [Parameter_Types => PARAMETER_TYPES,]
13422 -- Result_Type => result_SUBTYPE_NAME]
13424 -- PARAMETER_TYPES ::= (SUBTYPE_NAME {, SUBTYPE_NAME})
13425 -- SUBTYPE_NAME ::= STRING_LITERAL
13427 -- SOURCE_LOCATION ::= Source_Location => SOURCE_TRACE
13428 -- SOURCE_TRACE ::= STRING_LITERAL
13430 when Pragma_Eliminate => Eliminate : declare
13431 Args : Args_List (1 .. 5);
13432 Names : constant Name_List (1 .. 5) := (
13433 Name_Unit_Name,
13434 Name_Entity,
13435 Name_Parameter_Types,
13436 Name_Result_Type,
13437 Name_Source_Location);
13439 Unit_Name : Node_Id renames Args (1);
13440 Entity : Node_Id renames Args (2);
13441 Parameter_Types : Node_Id renames Args (3);
13442 Result_Type : Node_Id renames Args (4);
13443 Source_Location : Node_Id renames Args (5);
13445 begin
13446 GNAT_Pragma;
13447 Check_Valid_Configuration_Pragma;
13448 Gather_Associations (Names, Args);
13450 if No (Unit_Name) then
13451 Error_Pragma ("missing Unit_Name argument for pragma%");
13452 end if;
13454 if No (Entity)
13455 and then (Present (Parameter_Types)
13456 or else
13457 Present (Result_Type)
13458 or else
13459 Present (Source_Location))
13460 then
13461 Error_Pragma ("missing Entity argument for pragma%");
13462 end if;
13464 if (Present (Parameter_Types)
13465 or else
13466 Present (Result_Type))
13467 and then
13468 Present (Source_Location)
13469 then
13470 Error_Pragma
13471 ("parameter profile and source location cannot be used "
13472 & "together in pragma%");
13473 end if;
13475 Process_Eliminate_Pragma
13477 Unit_Name,
13478 Entity,
13479 Parameter_Types,
13480 Result_Type,
13481 Source_Location);
13482 end Eliminate;
13484 -----------------------------------
13485 -- Enable_Atomic_Synchronization --
13486 -----------------------------------
13488 -- pragma Enable_Atomic_Synchronization [(Entity)];
13490 when Pragma_Enable_Atomic_Synchronization =>
13491 GNAT_Pragma;
13492 Process_Disable_Enable_Atomic_Sync (Name_Unsuppress);
13494 ------------
13495 -- Export --
13496 ------------
13498 -- pragma Export (
13499 -- [ Convention =>] convention_IDENTIFIER,
13500 -- [ Entity =>] LOCAL_NAME
13501 -- [, [External_Name =>] static_string_EXPRESSION ]
13502 -- [, [Link_Name =>] static_string_EXPRESSION ]);
13504 when Pragma_Export => Export : declare
13505 C : Convention_Id;
13506 Def_Id : Entity_Id;
13508 pragma Warnings (Off, C);
13510 begin
13511 Check_Ada_83_Warning;
13512 Check_Arg_Order
13513 ((Name_Convention,
13514 Name_Entity,
13515 Name_External_Name,
13516 Name_Link_Name));
13518 Check_At_Least_N_Arguments (2);
13519 Check_At_Most_N_Arguments (4);
13521 -- In Relaxed_RM_Semantics, support old Ada 83 style:
13522 -- pragma Export (Entity, "external name");
13524 if Relaxed_RM_Semantics
13525 and then Arg_Count = 2
13526 and then Nkind (Expression (Arg2)) = N_String_Literal
13527 then
13528 C := Convention_C;
13529 Def_Id := Get_Pragma_Arg (Arg1);
13530 Analyze (Def_Id);
13532 if not Is_Entity_Name (Def_Id) then
13533 Error_Pragma_Arg ("entity name required", Arg1);
13534 end if;
13536 Def_Id := Entity (Def_Id);
13537 Set_Exported (Def_Id, Arg1);
13539 else
13540 Process_Convention (C, Def_Id);
13542 if Ekind (Def_Id) /= E_Constant then
13543 Note_Possible_Modification
13544 (Get_Pragma_Arg (Arg2), Sure => False);
13545 end if;
13547 Process_Interface_Name (Def_Id, Arg3, Arg4);
13548 Set_Exported (Def_Id, Arg2);
13549 end if;
13551 -- If the entity is a deferred constant, propagate the information
13552 -- to the full view, because gigi elaborates the full view only.
13554 if Ekind (Def_Id) = E_Constant
13555 and then Present (Full_View (Def_Id))
13556 then
13557 declare
13558 Id2 : constant Entity_Id := Full_View (Def_Id);
13559 begin
13560 Set_Is_Exported (Id2, Is_Exported (Def_Id));
13561 Set_First_Rep_Item (Id2, First_Rep_Item (Def_Id));
13562 Set_Interface_Name (Id2, Einfo.Interface_Name (Def_Id));
13563 end;
13564 end if;
13565 end Export;
13567 ---------------------
13568 -- Export_Function --
13569 ---------------------
13571 -- pragma Export_Function (
13572 -- [Internal =>] LOCAL_NAME
13573 -- [, [External =>] EXTERNAL_SYMBOL]
13574 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
13575 -- [, [Result_Type =>] TYPE_DESIGNATOR]
13576 -- [, [Mechanism =>] MECHANISM]
13577 -- [, [Result_Mechanism =>] MECHANISM_NAME]);
13579 -- EXTERNAL_SYMBOL ::=
13580 -- IDENTIFIER
13581 -- | static_string_EXPRESSION
13583 -- PARAMETER_TYPES ::=
13584 -- null
13585 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
13587 -- TYPE_DESIGNATOR ::=
13588 -- subtype_NAME
13589 -- | subtype_Name ' Access
13591 -- MECHANISM ::=
13592 -- MECHANISM_NAME
13593 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
13595 -- MECHANISM_ASSOCIATION ::=
13596 -- [formal_parameter_NAME =>] MECHANISM_NAME
13598 -- MECHANISM_NAME ::=
13599 -- Value
13600 -- | Reference
13602 when Pragma_Export_Function => Export_Function : declare
13603 Args : Args_List (1 .. 6);
13604 Names : constant Name_List (1 .. 6) := (
13605 Name_Internal,
13606 Name_External,
13607 Name_Parameter_Types,
13608 Name_Result_Type,
13609 Name_Mechanism,
13610 Name_Result_Mechanism);
13612 Internal : Node_Id renames Args (1);
13613 External : Node_Id renames Args (2);
13614 Parameter_Types : Node_Id renames Args (3);
13615 Result_Type : Node_Id renames Args (4);
13616 Mechanism : Node_Id renames Args (5);
13617 Result_Mechanism : Node_Id renames Args (6);
13619 begin
13620 GNAT_Pragma;
13621 Gather_Associations (Names, Args);
13622 Process_Extended_Import_Export_Subprogram_Pragma (
13623 Arg_Internal => Internal,
13624 Arg_External => External,
13625 Arg_Parameter_Types => Parameter_Types,
13626 Arg_Result_Type => Result_Type,
13627 Arg_Mechanism => Mechanism,
13628 Arg_Result_Mechanism => Result_Mechanism);
13629 end Export_Function;
13631 -------------------
13632 -- Export_Object --
13633 -------------------
13635 -- pragma Export_Object (
13636 -- [Internal =>] LOCAL_NAME
13637 -- [, [External =>] EXTERNAL_SYMBOL]
13638 -- [, [Size =>] EXTERNAL_SYMBOL]);
13640 -- EXTERNAL_SYMBOL ::=
13641 -- IDENTIFIER
13642 -- | static_string_EXPRESSION
13644 -- PARAMETER_TYPES ::=
13645 -- null
13646 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
13648 -- TYPE_DESIGNATOR ::=
13649 -- subtype_NAME
13650 -- | subtype_Name ' Access
13652 -- MECHANISM ::=
13653 -- MECHANISM_NAME
13654 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
13656 -- MECHANISM_ASSOCIATION ::=
13657 -- [formal_parameter_NAME =>] MECHANISM_NAME
13659 -- MECHANISM_NAME ::=
13660 -- Value
13661 -- | Reference
13663 when Pragma_Export_Object => Export_Object : declare
13664 Args : Args_List (1 .. 3);
13665 Names : constant Name_List (1 .. 3) := (
13666 Name_Internal,
13667 Name_External,
13668 Name_Size);
13670 Internal : Node_Id renames Args (1);
13671 External : Node_Id renames Args (2);
13672 Size : Node_Id renames Args (3);
13674 begin
13675 GNAT_Pragma;
13676 Gather_Associations (Names, Args);
13677 Process_Extended_Import_Export_Object_Pragma (
13678 Arg_Internal => Internal,
13679 Arg_External => External,
13680 Arg_Size => Size);
13681 end Export_Object;
13683 ----------------------
13684 -- Export_Procedure --
13685 ----------------------
13687 -- pragma Export_Procedure (
13688 -- [Internal =>] LOCAL_NAME
13689 -- [, [External =>] EXTERNAL_SYMBOL]
13690 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
13691 -- [, [Mechanism =>] MECHANISM]);
13693 -- EXTERNAL_SYMBOL ::=
13694 -- IDENTIFIER
13695 -- | static_string_EXPRESSION
13697 -- PARAMETER_TYPES ::=
13698 -- null
13699 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
13701 -- TYPE_DESIGNATOR ::=
13702 -- subtype_NAME
13703 -- | subtype_Name ' Access
13705 -- MECHANISM ::=
13706 -- MECHANISM_NAME
13707 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
13709 -- MECHANISM_ASSOCIATION ::=
13710 -- [formal_parameter_NAME =>] MECHANISM_NAME
13712 -- MECHANISM_NAME ::=
13713 -- Value
13714 -- | Reference
13716 when Pragma_Export_Procedure => Export_Procedure : declare
13717 Args : Args_List (1 .. 4);
13718 Names : constant Name_List (1 .. 4) := (
13719 Name_Internal,
13720 Name_External,
13721 Name_Parameter_Types,
13722 Name_Mechanism);
13724 Internal : Node_Id renames Args (1);
13725 External : Node_Id renames Args (2);
13726 Parameter_Types : Node_Id renames Args (3);
13727 Mechanism : Node_Id renames Args (4);
13729 begin
13730 GNAT_Pragma;
13731 Gather_Associations (Names, Args);
13732 Process_Extended_Import_Export_Subprogram_Pragma (
13733 Arg_Internal => Internal,
13734 Arg_External => External,
13735 Arg_Parameter_Types => Parameter_Types,
13736 Arg_Mechanism => Mechanism);
13737 end Export_Procedure;
13739 ------------------
13740 -- Export_Value --
13741 ------------------
13743 -- pragma Export_Value (
13744 -- [Value =>] static_integer_EXPRESSION,
13745 -- [Link_Name =>] static_string_EXPRESSION);
13747 when Pragma_Export_Value =>
13748 GNAT_Pragma;
13749 Check_Arg_Order ((Name_Value, Name_Link_Name));
13750 Check_Arg_Count (2);
13752 Check_Optional_Identifier (Arg1, Name_Value);
13753 Check_Arg_Is_OK_Static_Expression (Arg1, Any_Integer);
13755 Check_Optional_Identifier (Arg2, Name_Link_Name);
13756 Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
13758 -----------------------------
13759 -- Export_Valued_Procedure --
13760 -----------------------------
13762 -- pragma Export_Valued_Procedure (
13763 -- [Internal =>] LOCAL_NAME
13764 -- [, [External =>] EXTERNAL_SYMBOL,]
13765 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
13766 -- [, [Mechanism =>] MECHANISM]);
13768 -- EXTERNAL_SYMBOL ::=
13769 -- IDENTIFIER
13770 -- | static_string_EXPRESSION
13772 -- PARAMETER_TYPES ::=
13773 -- null
13774 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
13776 -- TYPE_DESIGNATOR ::=
13777 -- subtype_NAME
13778 -- | subtype_Name ' Access
13780 -- MECHANISM ::=
13781 -- MECHANISM_NAME
13782 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
13784 -- MECHANISM_ASSOCIATION ::=
13785 -- [formal_parameter_NAME =>] MECHANISM_NAME
13787 -- MECHANISM_NAME ::=
13788 -- Value
13789 -- | Reference
13791 when Pragma_Export_Valued_Procedure =>
13792 Export_Valued_Procedure : declare
13793 Args : Args_List (1 .. 4);
13794 Names : constant Name_List (1 .. 4) := (
13795 Name_Internal,
13796 Name_External,
13797 Name_Parameter_Types,
13798 Name_Mechanism);
13800 Internal : Node_Id renames Args (1);
13801 External : Node_Id renames Args (2);
13802 Parameter_Types : Node_Id renames Args (3);
13803 Mechanism : Node_Id renames Args (4);
13805 begin
13806 GNAT_Pragma;
13807 Gather_Associations (Names, Args);
13808 Process_Extended_Import_Export_Subprogram_Pragma (
13809 Arg_Internal => Internal,
13810 Arg_External => External,
13811 Arg_Parameter_Types => Parameter_Types,
13812 Arg_Mechanism => Mechanism);
13813 end Export_Valued_Procedure;
13815 -------------------
13816 -- Extend_System --
13817 -------------------
13819 -- pragma Extend_System ([Name =>] Identifier);
13821 when Pragma_Extend_System => Extend_System : declare
13822 begin
13823 GNAT_Pragma;
13824 Check_Valid_Configuration_Pragma;
13825 Check_Arg_Count (1);
13826 Check_Optional_Identifier (Arg1, Name_Name);
13827 Check_Arg_Is_Identifier (Arg1);
13829 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
13831 if Name_Len > 4
13832 and then Name_Buffer (1 .. 4) = "aux_"
13833 then
13834 if Present (System_Extend_Pragma_Arg) then
13835 if Chars (Get_Pragma_Arg (Arg1)) =
13836 Chars (Expression (System_Extend_Pragma_Arg))
13837 then
13838 null;
13839 else
13840 Error_Msg_Sloc := Sloc (System_Extend_Pragma_Arg);
13841 Error_Pragma ("pragma% conflicts with that #");
13842 end if;
13844 else
13845 System_Extend_Pragma_Arg := Arg1;
13847 if not GNAT_Mode then
13848 System_Extend_Unit := Arg1;
13849 end if;
13850 end if;
13851 else
13852 Error_Pragma ("incorrect name for pragma%, must be Aux_xxx");
13853 end if;
13854 end Extend_System;
13856 ------------------------
13857 -- Extensions_Allowed --
13858 ------------------------
13860 -- pragma Extensions_Allowed (ON | OFF);
13862 when Pragma_Extensions_Allowed =>
13863 GNAT_Pragma;
13864 Check_Arg_Count (1);
13865 Check_No_Identifiers;
13866 Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
13868 if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
13869 Extensions_Allowed := True;
13870 Ada_Version := Ada_Version_Type'Last;
13872 else
13873 Extensions_Allowed := False;
13874 Ada_Version := Ada_Version_Explicit;
13875 Ada_Version_Pragma := Empty;
13876 end if;
13878 ------------------------
13879 -- Extensions_Visible --
13880 ------------------------
13882 -- pragma Extensions_Visible [ (boolean_EXPRESSION) ];
13884 when Pragma_Extensions_Visible => Extensions_Visible : declare
13885 Context : constant Node_Id := Parent (N);
13886 Expr : Node_Id;
13887 Formal : Entity_Id;
13888 Orig_Stmt : Node_Id;
13889 Subp : Entity_Id;
13890 Stmt : Node_Id;
13892 Has_OK_Formal : Boolean := False;
13894 begin
13895 GNAT_Pragma;
13896 Check_No_Identifiers;
13897 Check_At_Most_N_Arguments (1);
13899 Subp := Empty;
13900 Stmt := Prev (N);
13901 while Present (Stmt) loop
13903 -- Skip prior pragmas, but check for duplicates
13905 if Nkind (Stmt) = N_Pragma then
13906 if Pragma_Name (Stmt) = Pname then
13907 Error_Msg_Name_1 := Pname;
13908 Error_Msg_Sloc := Sloc (Stmt);
13909 Error_Msg_N ("pragma % duplicates pragma declared#", N);
13910 end if;
13912 -- Skip internally generated code
13914 elsif not Comes_From_Source (Stmt) then
13915 Orig_Stmt := Original_Node (Stmt);
13917 -- When pragma Ghost applies to an expression function, the
13918 -- expression function is transformed into a subprogram.
13920 if Nkind (Stmt) = N_Subprogram_Declaration
13921 and then Comes_From_Source (Orig_Stmt)
13922 and then Nkind (Orig_Stmt) = N_Expression_Function
13923 then
13924 Subp := Defining_Entity (Stmt);
13925 exit;
13926 end if;
13928 -- The associated [generic] subprogram declaration has been
13929 -- found, stop the search.
13931 elsif Nkind_In (Stmt, N_Generic_Subprogram_Declaration,
13932 N_Subprogram_Declaration)
13933 then
13934 Subp := Defining_Entity (Stmt);
13935 exit;
13937 -- The pragma does not apply to a legal construct, issue an
13938 -- error and stop the analysis.
13940 else
13941 Error_Pragma ("pragma % must apply to a subprogram");
13942 return;
13943 end if;
13945 Stmt := Prev (Stmt);
13946 end loop;
13948 -- When the pragma applies to a stand alone subprogram body, it
13949 -- appears within the declarations of the body. In that case the
13950 -- enclosing construct is the proper context. This check is done
13951 -- after the traversal above to allow for duplicate detection.
13953 if No (Subp)
13954 and then Nkind (Context) = N_Subprogram_Body
13955 and then No (Corresponding_Spec (Context))
13956 then
13957 Subp := Defining_Entity (Context);
13958 end if;
13960 if No (Subp) then
13961 Error_Pragma ("pragma % must apply to a subprogram");
13962 return;
13963 end if;
13965 -- Examine the formals of the related subprogram
13967 Formal := First_Formal (Subp);
13968 while Present (Formal) loop
13970 -- At least one of the formals is of a specific tagged type,
13971 -- the pragma is legal.
13973 if Is_Specific_Tagged_Type (Etype (Formal)) then
13974 Has_OK_Formal := True;
13975 exit;
13977 -- A generic subprogram with at least one formal of a private
13978 -- type ensures the legality of the pragma because the actual
13979 -- may be specifically tagged. Note that this is verified by
13980 -- the check above at instantiation time.
13982 elsif Is_Private_Type (Etype (Formal))
13983 and then Is_Generic_Type (Etype (Formal))
13984 then
13985 Has_OK_Formal := True;
13986 exit;
13987 end if;
13989 Next_Formal (Formal);
13990 end loop;
13992 if not Has_OK_Formal then
13993 Error_Msg_Name_1 := Pname;
13994 Error_Msg_N (Fix_Error ("incorrect placement of pragma %"), N);
13995 Error_Msg_NE
13996 ("\subprogram & lacks parameter of specific tagged or "
13997 & "generic private type", N, Subp);
13998 return;
13999 end if;
14001 -- Analyze the Boolean expression (if any)
14003 if Present (Arg1) then
14004 Expr := Get_Pragma_Arg (Arg1);
14006 Analyze_And_Resolve (Expr, Standard_Boolean);
14008 if not Is_OK_Static_Expression (Expr) then
14009 Error_Pragma_Arg
14010 ("expression of pragma % must be static", Expr);
14011 return;
14012 end if;
14013 end if;
14015 -- Chain the pragma on the contract for further processing
14017 Add_Contract_Item (N, Subp);
14018 end Extensions_Visible;
14020 --------------
14021 -- External --
14022 --------------
14024 -- pragma External (
14025 -- [ Convention =>] convention_IDENTIFIER,
14026 -- [ Entity =>] LOCAL_NAME
14027 -- [, [External_Name =>] static_string_EXPRESSION ]
14028 -- [, [Link_Name =>] static_string_EXPRESSION ]);
14030 when Pragma_External => External : declare
14031 Def_Id : Entity_Id;
14033 C : Convention_Id;
14034 pragma Warnings (Off, C);
14036 begin
14037 GNAT_Pragma;
14038 Check_Arg_Order
14039 ((Name_Convention,
14040 Name_Entity,
14041 Name_External_Name,
14042 Name_Link_Name));
14043 Check_At_Least_N_Arguments (2);
14044 Check_At_Most_N_Arguments (4);
14045 Process_Convention (C, Def_Id);
14046 Note_Possible_Modification
14047 (Get_Pragma_Arg (Arg2), Sure => False);
14048 Process_Interface_Name (Def_Id, Arg3, Arg4);
14049 Set_Exported (Def_Id, Arg2);
14050 end External;
14052 --------------------------
14053 -- External_Name_Casing --
14054 --------------------------
14056 -- pragma External_Name_Casing (
14057 -- UPPERCASE | LOWERCASE
14058 -- [, AS_IS | UPPERCASE | LOWERCASE]);
14060 when Pragma_External_Name_Casing => External_Name_Casing : declare
14061 begin
14062 GNAT_Pragma;
14063 Check_No_Identifiers;
14065 if Arg_Count = 2 then
14066 Check_Arg_Is_One_Of
14067 (Arg2, Name_As_Is, Name_Uppercase, Name_Lowercase);
14069 case Chars (Get_Pragma_Arg (Arg2)) is
14070 when Name_As_Is =>
14071 Opt.External_Name_Exp_Casing := As_Is;
14073 when Name_Uppercase =>
14074 Opt.External_Name_Exp_Casing := Uppercase;
14076 when Name_Lowercase =>
14077 Opt.External_Name_Exp_Casing := Lowercase;
14079 when others =>
14080 null;
14081 end case;
14083 else
14084 Check_Arg_Count (1);
14085 end if;
14087 Check_Arg_Is_One_Of (Arg1, Name_Uppercase, Name_Lowercase);
14089 case Chars (Get_Pragma_Arg (Arg1)) is
14090 when Name_Uppercase =>
14091 Opt.External_Name_Imp_Casing := Uppercase;
14093 when Name_Lowercase =>
14094 Opt.External_Name_Imp_Casing := Lowercase;
14096 when others =>
14097 null;
14098 end case;
14099 end External_Name_Casing;
14101 ---------------
14102 -- Fast_Math --
14103 ---------------
14105 -- pragma Fast_Math;
14107 when Pragma_Fast_Math =>
14108 GNAT_Pragma;
14109 Check_No_Identifiers;
14110 Check_Valid_Configuration_Pragma;
14111 Fast_Math := True;
14113 --------------------------
14114 -- Favor_Top_Level --
14115 --------------------------
14117 -- pragma Favor_Top_Level (type_NAME);
14119 when Pragma_Favor_Top_Level => Favor_Top_Level : declare
14120 Named_Entity : Entity_Id;
14122 begin
14123 GNAT_Pragma;
14124 Check_No_Identifiers;
14125 Check_Arg_Count (1);
14126 Check_Arg_Is_Local_Name (Arg1);
14127 Named_Entity := Entity (Get_Pragma_Arg (Arg1));
14129 -- If it's an access-to-subprogram type (in particular, not a
14130 -- subtype), set the flag on that type.
14132 if Is_Access_Subprogram_Type (Named_Entity) then
14133 Set_Can_Use_Internal_Rep (Named_Entity, False);
14135 -- Otherwise it's an error (name denotes the wrong sort of entity)
14137 else
14138 Error_Pragma_Arg
14139 ("access-to-subprogram type expected",
14140 Get_Pragma_Arg (Arg1));
14141 end if;
14142 end Favor_Top_Level;
14144 ---------------------------
14145 -- Finalize_Storage_Only --
14146 ---------------------------
14148 -- pragma Finalize_Storage_Only (first_subtype_LOCAL_NAME);
14150 when Pragma_Finalize_Storage_Only => Finalize_Storage : declare
14151 Assoc : constant Node_Id := Arg1;
14152 Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
14153 Typ : Entity_Id;
14155 begin
14156 GNAT_Pragma;
14157 Check_No_Identifiers;
14158 Check_Arg_Count (1);
14159 Check_Arg_Is_Local_Name (Arg1);
14161 Find_Type (Type_Id);
14162 Typ := Entity (Type_Id);
14164 if Typ = Any_Type
14165 or else Rep_Item_Too_Early (Typ, N)
14166 then
14167 return;
14168 else
14169 Typ := Underlying_Type (Typ);
14170 end if;
14172 if not Is_Controlled (Typ) then
14173 Error_Pragma ("pragma% must specify controlled type");
14174 end if;
14176 Check_First_Subtype (Arg1);
14178 if Finalize_Storage_Only (Typ) then
14179 Error_Pragma ("duplicate pragma%, only one allowed");
14181 elsif not Rep_Item_Too_Late (Typ, N) then
14182 Set_Finalize_Storage_Only (Base_Type (Typ), True);
14183 end if;
14184 end Finalize_Storage;
14186 -----------
14187 -- Ghost --
14188 -----------
14190 -- pragma Ghost [ (boolean_EXPRESSION) ];
14192 when Pragma_Ghost => Ghost : declare
14193 Context : Node_Id;
14194 Expr : Node_Id;
14195 Id : Entity_Id;
14196 Orig_Stmt : Node_Id;
14197 Prev_Id : Entity_Id;
14198 Stmt : Node_Id;
14200 begin
14201 GNAT_Pragma;
14202 Check_No_Identifiers;
14203 Check_At_Most_N_Arguments (1);
14205 Context := Parent (N);
14207 -- Handle compilation units
14209 if Nkind (Context) = N_Compilation_Unit_Aux then
14210 Context := Unit (Parent (Context));
14211 end if;
14213 Id := Empty;
14214 Stmt := Prev (N);
14215 while Present (Stmt) loop
14217 -- Skip prior pragmas, but check for duplicates
14219 if Nkind (Stmt) = N_Pragma then
14220 if Pragma_Name (Stmt) = Pname then
14221 Error_Msg_Name_1 := Pname;
14222 Error_Msg_Sloc := Sloc (Stmt);
14223 Error_Msg_N ("pragma % duplicates pragma declared#", N);
14224 end if;
14226 -- Protected and task types cannot be subject to pragma Ghost
14228 elsif Nkind (Stmt) = N_Protected_Type_Declaration then
14229 Error_Pragma ("pragma % cannot apply to a protected type");
14230 return;
14232 elsif Nkind (Stmt) = N_Task_Type_Declaration then
14233 Error_Pragma ("pragma % cannot apply to a task type");
14234 return;
14236 -- Skip internally generated code
14238 elsif not Comes_From_Source (Stmt) then
14239 Orig_Stmt := Original_Node (Stmt);
14241 -- When pragma Ghost applies to an untagged derivation, the
14242 -- derivation is transformed into a [sub]type declaration.
14244 if Nkind_In (Stmt, N_Full_Type_Declaration,
14245 N_Subtype_Declaration)
14246 and then Comes_From_Source (Orig_Stmt)
14247 and then Nkind (Orig_Stmt) = N_Full_Type_Declaration
14248 and then Nkind (Type_Definition (Orig_Stmt)) =
14249 N_Derived_Type_Definition
14250 then
14251 Id := Defining_Entity (Stmt);
14252 exit;
14254 -- When pragma Ghost applies to an expression function, the
14255 -- expression function is transformed into a subprogram.
14257 elsif Nkind (Stmt) = N_Subprogram_Declaration
14258 and then Comes_From_Source (Orig_Stmt)
14259 and then Nkind (Orig_Stmt) = N_Expression_Function
14260 then
14261 Id := Defining_Entity (Stmt);
14262 exit;
14263 end if;
14265 -- The pragma applies to a legal construct, stop the traversal
14267 elsif Nkind_In (Stmt, N_Abstract_Subprogram_Declaration,
14268 N_Full_Type_Declaration,
14269 N_Generic_Subprogram_Declaration,
14270 N_Object_Declaration,
14271 N_Private_Extension_Declaration,
14272 N_Private_Type_Declaration,
14273 N_Subprogram_Declaration,
14274 N_Subtype_Declaration)
14275 then
14276 Id := Defining_Entity (Stmt);
14277 exit;
14279 -- The pragma does not apply to a legal construct, issue an
14280 -- error and stop the analysis.
14282 else
14283 Error_Pragma
14284 ("pragma % must apply to an object, package, subprogram "
14285 & "or type");
14286 return;
14287 end if;
14289 Stmt := Prev (Stmt);
14290 end loop;
14292 if No (Id) then
14294 -- When pragma Ghost is associated with a [generic] package, it
14295 -- appears in the visible declarations.
14297 if Nkind (Context) = N_Package_Specification
14298 and then Present (Visible_Declarations (Context))
14299 and then List_Containing (N) = Visible_Declarations (Context)
14300 then
14301 Id := Defining_Entity (Context);
14303 -- Pragma Ghost applies to a stand alone subprogram body
14305 elsif Nkind (Context) = N_Subprogram_Body
14306 and then No (Corresponding_Spec (Context))
14307 then
14308 Id := Defining_Entity (Context);
14309 end if;
14310 end if;
14312 if No (Id) then
14313 Error_Pragma
14314 ("pragma % must apply to an object, package, subprogram or "
14315 & "type");
14316 return;
14317 end if;
14319 -- A derived type or type extension cannot be subject to pragma
14320 -- Ghost if either the parent type or one of the progenitor types
14321 -- is not Ghost (SPARK RM 6.9(9)).
14323 if Is_Derived_Type (Id) then
14324 Check_Ghost_Derivation (Id);
14325 end if;
14327 -- Handle completions of types and constants that are subject to
14328 -- pragma Ghost.
14330 if Is_Record_Type (Id) or else Ekind (Id) = E_Constant then
14331 Prev_Id := Incomplete_Or_Partial_View (Id);
14333 if Present (Prev_Id) and then not Is_Ghost_Entity (Prev_Id) then
14334 Error_Msg_Name_1 := Pname;
14336 -- The full declaration of a deferred constant cannot be
14337 -- subject to pragma Ghost unless the deferred declaration
14338 -- is also Ghost (SPARK RM 6.9(10)).
14340 if Ekind (Prev_Id) = E_Constant then
14341 Error_Msg_Name_1 := Pname;
14342 Error_Msg_NE (Fix_Error
14343 ("pragma % must apply to declaration of deferred "
14344 & "constant &"), N, Id);
14345 return;
14347 -- Pragma Ghost may appear on the full view of an incomplete
14348 -- type because the incomplete declaration lacks aspects and
14349 -- cannot be subject to pragma Ghost.
14351 elsif Ekind (Prev_Id) = E_Incomplete_Type then
14352 null;
14354 -- The full declaration of a type cannot be subject to
14355 -- pragma Ghost unless the partial view is also Ghost
14356 -- (SPARK RM 6.9(10)).
14358 else
14359 Error_Msg_NE (Fix_Error
14360 ("pragma % must apply to partial view of type &"),
14361 N, Id);
14362 return;
14363 end if;
14364 end if;
14365 end if;
14367 -- Analyze the Boolean expression (if any)
14369 if Present (Arg1) then
14370 Expr := Get_Pragma_Arg (Arg1);
14372 Analyze_And_Resolve (Expr, Standard_Boolean);
14374 if Is_OK_Static_Expression (Expr) then
14376 -- "Ghostness" cannot be turned off once enabled within a
14377 -- region (SPARK RM 6.9(7)).
14379 if Is_False (Expr_Value (Expr))
14380 and then Within_Ghost_Scope
14381 then
14382 Error_Pragma
14383 ("pragma % with value False cannot appear in enabled "
14384 & "ghost region");
14385 return;
14386 end if;
14388 -- Otherwie the expression is not static
14390 else
14391 Error_Pragma_Arg
14392 ("expression of pragma % must be static", Expr);
14393 return;
14394 end if;
14395 end if;
14397 Set_Is_Ghost_Entity (Id);
14398 end Ghost;
14400 ------------
14401 -- Global --
14402 ------------
14404 -- pragma Global (GLOBAL_SPECIFICATION);
14406 -- GLOBAL_SPECIFICATION ::=
14407 -- null
14408 -- | GLOBAL_LIST
14409 -- | MODED_GLOBAL_LIST {, MODED_GLOBAL_LIST}
14411 -- MODED_GLOBAL_LIST ::= MODE_SELECTOR => GLOBAL_LIST
14413 -- MODE_SELECTOR ::= In_Out | Input | Output | Proof_In
14414 -- GLOBAL_LIST ::= GLOBAL_ITEM | (GLOBAL_ITEM {, GLOBAL_ITEM})
14415 -- GLOBAL_ITEM ::= NAME
14417 when Pragma_Global => Global : declare
14418 Subp_Decl : Node_Id;
14420 begin
14421 GNAT_Pragma;
14422 Check_Arg_Count (1);
14423 Ensure_Aggregate_Form (Arg1);
14425 -- Ensure the proper placement of the pragma. Global must be
14426 -- associated with a subprogram declaration or a body that acts
14427 -- as a spec.
14429 Subp_Decl :=
14430 Find_Related_Subprogram_Or_Body (N, Do_Checks => True);
14432 if Nkind (Subp_Decl) = N_Subprogram_Declaration then
14433 null;
14435 -- Body acts as spec
14437 elsif Nkind (Subp_Decl) = N_Subprogram_Body
14438 and then No (Corresponding_Spec (Subp_Decl))
14439 then
14440 null;
14442 -- Body stub acts as spec
14444 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
14445 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
14446 then
14447 null;
14449 else
14450 Pragma_Misplaced;
14451 return;
14452 end if;
14454 -- When the pragma appears on a subprogram body, perform the full
14455 -- analysis now.
14457 if Nkind (Subp_Decl) = N_Subprogram_Body then
14458 Analyze_Global_In_Decl_Part (N);
14460 -- When Global applies to a subprogram compilation unit, the
14461 -- corresponding pragma is placed after the unit's declaration
14462 -- node and needs to be analyzed immediately.
14464 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration
14465 and then Nkind (Parent (Subp_Decl)) = N_Compilation_Unit
14466 then
14467 Analyze_Global_In_Decl_Part (N);
14468 end if;
14470 -- Chain the pragma on the contract for further processing
14472 Add_Contract_Item (N, Defining_Entity (Subp_Decl));
14473 end Global;
14475 -----------
14476 -- Ident --
14477 -----------
14479 -- pragma Ident (static_string_EXPRESSION)
14481 -- Note: pragma Comment shares this processing. Pragma Ident is
14482 -- identical in effect to pragma Commment.
14484 when Pragma_Ident | Pragma_Comment => Ident : declare
14485 Str : Node_Id;
14487 begin
14488 GNAT_Pragma;
14489 Check_Arg_Count (1);
14490 Check_No_Identifiers;
14491 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
14492 Store_Note (N);
14494 Str := Expr_Value_S (Get_Pragma_Arg (Arg1));
14496 declare
14497 CS : Node_Id;
14498 GP : Node_Id;
14500 begin
14501 GP := Parent (Parent (N));
14503 if Nkind_In (GP, N_Package_Declaration,
14504 N_Generic_Package_Declaration)
14505 then
14506 GP := Parent (GP);
14507 end if;
14509 -- If we have a compilation unit, then record the ident value,
14510 -- checking for improper duplication.
14512 if Nkind (GP) = N_Compilation_Unit then
14513 CS := Ident_String (Current_Sem_Unit);
14515 if Present (CS) then
14517 -- If we have multiple instances, concatenate them, but
14518 -- not in ASIS, where we want the original tree.
14520 if not ASIS_Mode then
14521 Start_String (Strval (CS));
14522 Store_String_Char (' ');
14523 Store_String_Chars (Strval (Str));
14524 Set_Strval (CS, End_String);
14525 end if;
14527 else
14528 Set_Ident_String (Current_Sem_Unit, Str);
14529 end if;
14531 -- For subunits, we just ignore the Ident, since in GNAT these
14532 -- are not separate object files, and hence not separate units
14533 -- in the unit table.
14535 elsif Nkind (GP) = N_Subunit then
14536 null;
14537 end if;
14538 end;
14539 end Ident;
14541 ----------------------------
14542 -- Implementation_Defined --
14543 ----------------------------
14545 -- pragma Implementation_Defined (LOCAL_NAME);
14547 -- Marks previously declared entity as implementation defined. For
14548 -- an overloaded entity, applies to the most recent homonym.
14550 -- pragma Implementation_Defined;
14552 -- The form with no arguments appears anywhere within a scope, most
14553 -- typically a package spec, and indicates that all entities that are
14554 -- defined within the package spec are Implementation_Defined.
14556 when Pragma_Implementation_Defined => Implementation_Defined : declare
14557 Ent : Entity_Id;
14559 begin
14560 GNAT_Pragma;
14561 Check_No_Identifiers;
14563 -- Form with no arguments
14565 if Arg_Count = 0 then
14566 Set_Is_Implementation_Defined (Current_Scope);
14568 -- Form with one argument
14570 else
14571 Check_Arg_Count (1);
14572 Check_Arg_Is_Local_Name (Arg1);
14573 Ent := Entity (Get_Pragma_Arg (Arg1));
14574 Set_Is_Implementation_Defined (Ent);
14575 end if;
14576 end Implementation_Defined;
14578 -----------------
14579 -- Implemented --
14580 -----------------
14582 -- pragma Implemented (procedure_LOCAL_NAME, IMPLEMENTATION_KIND);
14584 -- IMPLEMENTATION_KIND ::=
14585 -- By_Entry | By_Protected_Procedure | By_Any | Optional
14587 -- "By_Any" and "Optional" are treated as synonyms in order to
14588 -- support Ada 2012 aspect Synchronization.
14590 when Pragma_Implemented => Implemented : declare
14591 Proc_Id : Entity_Id;
14592 Typ : Entity_Id;
14594 begin
14595 Ada_2012_Pragma;
14596 Check_Arg_Count (2);
14597 Check_No_Identifiers;
14598 Check_Arg_Is_Identifier (Arg1);
14599 Check_Arg_Is_Local_Name (Arg1);
14600 Check_Arg_Is_One_Of (Arg2,
14601 Name_By_Any,
14602 Name_By_Entry,
14603 Name_By_Protected_Procedure,
14604 Name_Optional);
14606 -- Extract the name of the local procedure
14608 Proc_Id := Entity (Get_Pragma_Arg (Arg1));
14610 -- Ada 2012 (AI05-0030): The procedure_LOCAL_NAME must denote a
14611 -- primitive procedure of a synchronized tagged type.
14613 if Ekind (Proc_Id) = E_Procedure
14614 and then Is_Primitive (Proc_Id)
14615 and then Present (First_Formal (Proc_Id))
14616 then
14617 Typ := Etype (First_Formal (Proc_Id));
14619 if Is_Tagged_Type (Typ)
14620 and then
14622 -- Check for a protected, a synchronized or a task interface
14624 ((Is_Interface (Typ)
14625 and then Is_Synchronized_Interface (Typ))
14627 -- Check for a protected type or a task type that implements
14628 -- an interface.
14630 or else
14631 (Is_Concurrent_Record_Type (Typ)
14632 and then Present (Interfaces (Typ)))
14634 -- In analysis-only mode, examine original protected type
14636 or else
14637 (Nkind (Parent (Typ)) = N_Protected_Type_Declaration
14638 and then Present (Interface_List (Parent (Typ))))
14640 -- Check for a private record extension with keyword
14641 -- "synchronized".
14643 or else
14644 (Ekind_In (Typ, E_Record_Type_With_Private,
14645 E_Record_Subtype_With_Private)
14646 and then Synchronized_Present (Parent (Typ))))
14647 then
14648 null;
14649 else
14650 Error_Pragma_Arg
14651 ("controlling formal must be of synchronized tagged type",
14652 Arg1);
14653 return;
14654 end if;
14656 -- Procedures declared inside a protected type must be accepted
14658 elsif Ekind (Proc_Id) = E_Procedure
14659 and then Is_Protected_Type (Scope (Proc_Id))
14660 then
14661 null;
14663 -- The first argument is not a primitive procedure
14665 else
14666 Error_Pragma_Arg
14667 ("pragma % must be applied to a primitive procedure", Arg1);
14668 return;
14669 end if;
14671 -- Ada 2012 (AI05-0030): Cannot apply the implementation_kind
14672 -- By_Protected_Procedure to the primitive procedure of a task
14673 -- interface.
14675 if Chars (Arg2) = Name_By_Protected_Procedure
14676 and then Is_Interface (Typ)
14677 and then Is_Task_Interface (Typ)
14678 then
14679 Error_Pragma_Arg
14680 ("implementation kind By_Protected_Procedure cannot be "
14681 & "applied to a task interface primitive", Arg2);
14682 return;
14683 end if;
14685 Record_Rep_Item (Proc_Id, N);
14686 end Implemented;
14688 ----------------------
14689 -- Implicit_Packing --
14690 ----------------------
14692 -- pragma Implicit_Packing;
14694 when Pragma_Implicit_Packing =>
14695 GNAT_Pragma;
14696 Check_Arg_Count (0);
14697 Implicit_Packing := True;
14699 ------------
14700 -- Import --
14701 ------------
14703 -- pragma Import (
14704 -- [Convention =>] convention_IDENTIFIER,
14705 -- [Entity =>] LOCAL_NAME
14706 -- [, [External_Name =>] static_string_EXPRESSION ]
14707 -- [, [Link_Name =>] static_string_EXPRESSION ]);
14709 when Pragma_Import =>
14710 Check_Ada_83_Warning;
14711 Check_Arg_Order
14712 ((Name_Convention,
14713 Name_Entity,
14714 Name_External_Name,
14715 Name_Link_Name));
14717 Check_At_Least_N_Arguments (2);
14718 Check_At_Most_N_Arguments (4);
14719 Process_Import_Or_Interface;
14721 ---------------------
14722 -- Import_Function --
14723 ---------------------
14725 -- pragma Import_Function (
14726 -- [Internal =>] LOCAL_NAME,
14727 -- [, [External =>] EXTERNAL_SYMBOL]
14728 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
14729 -- [, [Result_Type =>] SUBTYPE_MARK]
14730 -- [, [Mechanism =>] MECHANISM]
14731 -- [, [Result_Mechanism =>] MECHANISM_NAME]);
14733 -- EXTERNAL_SYMBOL ::=
14734 -- IDENTIFIER
14735 -- | static_string_EXPRESSION
14737 -- PARAMETER_TYPES ::=
14738 -- null
14739 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
14741 -- TYPE_DESIGNATOR ::=
14742 -- subtype_NAME
14743 -- | subtype_Name ' Access
14745 -- MECHANISM ::=
14746 -- MECHANISM_NAME
14747 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
14749 -- MECHANISM_ASSOCIATION ::=
14750 -- [formal_parameter_NAME =>] MECHANISM_NAME
14752 -- MECHANISM_NAME ::=
14753 -- Value
14754 -- | Reference
14756 when Pragma_Import_Function => Import_Function : declare
14757 Args : Args_List (1 .. 6);
14758 Names : constant Name_List (1 .. 6) := (
14759 Name_Internal,
14760 Name_External,
14761 Name_Parameter_Types,
14762 Name_Result_Type,
14763 Name_Mechanism,
14764 Name_Result_Mechanism);
14766 Internal : Node_Id renames Args (1);
14767 External : Node_Id renames Args (2);
14768 Parameter_Types : Node_Id renames Args (3);
14769 Result_Type : Node_Id renames Args (4);
14770 Mechanism : Node_Id renames Args (5);
14771 Result_Mechanism : Node_Id renames Args (6);
14773 begin
14774 GNAT_Pragma;
14775 Gather_Associations (Names, Args);
14776 Process_Extended_Import_Export_Subprogram_Pragma (
14777 Arg_Internal => Internal,
14778 Arg_External => External,
14779 Arg_Parameter_Types => Parameter_Types,
14780 Arg_Result_Type => Result_Type,
14781 Arg_Mechanism => Mechanism,
14782 Arg_Result_Mechanism => Result_Mechanism);
14783 end Import_Function;
14785 -------------------
14786 -- Import_Object --
14787 -------------------
14789 -- pragma Import_Object (
14790 -- [Internal =>] LOCAL_NAME
14791 -- [, [External =>] EXTERNAL_SYMBOL]
14792 -- [, [Size =>] EXTERNAL_SYMBOL]);
14794 -- EXTERNAL_SYMBOL ::=
14795 -- IDENTIFIER
14796 -- | static_string_EXPRESSION
14798 when Pragma_Import_Object => Import_Object : declare
14799 Args : Args_List (1 .. 3);
14800 Names : constant Name_List (1 .. 3) := (
14801 Name_Internal,
14802 Name_External,
14803 Name_Size);
14805 Internal : Node_Id renames Args (1);
14806 External : Node_Id renames Args (2);
14807 Size : Node_Id renames Args (3);
14809 begin
14810 GNAT_Pragma;
14811 Gather_Associations (Names, Args);
14812 Process_Extended_Import_Export_Object_Pragma (
14813 Arg_Internal => Internal,
14814 Arg_External => External,
14815 Arg_Size => Size);
14816 end Import_Object;
14818 ----------------------
14819 -- Import_Procedure --
14820 ----------------------
14822 -- pragma Import_Procedure (
14823 -- [Internal =>] LOCAL_NAME
14824 -- [, [External =>] EXTERNAL_SYMBOL]
14825 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
14826 -- [, [Mechanism =>] MECHANISM]);
14828 -- EXTERNAL_SYMBOL ::=
14829 -- IDENTIFIER
14830 -- | static_string_EXPRESSION
14832 -- PARAMETER_TYPES ::=
14833 -- null
14834 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
14836 -- TYPE_DESIGNATOR ::=
14837 -- subtype_NAME
14838 -- | subtype_Name ' Access
14840 -- MECHANISM ::=
14841 -- MECHANISM_NAME
14842 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
14844 -- MECHANISM_ASSOCIATION ::=
14845 -- [formal_parameter_NAME =>] MECHANISM_NAME
14847 -- MECHANISM_NAME ::=
14848 -- Value
14849 -- | Reference
14851 when Pragma_Import_Procedure => Import_Procedure : declare
14852 Args : Args_List (1 .. 4);
14853 Names : constant Name_List (1 .. 4) := (
14854 Name_Internal,
14855 Name_External,
14856 Name_Parameter_Types,
14857 Name_Mechanism);
14859 Internal : Node_Id renames Args (1);
14860 External : Node_Id renames Args (2);
14861 Parameter_Types : Node_Id renames Args (3);
14862 Mechanism : Node_Id renames Args (4);
14864 begin
14865 GNAT_Pragma;
14866 Gather_Associations (Names, Args);
14867 Process_Extended_Import_Export_Subprogram_Pragma (
14868 Arg_Internal => Internal,
14869 Arg_External => External,
14870 Arg_Parameter_Types => Parameter_Types,
14871 Arg_Mechanism => Mechanism);
14872 end Import_Procedure;
14874 -----------------------------
14875 -- Import_Valued_Procedure --
14876 -----------------------------
14878 -- pragma Import_Valued_Procedure (
14879 -- [Internal =>] LOCAL_NAME
14880 -- [, [External =>] EXTERNAL_SYMBOL]
14881 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
14882 -- [, [Mechanism =>] MECHANISM]);
14884 -- EXTERNAL_SYMBOL ::=
14885 -- IDENTIFIER
14886 -- | static_string_EXPRESSION
14888 -- PARAMETER_TYPES ::=
14889 -- null
14890 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
14892 -- TYPE_DESIGNATOR ::=
14893 -- subtype_NAME
14894 -- | subtype_Name ' Access
14896 -- MECHANISM ::=
14897 -- MECHANISM_NAME
14898 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
14900 -- MECHANISM_ASSOCIATION ::=
14901 -- [formal_parameter_NAME =>] MECHANISM_NAME
14903 -- MECHANISM_NAME ::=
14904 -- Value
14905 -- | Reference
14907 when Pragma_Import_Valued_Procedure =>
14908 Import_Valued_Procedure : declare
14909 Args : Args_List (1 .. 4);
14910 Names : constant Name_List (1 .. 4) := (
14911 Name_Internal,
14912 Name_External,
14913 Name_Parameter_Types,
14914 Name_Mechanism);
14916 Internal : Node_Id renames Args (1);
14917 External : Node_Id renames Args (2);
14918 Parameter_Types : Node_Id renames Args (3);
14919 Mechanism : Node_Id renames Args (4);
14921 begin
14922 GNAT_Pragma;
14923 Gather_Associations (Names, Args);
14924 Process_Extended_Import_Export_Subprogram_Pragma (
14925 Arg_Internal => Internal,
14926 Arg_External => External,
14927 Arg_Parameter_Types => Parameter_Types,
14928 Arg_Mechanism => Mechanism);
14929 end Import_Valued_Procedure;
14931 -----------------
14932 -- Independent --
14933 -----------------
14935 -- pragma Independent (LOCAL_NAME);
14937 when Pragma_Independent =>
14938 Process_Atomic_Independent_Shared_Volatile;
14940 ----------------------------
14941 -- Independent_Components --
14942 ----------------------------
14944 -- pragma Independent_Components (array_or_record_LOCAL_NAME);
14946 when Pragma_Independent_Components => Independent_Components : declare
14947 E_Id : Node_Id;
14948 E : Entity_Id;
14949 D : Node_Id;
14950 K : Node_Kind;
14951 C : Node_Id;
14953 begin
14954 Check_Ada_83_Warning;
14955 Ada_2012_Pragma;
14956 Check_No_Identifiers;
14957 Check_Arg_Count (1);
14958 Check_Arg_Is_Local_Name (Arg1);
14959 E_Id := Get_Pragma_Arg (Arg1);
14961 if Etype (E_Id) = Any_Type then
14962 return;
14963 end if;
14965 E := Entity (E_Id);
14967 -- Check duplicate before we chain ourselves
14969 Check_Duplicate_Pragma (E);
14971 -- Check appropriate entity
14973 if Rep_Item_Too_Early (E, N)
14974 or else
14975 Rep_Item_Too_Late (E, N)
14976 then
14977 return;
14978 end if;
14980 D := Declaration_Node (E);
14981 K := Nkind (D);
14983 -- The flag is set on the base type, or on the object
14985 if K = N_Full_Type_Declaration
14986 and then (Is_Array_Type (E) or else Is_Record_Type (E))
14987 then
14988 Set_Has_Independent_Components (Base_Type (E));
14989 Independence_Checks.Append ((N, Base_Type (E)));
14991 -- For record type, set all components independent
14993 if Is_Record_Type (E) then
14994 C := First_Component (E);
14995 while Present (C) loop
14996 Set_Is_Independent (C);
14997 Next_Component (C);
14998 end loop;
14999 end if;
15001 elsif (Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
15002 and then Nkind (D) = N_Object_Declaration
15003 and then Nkind (Object_Definition (D)) =
15004 N_Constrained_Array_Definition
15005 then
15006 Set_Has_Independent_Components (E);
15007 Independence_Checks.Append ((N, E));
15009 else
15010 Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
15011 end if;
15012 end Independent_Components;
15014 -----------------------
15015 -- Initial_Condition --
15016 -----------------------
15018 -- pragma Initial_Condition (boolean_EXPRESSION);
15020 when Pragma_Initial_Condition => Initial_Condition : declare
15021 Context : constant Node_Id := Parent (Parent (N));
15022 Pack_Id : Entity_Id;
15023 Stmt : Node_Id;
15025 begin
15026 GNAT_Pragma;
15027 Check_No_Identifiers;
15028 Check_Arg_Count (1);
15030 -- Ensure the proper placement of the pragma. Initial_Condition
15031 -- must be associated with a package declaration.
15033 if not Nkind_In (Context, N_Generic_Package_Declaration,
15034 N_Package_Declaration)
15035 then
15036 Pragma_Misplaced;
15037 return;
15038 end if;
15040 Stmt := Prev (N);
15041 while Present (Stmt) loop
15043 -- Skip prior pragmas, but check for duplicates
15045 if Nkind (Stmt) = N_Pragma then
15046 if Pragma_Name (Stmt) = Pname then
15047 Error_Msg_Name_1 := Pname;
15048 Error_Msg_Sloc := Sloc (Stmt);
15049 Error_Msg_N ("pragma % duplicates pragma declared #", N);
15050 end if;
15052 -- Skip internally generated code
15054 elsif not Comes_From_Source (Stmt) then
15055 null;
15057 -- The pragma does not apply to a legal construct, issue an
15058 -- error and stop the analysis.
15060 else
15061 Pragma_Misplaced;
15062 return;
15063 end if;
15065 Stmt := Prev (Stmt);
15066 end loop;
15068 -- The pragma must be analyzed at the end of the visible
15069 -- declarations of the related package. Save the pragma for later
15070 -- (see Analyze_Initial_Condition_In_Decl_Part) by adding it to
15071 -- the contract of the package.
15073 Pack_Id := Defining_Entity (Context);
15074 Add_Contract_Item (N, Pack_Id);
15076 -- Verify the declaration order of pragma Initial_Condition with
15077 -- respect to pragmas Abstract_State and Initializes when SPARK
15078 -- checks are enabled.
15080 if SPARK_Mode /= Off then
15081 Check_Declaration_Order
15082 (First => Get_Pragma (Pack_Id, Pragma_Abstract_State),
15083 Second => N);
15085 Check_Declaration_Order
15086 (First => Get_Pragma (Pack_Id, Pragma_Initializes),
15087 Second => N);
15088 end if;
15089 end Initial_Condition;
15091 ------------------------
15092 -- Initialize_Scalars --
15093 ------------------------
15095 -- pragma Initialize_Scalars;
15097 when Pragma_Initialize_Scalars =>
15098 GNAT_Pragma;
15099 Check_Arg_Count (0);
15100 Check_Valid_Configuration_Pragma;
15101 Check_Restriction (No_Initialize_Scalars, N);
15103 -- Initialize_Scalars creates false positives in CodePeer, and
15104 -- incorrect negative results in GNATprove mode, so ignore this
15105 -- pragma in these modes.
15107 if not Restriction_Active (No_Initialize_Scalars)
15108 and then not (CodePeer_Mode or GNATprove_Mode)
15109 then
15110 Init_Or_Norm_Scalars := True;
15111 Initialize_Scalars := True;
15112 end if;
15114 -----------------
15115 -- Initializes --
15116 -----------------
15118 -- pragma Initializes (INITIALIZATION_SPEC);
15120 -- INITIALIZATION_SPEC ::= null | INITIALIZATION_LIST
15122 -- INITIALIZATION_LIST ::=
15123 -- INITIALIZATION_ITEM
15124 -- | (INITIALIZATION_ITEM {, INITIALIZATION_ITEM})
15126 -- INITIALIZATION_ITEM ::= name [=> INPUT_LIST]
15128 -- INPUT_LIST ::=
15129 -- null
15130 -- | INPUT
15131 -- | (INPUT {, INPUT})
15133 -- INPUT ::= name
15135 when Pragma_Initializes => Initializes : declare
15136 Context : constant Node_Id := Parent (Parent (N));
15137 Pack_Id : Entity_Id;
15138 Stmt : Node_Id;
15140 begin
15141 GNAT_Pragma;
15142 Check_No_Identifiers;
15143 Check_Arg_Count (1);
15144 Ensure_Aggregate_Form (Arg1);
15146 -- Ensure the proper placement of the pragma. Initializes must be
15147 -- associated with a package declaration.
15149 if not Nkind_In (Context, N_Generic_Package_Declaration,
15150 N_Package_Declaration)
15151 then
15152 Pragma_Misplaced;
15153 return;
15154 end if;
15156 Stmt := Prev (N);
15157 while Present (Stmt) loop
15159 -- Skip prior pragmas, but check for duplicates
15161 if Nkind (Stmt) = N_Pragma then
15162 if Pragma_Name (Stmt) = Pname then
15163 Error_Msg_Name_1 := Pname;
15164 Error_Msg_Sloc := Sloc (Stmt);
15165 Error_Msg_N ("pragma % duplicates pragma declared #", N);
15166 end if;
15168 -- Skip internally generated code
15170 elsif not Comes_From_Source (Stmt) then
15171 null;
15173 -- The pragma does not apply to a legal construct, issue an
15174 -- error and stop the analysis.
15176 else
15177 Pragma_Misplaced;
15178 return;
15179 end if;
15181 Stmt := Prev (Stmt);
15182 end loop;
15184 -- The pragma must be analyzed at the end of the visible
15185 -- declarations of the related package. Save the pragma for later
15186 -- (see Analyze_Initializes_In_Decl_Part) by adding it to the
15187 -- contract of the package.
15189 Pack_Id := Defining_Entity (Context);
15190 Add_Contract_Item (N, Pack_Id);
15192 -- Verify the declaration order of pragmas Abstract_State and
15193 -- Initializes when SPARK checks are enabled.
15195 if SPARK_Mode /= Off then
15196 Check_Declaration_Order
15197 (First => Get_Pragma (Pack_Id, Pragma_Abstract_State),
15198 Second => N);
15199 end if;
15200 end Initializes;
15202 ------------
15203 -- Inline --
15204 ------------
15206 -- pragma Inline ( NAME {, NAME} );
15208 when Pragma_Inline =>
15210 -- Pragma always active unless in GNATprove mode. It is disabled
15211 -- in GNATprove mode because frontend inlining is applied
15212 -- independently of pragmas Inline and Inline_Always for
15213 -- formal verification, see Can_Be_Inlined_In_GNATprove_Mode
15214 -- in inline.ads.
15216 if not GNATprove_Mode then
15218 -- Inline status is Enabled if inlining option is active
15220 if Inline_Active then
15221 Process_Inline (Enabled);
15222 else
15223 Process_Inline (Disabled);
15224 end if;
15225 end if;
15227 -------------------
15228 -- Inline_Always --
15229 -------------------
15231 -- pragma Inline_Always ( NAME {, NAME} );
15233 when Pragma_Inline_Always =>
15234 GNAT_Pragma;
15236 -- Pragma always active unless in CodePeer mode or GNATprove
15237 -- mode. It is disabled in CodePeer mode because inlining is
15238 -- not helpful, and enabling it caused walk order issues. It
15239 -- is disabled in GNATprove mode because frontend inlining is
15240 -- applied independently of pragmas Inline and Inline_Always for
15241 -- formal verification, see Can_Be_Inlined_In_GNATprove_Mode in
15242 -- inline.ads.
15244 if not CodePeer_Mode and not GNATprove_Mode then
15245 Process_Inline (Enabled);
15246 end if;
15248 --------------------
15249 -- Inline_Generic --
15250 --------------------
15252 -- pragma Inline_Generic (NAME {, NAME});
15254 when Pragma_Inline_Generic =>
15255 GNAT_Pragma;
15256 Process_Generic_List;
15258 ----------------------
15259 -- Inspection_Point --
15260 ----------------------
15262 -- pragma Inspection_Point [(object_NAME {, object_NAME})];
15264 when Pragma_Inspection_Point => Inspection_Point : declare
15265 Arg : Node_Id;
15266 Exp : Node_Id;
15268 begin
15271 if Arg_Count > 0 then
15272 Arg := Arg1;
15273 loop
15274 Exp := Get_Pragma_Arg (Arg);
15275 Analyze (Exp);
15277 if not Is_Entity_Name (Exp)
15278 or else not Is_Object (Entity (Exp))
15279 then
15280 Error_Pragma_Arg ("object name required", Arg);
15281 end if;
15283 Next (Arg);
15284 exit when No (Arg);
15285 end loop;
15286 end if;
15287 end Inspection_Point;
15289 ---------------
15290 -- Interface --
15291 ---------------
15293 -- pragma Interface (
15294 -- [ Convention =>] convention_IDENTIFIER,
15295 -- [ Entity =>] LOCAL_NAME
15296 -- [, [External_Name =>] static_string_EXPRESSION ]
15297 -- [, [Link_Name =>] static_string_EXPRESSION ]);
15299 when Pragma_Interface =>
15300 GNAT_Pragma;
15301 Check_Arg_Order
15302 ((Name_Convention,
15303 Name_Entity,
15304 Name_External_Name,
15305 Name_Link_Name));
15306 Check_At_Least_N_Arguments (2);
15307 Check_At_Most_N_Arguments (4);
15308 Process_Import_Or_Interface;
15310 -- In Ada 2005, the permission to use Interface (a reserved word)
15311 -- as a pragma name is considered an obsolescent feature, and this
15312 -- pragma was already obsolescent in Ada 95.
15314 if Ada_Version >= Ada_95 then
15315 Check_Restriction
15316 (No_Obsolescent_Features, Pragma_Identifier (N));
15318 if Warn_On_Obsolescent_Feature then
15319 Error_Msg_N
15320 ("pragma Interface is an obsolescent feature?j?", N);
15321 Error_Msg_N
15322 ("|use pragma Import instead?j?", N);
15323 end if;
15324 end if;
15326 --------------------
15327 -- Interface_Name --
15328 --------------------
15330 -- pragma Interface_Name (
15331 -- [ Entity =>] LOCAL_NAME
15332 -- [,[External_Name =>] static_string_EXPRESSION ]
15333 -- [,[Link_Name =>] static_string_EXPRESSION ]);
15335 when Pragma_Interface_Name => Interface_Name : declare
15336 Id : Node_Id;
15337 Def_Id : Entity_Id;
15338 Hom_Id : Entity_Id;
15339 Found : Boolean;
15341 begin
15342 GNAT_Pragma;
15343 Check_Arg_Order
15344 ((Name_Entity, Name_External_Name, Name_Link_Name));
15345 Check_At_Least_N_Arguments (2);
15346 Check_At_Most_N_Arguments (3);
15347 Id := Get_Pragma_Arg (Arg1);
15348 Analyze (Id);
15350 -- This is obsolete from Ada 95 on, but it is an implementation
15351 -- defined pragma, so we do not consider that it violates the
15352 -- restriction (No_Obsolescent_Features).
15354 if Ada_Version >= Ada_95 then
15355 if Warn_On_Obsolescent_Feature then
15356 Error_Msg_N
15357 ("pragma Interface_Name is an obsolescent feature?j?", N);
15358 Error_Msg_N
15359 ("|use pragma Import instead?j?", N);
15360 end if;
15361 end if;
15363 if not Is_Entity_Name (Id) then
15364 Error_Pragma_Arg
15365 ("first argument for pragma% must be entity name", Arg1);
15366 elsif Etype (Id) = Any_Type then
15367 return;
15368 else
15369 Def_Id := Entity (Id);
15370 end if;
15372 -- Special DEC-compatible processing for the object case, forces
15373 -- object to be imported.
15375 if Ekind (Def_Id) = E_Variable then
15376 Kill_Size_Check_Code (Def_Id);
15377 Note_Possible_Modification (Id, Sure => False);
15379 -- Initialization is not allowed for imported variable
15381 if Present (Expression (Parent (Def_Id)))
15382 and then Comes_From_Source (Expression (Parent (Def_Id)))
15383 then
15384 Error_Msg_Sloc := Sloc (Def_Id);
15385 Error_Pragma_Arg
15386 ("no initialization allowed for declaration of& #",
15387 Arg2);
15389 else
15390 -- For compatibility, support VADS usage of providing both
15391 -- pragmas Interface and Interface_Name to obtain the effect
15392 -- of a single Import pragma.
15394 if Is_Imported (Def_Id)
15395 and then Present (First_Rep_Item (Def_Id))
15396 and then Nkind (First_Rep_Item (Def_Id)) = N_Pragma
15397 and then
15398 Pragma_Name (First_Rep_Item (Def_Id)) = Name_Interface
15399 then
15400 null;
15401 else
15402 Set_Imported (Def_Id);
15403 end if;
15405 Set_Is_Public (Def_Id);
15406 Process_Interface_Name (Def_Id, Arg2, Arg3);
15407 end if;
15409 -- Otherwise must be subprogram
15411 elsif not Is_Subprogram (Def_Id) then
15412 Error_Pragma_Arg
15413 ("argument of pragma% is not subprogram", Arg1);
15415 else
15416 Check_At_Most_N_Arguments (3);
15417 Hom_Id := Def_Id;
15418 Found := False;
15420 -- Loop through homonyms
15422 loop
15423 Def_Id := Get_Base_Subprogram (Hom_Id);
15425 if Is_Imported (Def_Id) then
15426 Process_Interface_Name (Def_Id, Arg2, Arg3);
15427 Found := True;
15428 end if;
15430 exit when From_Aspect_Specification (N);
15431 Hom_Id := Homonym (Hom_Id);
15433 exit when No (Hom_Id)
15434 or else Scope (Hom_Id) /= Current_Scope;
15435 end loop;
15437 if not Found then
15438 Error_Pragma_Arg
15439 ("argument of pragma% is not imported subprogram",
15440 Arg1);
15441 end if;
15442 end if;
15443 end Interface_Name;
15445 -----------------------
15446 -- Interrupt_Handler --
15447 -----------------------
15449 -- pragma Interrupt_Handler (handler_NAME);
15451 when Pragma_Interrupt_Handler =>
15452 Check_Ada_83_Warning;
15453 Check_Arg_Count (1);
15454 Check_No_Identifiers;
15456 if No_Run_Time_Mode then
15457 Error_Msg_CRT ("Interrupt_Handler pragma", N);
15458 else
15459 Check_Interrupt_Or_Attach_Handler;
15460 Process_Interrupt_Or_Attach_Handler;
15461 end if;
15463 ------------------------
15464 -- Interrupt_Priority --
15465 ------------------------
15467 -- pragma Interrupt_Priority [(EXPRESSION)];
15469 when Pragma_Interrupt_Priority => Interrupt_Priority : declare
15470 P : constant Node_Id := Parent (N);
15471 Arg : Node_Id;
15472 Ent : Entity_Id;
15474 begin
15475 Check_Ada_83_Warning;
15477 if Arg_Count /= 0 then
15478 Arg := Get_Pragma_Arg (Arg1);
15479 Check_Arg_Count (1);
15480 Check_No_Identifiers;
15482 -- The expression must be analyzed in the special manner
15483 -- described in "Handling of Default and Per-Object
15484 -- Expressions" in sem.ads.
15486 Preanalyze_Spec_Expression (Arg, RTE (RE_Interrupt_Priority));
15487 end if;
15489 if not Nkind_In (P, N_Task_Definition, N_Protected_Definition) then
15490 Pragma_Misplaced;
15491 return;
15493 else
15494 Ent := Defining_Identifier (Parent (P));
15496 -- Check duplicate pragma before we chain the pragma in the Rep
15497 -- Item chain of Ent.
15499 Check_Duplicate_Pragma (Ent);
15500 Record_Rep_Item (Ent, N);
15501 end if;
15502 end Interrupt_Priority;
15504 ---------------------
15505 -- Interrupt_State --
15506 ---------------------
15508 -- pragma Interrupt_State (
15509 -- [Name =>] INTERRUPT_ID,
15510 -- [State =>] INTERRUPT_STATE);
15512 -- INTERRUPT_ID => IDENTIFIER | static_integer_EXPRESSION
15513 -- INTERRUPT_STATE => System | Runtime | User
15515 -- Note: if the interrupt id is given as an identifier, then it must
15516 -- be one of the identifiers in Ada.Interrupts.Names. Otherwise it is
15517 -- given as a static integer expression which must be in the range of
15518 -- Ada.Interrupts.Interrupt_ID.
15520 when Pragma_Interrupt_State => Interrupt_State : declare
15521 Int_Id : constant Entity_Id := RTE (RE_Interrupt_ID);
15522 -- This is the entity Ada.Interrupts.Interrupt_ID;
15524 State_Type : Character;
15525 -- Set to 's'/'r'/'u' for System/Runtime/User
15527 IST_Num : Pos;
15528 -- Index to entry in Interrupt_States table
15530 Int_Val : Uint;
15531 -- Value of interrupt
15533 Arg1X : constant Node_Id := Get_Pragma_Arg (Arg1);
15534 -- The first argument to the pragma
15536 Int_Ent : Entity_Id;
15537 -- Interrupt entity in Ada.Interrupts.Names
15539 begin
15540 GNAT_Pragma;
15541 Check_Arg_Order ((Name_Name, Name_State));
15542 Check_Arg_Count (2);
15544 Check_Optional_Identifier (Arg1, Name_Name);
15545 Check_Optional_Identifier (Arg2, Name_State);
15546 Check_Arg_Is_Identifier (Arg2);
15548 -- First argument is identifier
15550 if Nkind (Arg1X) = N_Identifier then
15552 -- Search list of names in Ada.Interrupts.Names
15554 Int_Ent := First_Entity (RTE (RE_Names));
15555 loop
15556 if No (Int_Ent) then
15557 Error_Pragma_Arg ("invalid interrupt name", Arg1);
15559 elsif Chars (Int_Ent) = Chars (Arg1X) then
15560 Int_Val := Expr_Value (Constant_Value (Int_Ent));
15561 exit;
15562 end if;
15564 Next_Entity (Int_Ent);
15565 end loop;
15567 -- First argument is not an identifier, so it must be a static
15568 -- expression of type Ada.Interrupts.Interrupt_ID.
15570 else
15571 Check_Arg_Is_OK_Static_Expression (Arg1, Any_Integer);
15572 Int_Val := Expr_Value (Arg1X);
15574 if Int_Val < Expr_Value (Type_Low_Bound (Int_Id))
15575 or else
15576 Int_Val > Expr_Value (Type_High_Bound (Int_Id))
15577 then
15578 Error_Pragma_Arg
15579 ("value not in range of type "
15580 & """Ada.Interrupts.Interrupt_'I'D""", Arg1);
15581 end if;
15582 end if;
15584 -- Check OK state
15586 case Chars (Get_Pragma_Arg (Arg2)) is
15587 when Name_Runtime => State_Type := 'r';
15588 when Name_System => State_Type := 's';
15589 when Name_User => State_Type := 'u';
15591 when others =>
15592 Error_Pragma_Arg ("invalid interrupt state", Arg2);
15593 end case;
15595 -- Check if entry is already stored
15597 IST_Num := Interrupt_States.First;
15598 loop
15599 -- If entry not found, add it
15601 if IST_Num > Interrupt_States.Last then
15602 Interrupt_States.Append
15603 ((Interrupt_Number => UI_To_Int (Int_Val),
15604 Interrupt_State => State_Type,
15605 Pragma_Loc => Loc));
15606 exit;
15608 -- Case of entry for the same entry
15610 elsif Int_Val = Interrupt_States.Table (IST_Num).
15611 Interrupt_Number
15612 then
15613 -- If state matches, done, no need to make redundant entry
15615 exit when
15616 State_Type = Interrupt_States.Table (IST_Num).
15617 Interrupt_State;
15619 -- Otherwise if state does not match, error
15621 Error_Msg_Sloc :=
15622 Interrupt_States.Table (IST_Num).Pragma_Loc;
15623 Error_Pragma_Arg
15624 ("state conflicts with that given #", Arg2);
15625 exit;
15626 end if;
15628 IST_Num := IST_Num + 1;
15629 end loop;
15630 end Interrupt_State;
15632 ---------------
15633 -- Invariant --
15634 ---------------
15636 -- pragma Invariant
15637 -- ([Entity =>] type_LOCAL_NAME,
15638 -- [Check =>] EXPRESSION
15639 -- [,[Message =>] String_Expression]);
15641 when Pragma_Invariant => Invariant : declare
15642 Type_Id : Node_Id;
15643 Typ : Entity_Id;
15644 Discard : Boolean;
15646 begin
15647 GNAT_Pragma;
15648 Check_At_Least_N_Arguments (2);
15649 Check_At_Most_N_Arguments (3);
15650 Check_Optional_Identifier (Arg1, Name_Entity);
15651 Check_Optional_Identifier (Arg2, Name_Check);
15653 if Arg_Count = 3 then
15654 Check_Optional_Identifier (Arg3, Name_Message);
15655 Check_Arg_Is_OK_Static_Expression (Arg3, Standard_String);
15656 end if;
15658 Check_Arg_Is_Local_Name (Arg1);
15660 Type_Id := Get_Pragma_Arg (Arg1);
15661 Find_Type (Type_Id);
15662 Typ := Entity (Type_Id);
15664 if Typ = Any_Type then
15665 return;
15667 -- An invariant must apply to a private type, or appear in the
15668 -- private part of a package spec and apply to a completion.
15669 -- a class-wide invariant can only appear on a private declaration
15670 -- or private extension, not a completion.
15672 elsif Ekind_In (Typ, E_Private_Type,
15673 E_Record_Type_With_Private,
15674 E_Limited_Private_Type)
15675 then
15676 null;
15678 elsif In_Private_Part (Current_Scope)
15679 and then Has_Private_Declaration (Typ)
15680 and then not Class_Present (N)
15681 then
15682 null;
15684 elsif In_Private_Part (Current_Scope) then
15685 Error_Pragma_Arg
15686 ("pragma% only allowed for private type declared in "
15687 & "visible part", Arg1);
15689 else
15690 Error_Pragma_Arg
15691 ("pragma% only allowed for private type", Arg1);
15692 end if;
15694 -- Note that the type has at least one invariant, and also that
15695 -- it has inheritable invariants if we have Invariant'Class
15696 -- or Type_Invariant'Class. Build the corresponding invariant
15697 -- procedure declaration, so that calls to it can be generated
15698 -- before the body is built (e.g. within an expression function).
15700 Insert_After_And_Analyze
15701 (N, Build_Invariant_Procedure_Declaration (Typ));
15703 if Class_Present (N) then
15704 Set_Has_Inheritable_Invariants (Typ);
15705 end if;
15707 -- The remaining processing is simply to link the pragma on to
15708 -- the rep item chain, for processing when the type is frozen.
15709 -- This is accomplished by a call to Rep_Item_Too_Late.
15711 Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
15712 end Invariant;
15714 ----------------------
15715 -- Java_Constructor --
15716 ----------------------
15718 -- pragma Java_Constructor ([Entity =>] LOCAL_NAME);
15720 -- Also handles pragma CIL_Constructor
15722 when Pragma_CIL_Constructor | Pragma_Java_Constructor =>
15723 Java_Constructor : declare
15724 Convention : Convention_Id;
15725 Def_Id : Entity_Id;
15726 Hom_Id : Entity_Id;
15727 Id : Entity_Id;
15728 This_Formal : Entity_Id;
15730 begin
15731 GNAT_Pragma;
15732 Check_Arg_Count (1);
15733 Check_Optional_Identifier (Arg1, Name_Entity);
15734 Check_Arg_Is_Local_Name (Arg1);
15736 Id := Get_Pragma_Arg (Arg1);
15737 Find_Program_Unit_Name (Id);
15739 -- If we did not find the name, we are done
15741 if Etype (Id) = Any_Type then
15742 return;
15743 end if;
15745 -- Check wrong use of pragma in wrong VM target
15747 if VM_Target = No_VM then
15748 return;
15750 elsif VM_Target = CLI_Target
15751 and then Prag_Id = Pragma_Java_Constructor
15752 then
15753 Error_Pragma ("must use pragma 'C'I'L_'Constructor");
15755 elsif VM_Target = JVM_Target
15756 and then Prag_Id = Pragma_CIL_Constructor
15757 then
15758 Error_Pragma ("must use pragma 'Java_'Constructor");
15759 end if;
15761 case Prag_Id is
15762 when Pragma_CIL_Constructor => Convention := Convention_CIL;
15763 when Pragma_Java_Constructor => Convention := Convention_Java;
15764 when others => null;
15765 end case;
15767 Hom_Id := Entity (Id);
15769 -- Loop through homonyms
15771 loop
15772 Def_Id := Get_Base_Subprogram (Hom_Id);
15774 -- The constructor is required to be a function
15776 if Ekind (Def_Id) /= E_Function then
15777 if VM_Target = JVM_Target then
15778 Error_Pragma_Arg
15779 ("pragma% requires function returning a 'Java access "
15780 & "type", Def_Id);
15781 else
15782 Error_Pragma_Arg
15783 ("pragma% requires function returning a 'C'I'L access "
15784 & "type", Def_Id);
15785 end if;
15786 end if;
15788 -- Check arguments: For tagged type the first formal must be
15789 -- named "this" and its type must be a named access type
15790 -- designating a class-wide tagged type that has convention
15791 -- CIL/Java. The first formal must also have a null default
15792 -- value. For example:
15794 -- type Typ is tagged ...
15795 -- type Ref is access all Typ;
15796 -- pragma Convention (CIL, Typ);
15798 -- function New_Typ (This : Ref) return Ref;
15799 -- function New_Typ (This : Ref; I : Integer) return Ref;
15800 -- pragma Cil_Constructor (New_Typ);
15802 -- Reason: The first formal must NOT be a primitive of the
15803 -- tagged type.
15805 -- This rule also applies to constructors of delegates used
15806 -- to interface with standard target libraries. For example:
15808 -- type Delegate is access procedure ...
15809 -- pragma Import (CIL, Delegate, ...);
15811 -- function new_Delegate
15812 -- (This : Delegate := null; ... ) return Delegate;
15814 -- For value-types this rule does not apply.
15816 if not Is_Value_Type (Etype (Def_Id)) then
15817 if No (First_Formal (Def_Id)) then
15818 Error_Msg_Name_1 := Pname;
15819 Error_Msg_N ("% function must have parameters", Def_Id);
15820 return;
15821 end if;
15823 -- In the JRE library we have several occurrences in which
15824 -- the "this" parameter is not the first formal.
15826 This_Formal := First_Formal (Def_Id);
15828 -- In the JRE library we have several occurrences in which
15829 -- the "this" parameter is not the first formal. Search for
15830 -- it.
15832 if VM_Target = JVM_Target then
15833 while Present (This_Formal)
15834 and then Get_Name_String (Chars (This_Formal)) /= "this"
15835 loop
15836 Next_Formal (This_Formal);
15837 end loop;
15839 if No (This_Formal) then
15840 This_Formal := First_Formal (Def_Id);
15841 end if;
15842 end if;
15844 -- Warning: The first parameter should be named "this".
15845 -- We temporarily allow it because we have the following
15846 -- case in the Java runtime (file s-osinte.ads) ???
15848 -- function new_Thread
15849 -- (Self_Id : System.Address) return Thread_Id;
15850 -- pragma Java_Constructor (new_Thread);
15852 if VM_Target = JVM_Target
15853 and then Get_Name_String (Chars (First_Formal (Def_Id)))
15854 = "self_id"
15855 and then Etype (First_Formal (Def_Id)) = RTE (RE_Address)
15856 then
15857 null;
15859 elsif Get_Name_String (Chars (This_Formal)) /= "this" then
15860 Error_Msg_Name_1 := Pname;
15861 Error_Msg_N
15862 ("first formal of % function must be named `this`",
15863 Parent (This_Formal));
15865 elsif not Is_Access_Type (Etype (This_Formal)) then
15866 Error_Msg_Name_1 := Pname;
15867 Error_Msg_N
15868 ("first formal of % function must be an access type",
15869 Parameter_Type (Parent (This_Formal)));
15871 -- For delegates the type of the first formal must be a
15872 -- named access-to-subprogram type (see previous example)
15874 elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type
15875 and then Ekind (Etype (This_Formal))
15876 /= E_Access_Subprogram_Type
15877 then
15878 Error_Msg_Name_1 := Pname;
15879 Error_Msg_N
15880 ("first formal of % function must be a named access "
15881 & "to subprogram type",
15882 Parameter_Type (Parent (This_Formal)));
15884 -- Warning: We should reject anonymous access types because
15885 -- the constructor must not be handled as a primitive of the
15886 -- tagged type. We temporarily allow it because this profile
15887 -- is currently generated by cil2ada???
15889 elsif Ekind (Etype (Def_Id)) /= E_Access_Subprogram_Type
15890 and then not Ekind_In (Etype (This_Formal),
15891 E_Access_Type,
15892 E_General_Access_Type,
15893 E_Anonymous_Access_Type)
15894 then
15895 Error_Msg_Name_1 := Pname;
15896 Error_Msg_N
15897 ("first formal of % function must be a named access "
15898 & "type", Parameter_Type (Parent (This_Formal)));
15900 elsif Atree.Convention
15901 (Designated_Type (Etype (This_Formal))) /= Convention
15902 then
15903 Error_Msg_Name_1 := Pname;
15905 if Convention = Convention_Java then
15906 Error_Msg_N
15907 ("pragma% requires convention 'Cil in designated "
15908 & "type", Parameter_Type (Parent (This_Formal)));
15909 else
15910 Error_Msg_N
15911 ("pragma% requires convention 'Java in designated "
15912 & "type", Parameter_Type (Parent (This_Formal)));
15913 end if;
15915 elsif No (Expression (Parent (This_Formal)))
15916 or else Nkind (Expression (Parent (This_Formal))) /= N_Null
15917 then
15918 Error_Msg_Name_1 := Pname;
15919 Error_Msg_N
15920 ("pragma% requires first formal with default `null`",
15921 Parameter_Type (Parent (This_Formal)));
15922 end if;
15923 end if;
15925 -- Check result type: the constructor must be a function
15926 -- returning:
15927 -- * a value type (only allowed in the CIL compiler)
15928 -- * an access-to-subprogram type with convention Java/CIL
15929 -- * an access-type designating a type that has convention
15930 -- Java/CIL.
15932 if Is_Value_Type (Etype (Def_Id)) then
15933 null;
15935 -- Access-to-subprogram type with convention Java/CIL
15937 elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type then
15938 if Atree.Convention (Etype (Def_Id)) /= Convention then
15939 if Convention = Convention_Java then
15940 Error_Pragma_Arg
15941 ("pragma% requires function returning a 'Java "
15942 & "access type", Arg1);
15943 else
15944 pragma Assert (Convention = Convention_CIL);
15945 Error_Pragma_Arg
15946 ("pragma% requires function returning a 'C'I'L "
15947 & "access type", Arg1);
15948 end if;
15949 end if;
15951 elsif Is_Access_Type (Etype (Def_Id)) then
15952 if not Ekind_In (Etype (Def_Id), E_Access_Type,
15953 E_General_Access_Type)
15954 or else
15955 Atree.Convention
15956 (Designated_Type (Etype (Def_Id))) /= Convention
15957 then
15958 Error_Msg_Name_1 := Pname;
15960 if Convention = Convention_Java then
15961 Error_Pragma_Arg
15962 ("pragma% requires function returning a named "
15963 & "'Java access type", Arg1);
15964 else
15965 Error_Pragma_Arg
15966 ("pragma% requires function returning a named "
15967 & "'C'I'L access type", Arg1);
15968 end if;
15969 end if;
15970 end if;
15972 Set_Is_Constructor (Def_Id);
15973 Set_Convention (Def_Id, Convention);
15974 Set_Is_Imported (Def_Id);
15976 exit when From_Aspect_Specification (N);
15977 Hom_Id := Homonym (Hom_Id);
15979 exit when No (Hom_Id) or else Scope (Hom_Id) /= Current_Scope;
15980 end loop;
15981 end Java_Constructor;
15983 ----------------------
15984 -- Java_Interface --
15985 ----------------------
15987 -- pragma Java_Interface ([Entity =>] LOCAL_NAME);
15989 when Pragma_Java_Interface => Java_Interface : declare
15990 Arg : Node_Id;
15991 Typ : Entity_Id;
15993 begin
15994 GNAT_Pragma;
15995 Check_Arg_Count (1);
15996 Check_Optional_Identifier (Arg1, Name_Entity);
15997 Check_Arg_Is_Local_Name (Arg1);
15999 Arg := Get_Pragma_Arg (Arg1);
16000 Analyze (Arg);
16002 if Etype (Arg) = Any_Type then
16003 return;
16004 end if;
16006 if not Is_Entity_Name (Arg)
16007 or else not Is_Type (Entity (Arg))
16008 then
16009 Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
16010 end if;
16012 Typ := Underlying_Type (Entity (Arg));
16014 -- For now simply check some of the semantic constraints on the
16015 -- type. This currently leaves out some restrictions on interface
16016 -- types, namely that the parent type must be java.lang.Object.Typ
16017 -- and that all primitives of the type should be declared
16018 -- abstract. ???
16020 if not Is_Tagged_Type (Typ) or else not Is_Abstract_Type (Typ) then
16021 Error_Pragma_Arg
16022 ("pragma% requires an abstract tagged type", Arg1);
16024 elsif not Has_Discriminants (Typ)
16025 or else Ekind (Etype (First_Discriminant (Typ)))
16026 /= E_Anonymous_Access_Type
16027 or else
16028 not Is_Class_Wide_Type
16029 (Designated_Type (Etype (First_Discriminant (Typ))))
16030 then
16031 Error_Pragma_Arg
16032 ("type must have a class-wide access discriminant", Arg1);
16033 end if;
16034 end Java_Interface;
16036 ----------------
16037 -- Keep_Names --
16038 ----------------
16040 -- pragma Keep_Names ([On => ] LOCAL_NAME);
16042 when Pragma_Keep_Names => Keep_Names : declare
16043 Arg : Node_Id;
16045 begin
16046 GNAT_Pragma;
16047 Check_Arg_Count (1);
16048 Check_Optional_Identifier (Arg1, Name_On);
16049 Check_Arg_Is_Local_Name (Arg1);
16051 Arg := Get_Pragma_Arg (Arg1);
16052 Analyze (Arg);
16054 if Etype (Arg) = Any_Type then
16055 return;
16056 end if;
16058 if not Is_Entity_Name (Arg)
16059 or else Ekind (Entity (Arg)) /= E_Enumeration_Type
16060 then
16061 Error_Pragma_Arg
16062 ("pragma% requires a local enumeration type", Arg1);
16063 end if;
16065 Set_Discard_Names (Entity (Arg), False);
16066 end Keep_Names;
16068 -------------
16069 -- License --
16070 -------------
16072 -- pragma License (RESTRICTED | UNRESTRICTED | GPL | MODIFIED_GPL);
16074 when Pragma_License =>
16075 GNAT_Pragma;
16077 -- Do not analyze pragma any further in CodePeer mode, to avoid
16078 -- extraneous errors in this implementation-dependent pragma,
16079 -- which has a different profile on other compilers.
16081 if CodePeer_Mode then
16082 return;
16083 end if;
16085 Check_Arg_Count (1);
16086 Check_No_Identifiers;
16087 Check_Valid_Configuration_Pragma;
16088 Check_Arg_Is_Identifier (Arg1);
16090 declare
16091 Sind : constant Source_File_Index :=
16092 Source_Index (Current_Sem_Unit);
16094 begin
16095 case Chars (Get_Pragma_Arg (Arg1)) is
16096 when Name_GPL =>
16097 Set_License (Sind, GPL);
16099 when Name_Modified_GPL =>
16100 Set_License (Sind, Modified_GPL);
16102 when Name_Restricted =>
16103 Set_License (Sind, Restricted);
16105 when Name_Unrestricted =>
16106 Set_License (Sind, Unrestricted);
16108 when others =>
16109 Error_Pragma_Arg ("invalid license name", Arg1);
16110 end case;
16111 end;
16113 ---------------
16114 -- Link_With --
16115 ---------------
16117 -- pragma Link_With (string_EXPRESSION {, string_EXPRESSION});
16119 when Pragma_Link_With => Link_With : declare
16120 Arg : Node_Id;
16122 begin
16123 GNAT_Pragma;
16125 if Operating_Mode = Generate_Code
16126 and then In_Extended_Main_Source_Unit (N)
16127 then
16128 Check_At_Least_N_Arguments (1);
16129 Check_No_Identifiers;
16130 Check_Is_In_Decl_Part_Or_Package_Spec;
16131 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
16132 Start_String;
16134 Arg := Arg1;
16135 while Present (Arg) loop
16136 Check_Arg_Is_OK_Static_Expression (Arg, Standard_String);
16138 -- Store argument, converting sequences of spaces to a
16139 -- single null character (this is one of the differences
16140 -- in processing between Link_With and Linker_Options).
16142 Arg_Store : declare
16143 C : constant Char_Code := Get_Char_Code (' ');
16144 S : constant String_Id :=
16145 Strval (Expr_Value_S (Get_Pragma_Arg (Arg)));
16146 L : constant Nat := String_Length (S);
16147 F : Nat := 1;
16149 procedure Skip_Spaces;
16150 -- Advance F past any spaces
16152 -----------------
16153 -- Skip_Spaces --
16154 -----------------
16156 procedure Skip_Spaces is
16157 begin
16158 while F <= L and then Get_String_Char (S, F) = C loop
16159 F := F + 1;
16160 end loop;
16161 end Skip_Spaces;
16163 -- Start of processing for Arg_Store
16165 begin
16166 Skip_Spaces; -- skip leading spaces
16168 -- Loop through characters, changing any embedded
16169 -- sequence of spaces to a single null character (this
16170 -- is how Link_With/Linker_Options differ)
16172 while F <= L loop
16173 if Get_String_Char (S, F) = C then
16174 Skip_Spaces;
16175 exit when F > L;
16176 Store_String_Char (ASCII.NUL);
16178 else
16179 Store_String_Char (Get_String_Char (S, F));
16180 F := F + 1;
16181 end if;
16182 end loop;
16183 end Arg_Store;
16185 Arg := Next (Arg);
16187 if Present (Arg) then
16188 Store_String_Char (ASCII.NUL);
16189 end if;
16190 end loop;
16192 Store_Linker_Option_String (End_String);
16193 end if;
16194 end Link_With;
16196 ------------------
16197 -- Linker_Alias --
16198 ------------------
16200 -- pragma Linker_Alias (
16201 -- [Entity =>] LOCAL_NAME
16202 -- [Target =>] static_string_EXPRESSION);
16204 when Pragma_Linker_Alias =>
16205 GNAT_Pragma;
16206 Check_Arg_Order ((Name_Entity, Name_Target));
16207 Check_Arg_Count (2);
16208 Check_Optional_Identifier (Arg1, Name_Entity);
16209 Check_Optional_Identifier (Arg2, Name_Target);
16210 Check_Arg_Is_Library_Level_Local_Name (Arg1);
16211 Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
16213 -- The only processing required is to link this item on to the
16214 -- list of rep items for the given entity. This is accomplished
16215 -- by the call to Rep_Item_Too_Late (when no error is detected
16216 -- and False is returned).
16218 if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
16219 return;
16220 else
16221 Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
16222 end if;
16224 ------------------------
16225 -- Linker_Constructor --
16226 ------------------------
16228 -- pragma Linker_Constructor (procedure_LOCAL_NAME);
16230 -- Code is shared with Linker_Destructor
16232 -----------------------
16233 -- Linker_Destructor --
16234 -----------------------
16236 -- pragma Linker_Destructor (procedure_LOCAL_NAME);
16238 when Pragma_Linker_Constructor |
16239 Pragma_Linker_Destructor =>
16240 Linker_Constructor : declare
16241 Arg1_X : Node_Id;
16242 Proc : Entity_Id;
16244 begin
16245 GNAT_Pragma;
16246 Check_Arg_Count (1);
16247 Check_No_Identifiers;
16248 Check_Arg_Is_Local_Name (Arg1);
16249 Arg1_X := Get_Pragma_Arg (Arg1);
16250 Analyze (Arg1_X);
16251 Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
16253 if not Is_Library_Level_Entity (Proc) then
16254 Error_Pragma_Arg
16255 ("argument for pragma% must be library level entity", Arg1);
16256 end if;
16258 -- The only processing required is to link this item on to the
16259 -- list of rep items for the given entity. This is accomplished
16260 -- by the call to Rep_Item_Too_Late (when no error is detected
16261 -- and False is returned).
16263 if Rep_Item_Too_Late (Proc, N) then
16264 return;
16265 else
16266 Set_Has_Gigi_Rep_Item (Proc);
16267 end if;
16268 end Linker_Constructor;
16270 --------------------
16271 -- Linker_Options --
16272 --------------------
16274 -- pragma Linker_Options (string_EXPRESSION {, string_EXPRESSION});
16276 when Pragma_Linker_Options => Linker_Options : declare
16277 Arg : Node_Id;
16279 begin
16280 Check_Ada_83_Warning;
16281 Check_No_Identifiers;
16282 Check_Arg_Count (1);
16283 Check_Is_In_Decl_Part_Or_Package_Spec;
16284 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
16285 Start_String (Strval (Expr_Value_S (Get_Pragma_Arg (Arg1))));
16287 Arg := Arg2;
16288 while Present (Arg) loop
16289 Check_Arg_Is_OK_Static_Expression (Arg, Standard_String);
16290 Store_String_Char (ASCII.NUL);
16291 Store_String_Chars
16292 (Strval (Expr_Value_S (Get_Pragma_Arg (Arg))));
16293 Arg := Next (Arg);
16294 end loop;
16296 if Operating_Mode = Generate_Code
16297 and then In_Extended_Main_Source_Unit (N)
16298 then
16299 Store_Linker_Option_String (End_String);
16300 end if;
16301 end Linker_Options;
16303 --------------------
16304 -- Linker_Section --
16305 --------------------
16307 -- pragma Linker_Section (
16308 -- [Entity =>] LOCAL_NAME
16309 -- [Section =>] static_string_EXPRESSION);
16311 when Pragma_Linker_Section => Linker_Section : declare
16312 Arg : Node_Id;
16313 Ent : Entity_Id;
16314 LPE : Node_Id;
16316 begin
16317 GNAT_Pragma;
16318 Check_Arg_Order ((Name_Entity, Name_Section));
16319 Check_Arg_Count (2);
16320 Check_Optional_Identifier (Arg1, Name_Entity);
16321 Check_Optional_Identifier (Arg2, Name_Section);
16322 Check_Arg_Is_Library_Level_Local_Name (Arg1);
16323 Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
16325 -- Check kind of entity
16327 Arg := Get_Pragma_Arg (Arg1);
16328 Ent := Entity (Arg);
16330 case Ekind (Ent) is
16332 -- Objects (constants and variables) and types. For these cases
16333 -- all we need to do is to set the Linker_Section_pragma field,
16334 -- checking that we do not have a duplicate.
16336 when E_Constant | E_Variable | Type_Kind =>
16337 LPE := Linker_Section_Pragma (Ent);
16339 if Present (LPE) then
16340 Error_Msg_Sloc := Sloc (LPE);
16341 Error_Msg_NE
16342 ("Linker_Section already specified for &#", Arg1, Ent);
16343 end if;
16345 Set_Linker_Section_Pragma (Ent, N);
16347 -- Subprograms
16349 when Subprogram_Kind =>
16351 -- Aspect case, entity already set
16353 if From_Aspect_Specification (N) then
16354 Set_Linker_Section_Pragma
16355 (Entity (Corresponding_Aspect (N)), N);
16357 -- Pragma case, we must climb the homonym chain, but skip
16358 -- any for which the linker section is already set.
16360 else
16361 loop
16362 if No (Linker_Section_Pragma (Ent)) then
16363 Set_Linker_Section_Pragma (Ent, N);
16364 end if;
16366 Ent := Homonym (Ent);
16367 exit when No (Ent)
16368 or else Scope (Ent) /= Current_Scope;
16369 end loop;
16370 end if;
16372 -- All other cases are illegal
16374 when others =>
16375 Error_Pragma_Arg
16376 ("pragma% applies only to objects, subprograms, and types",
16377 Arg1);
16378 end case;
16379 end Linker_Section;
16381 ----------
16382 -- List --
16383 ----------
16385 -- pragma List (On | Off)
16387 -- There is nothing to do here, since we did all the processing for
16388 -- this pragma in Par.Prag (so that it works properly even in syntax
16389 -- only mode).
16391 when Pragma_List =>
16392 null;
16394 ---------------
16395 -- Lock_Free --
16396 ---------------
16398 -- pragma Lock_Free [(Boolean_EXPRESSION)];
16400 when Pragma_Lock_Free => Lock_Free : declare
16401 P : constant Node_Id := Parent (N);
16402 Arg : Node_Id;
16403 Ent : Entity_Id;
16404 Val : Boolean;
16406 begin
16407 Check_No_Identifiers;
16408 Check_At_Most_N_Arguments (1);
16410 -- Protected definition case
16412 if Nkind (P) = N_Protected_Definition then
16413 Ent := Defining_Identifier (Parent (P));
16415 -- One argument
16417 if Arg_Count = 1 then
16418 Arg := Get_Pragma_Arg (Arg1);
16419 Val := Is_True (Static_Boolean (Arg));
16421 -- No arguments (expression is considered to be True)
16423 else
16424 Val := True;
16425 end if;
16427 -- Check duplicate pragma before we chain the pragma in the Rep
16428 -- Item chain of Ent.
16430 Check_Duplicate_Pragma (Ent);
16431 Record_Rep_Item (Ent, N);
16432 Set_Uses_Lock_Free (Ent, Val);
16434 -- Anything else is incorrect placement
16436 else
16437 Pragma_Misplaced;
16438 end if;
16439 end Lock_Free;
16441 --------------------
16442 -- Locking_Policy --
16443 --------------------
16445 -- pragma Locking_Policy (policy_IDENTIFIER);
16447 when Pragma_Locking_Policy => declare
16448 subtype LP_Range is Name_Id
16449 range First_Locking_Policy_Name .. Last_Locking_Policy_Name;
16450 LP_Val : LP_Range;
16451 LP : Character;
16453 begin
16454 Check_Ada_83_Warning;
16455 Check_Arg_Count (1);
16456 Check_No_Identifiers;
16457 Check_Arg_Is_Locking_Policy (Arg1);
16458 Check_Valid_Configuration_Pragma;
16459 LP_Val := Chars (Get_Pragma_Arg (Arg1));
16461 case LP_Val is
16462 when Name_Ceiling_Locking =>
16463 LP := 'C';
16464 when Name_Inheritance_Locking =>
16465 LP := 'I';
16466 when Name_Concurrent_Readers_Locking =>
16467 LP := 'R';
16468 end case;
16470 if Locking_Policy /= ' '
16471 and then Locking_Policy /= LP
16472 then
16473 Error_Msg_Sloc := Locking_Policy_Sloc;
16474 Error_Pragma ("locking policy incompatible with policy#");
16476 -- Set new policy, but always preserve System_Location since we
16477 -- like the error message with the run time name.
16479 else
16480 Locking_Policy := LP;
16482 if Locking_Policy_Sloc /= System_Location then
16483 Locking_Policy_Sloc := Loc;
16484 end if;
16485 end if;
16486 end;
16488 -------------------
16489 -- Loop_Optimize --
16490 -------------------
16492 -- pragma Loop_Optimize ( OPTIMIZATION_HINT {, OPTIMIZATION_HINT } );
16494 -- OPTIMIZATION_HINT ::=
16495 -- Ivdep | No_Unroll | Unroll | No_Vector | Vector
16497 when Pragma_Loop_Optimize => Loop_Optimize : declare
16498 Hint : Node_Id;
16500 begin
16501 GNAT_Pragma;
16502 Check_At_Least_N_Arguments (1);
16503 Check_No_Identifiers;
16505 Hint := First (Pragma_Argument_Associations (N));
16506 while Present (Hint) loop
16507 Check_Arg_Is_One_Of (Hint, Name_Ivdep,
16508 Name_No_Unroll,
16509 Name_Unroll,
16510 Name_No_Vector,
16511 Name_Vector);
16512 Next (Hint);
16513 end loop;
16515 Check_Loop_Pragma_Placement;
16516 end Loop_Optimize;
16518 ------------------
16519 -- Loop_Variant --
16520 ------------------
16522 -- pragma Loop_Variant
16523 -- ( LOOP_VARIANT_ITEM {, LOOP_VARIANT_ITEM } );
16525 -- LOOP_VARIANT_ITEM ::= CHANGE_DIRECTION => discrete_EXPRESSION
16527 -- CHANGE_DIRECTION ::= Increases | Decreases
16529 when Pragma_Loop_Variant => Loop_Variant : declare
16530 Variant : Node_Id;
16532 begin
16533 GNAT_Pragma;
16534 Check_At_Least_N_Arguments (1);
16535 Check_Loop_Pragma_Placement;
16537 -- Process all increasing / decreasing expressions
16539 Variant := First (Pragma_Argument_Associations (N));
16540 while Present (Variant) loop
16541 if not Nam_In (Chars (Variant), Name_Decreases,
16542 Name_Increases)
16543 then
16544 Error_Pragma_Arg ("wrong change modifier", Variant);
16545 end if;
16547 Preanalyze_Assert_Expression
16548 (Expression (Variant), Any_Discrete);
16550 Next (Variant);
16551 end loop;
16552 end Loop_Variant;
16554 -----------------------
16555 -- Machine_Attribute --
16556 -----------------------
16558 -- pragma Machine_Attribute (
16559 -- [Entity =>] LOCAL_NAME,
16560 -- [Attribute_Name =>] static_string_EXPRESSION
16561 -- [, [Info =>] static_EXPRESSION] );
16563 when Pragma_Machine_Attribute => Machine_Attribute : declare
16564 Def_Id : Entity_Id;
16566 begin
16567 GNAT_Pragma;
16568 Check_Arg_Order ((Name_Entity, Name_Attribute_Name, Name_Info));
16570 if Arg_Count = 3 then
16571 Check_Optional_Identifier (Arg3, Name_Info);
16572 Check_Arg_Is_OK_Static_Expression (Arg3);
16573 else
16574 Check_Arg_Count (2);
16575 end if;
16577 Check_Optional_Identifier (Arg1, Name_Entity);
16578 Check_Optional_Identifier (Arg2, Name_Attribute_Name);
16579 Check_Arg_Is_Local_Name (Arg1);
16580 Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
16581 Def_Id := Entity (Get_Pragma_Arg (Arg1));
16583 if Is_Access_Type (Def_Id) then
16584 Def_Id := Designated_Type (Def_Id);
16585 end if;
16587 if Rep_Item_Too_Early (Def_Id, N) then
16588 return;
16589 end if;
16591 Def_Id := Underlying_Type (Def_Id);
16593 -- The only processing required is to link this item on to the
16594 -- list of rep items for the given entity. This is accomplished
16595 -- by the call to Rep_Item_Too_Late (when no error is detected
16596 -- and False is returned).
16598 if Rep_Item_Too_Late (Def_Id, N) then
16599 return;
16600 else
16601 Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
16602 end if;
16603 end Machine_Attribute;
16605 ----------
16606 -- Main --
16607 ----------
16609 -- pragma Main
16610 -- (MAIN_OPTION [, MAIN_OPTION]);
16612 -- MAIN_OPTION ::=
16613 -- [STACK_SIZE =>] static_integer_EXPRESSION
16614 -- | [TASK_STACK_SIZE_DEFAULT =>] static_integer_EXPRESSION
16615 -- | [TIME_SLICING_ENABLED =>] static_boolean_EXPRESSION
16617 when Pragma_Main => Main : declare
16618 Args : Args_List (1 .. 3);
16619 Names : constant Name_List (1 .. 3) := (
16620 Name_Stack_Size,
16621 Name_Task_Stack_Size_Default,
16622 Name_Time_Slicing_Enabled);
16624 Nod : Node_Id;
16626 begin
16627 GNAT_Pragma;
16628 Gather_Associations (Names, Args);
16630 for J in 1 .. 2 loop
16631 if Present (Args (J)) then
16632 Check_Arg_Is_OK_Static_Expression (Args (J), Any_Integer);
16633 end if;
16634 end loop;
16636 if Present (Args (3)) then
16637 Check_Arg_Is_OK_Static_Expression (Args (3), Standard_Boolean);
16638 end if;
16640 Nod := Next (N);
16641 while Present (Nod) loop
16642 if Nkind (Nod) = N_Pragma
16643 and then Pragma_Name (Nod) = Name_Main
16644 then
16645 Error_Msg_Name_1 := Pname;
16646 Error_Msg_N ("duplicate pragma% not permitted", Nod);
16647 end if;
16649 Next (Nod);
16650 end loop;
16651 end Main;
16653 ------------------
16654 -- Main_Storage --
16655 ------------------
16657 -- pragma Main_Storage
16658 -- (MAIN_STORAGE_OPTION [, MAIN_STORAGE_OPTION]);
16660 -- MAIN_STORAGE_OPTION ::=
16661 -- [WORKING_STORAGE =>] static_SIMPLE_EXPRESSION
16662 -- | [TOP_GUARD =>] static_SIMPLE_EXPRESSION
16664 when Pragma_Main_Storage => Main_Storage : declare
16665 Args : Args_List (1 .. 2);
16666 Names : constant Name_List (1 .. 2) := (
16667 Name_Working_Storage,
16668 Name_Top_Guard);
16670 Nod : Node_Id;
16672 begin
16673 GNAT_Pragma;
16674 Gather_Associations (Names, Args);
16676 for J in 1 .. 2 loop
16677 if Present (Args (J)) then
16678 Check_Arg_Is_OK_Static_Expression (Args (J), Any_Integer);
16679 end if;
16680 end loop;
16682 Check_In_Main_Program;
16684 Nod := Next (N);
16685 while Present (Nod) loop
16686 if Nkind (Nod) = N_Pragma
16687 and then Pragma_Name (Nod) = Name_Main_Storage
16688 then
16689 Error_Msg_Name_1 := Pname;
16690 Error_Msg_N ("duplicate pragma% not permitted", Nod);
16691 end if;
16693 Next (Nod);
16694 end loop;
16695 end Main_Storage;
16697 -----------------
16698 -- Memory_Size --
16699 -----------------
16701 -- pragma Memory_Size (NUMERIC_LITERAL)
16703 when Pragma_Memory_Size =>
16704 GNAT_Pragma;
16706 -- Memory size is simply ignored
16708 Check_No_Identifiers;
16709 Check_Arg_Count (1);
16710 Check_Arg_Is_Integer_Literal (Arg1);
16712 -------------
16713 -- No_Body --
16714 -------------
16716 -- pragma No_Body;
16718 -- The only correct use of this pragma is on its own in a file, in
16719 -- which case it is specially processed (see Gnat1drv.Check_Bad_Body
16720 -- and Frontend, which use Sinput.L.Source_File_Is_Pragma_No_Body to
16721 -- check for a file containing nothing but a No_Body pragma). If we
16722 -- attempt to process it during normal semantics processing, it means
16723 -- it was misplaced.
16725 when Pragma_No_Body =>
16726 GNAT_Pragma;
16727 Pragma_Misplaced;
16729 -----------------------------
16730 -- No_Elaboration_Code_All --
16731 -----------------------------
16733 -- pragma No_Elaboration_Code_All;
16735 when Pragma_No_Elaboration_Code_All => NECA : declare
16736 begin
16737 GNAT_Pragma;
16738 Check_Valid_Library_Unit_Pragma;
16740 if Nkind (N) = N_Null_Statement then
16741 return;
16742 end if;
16744 -- Must appear for a spec or generic spec
16746 if not Nkind_In (Unit (Cunit (Current_Sem_Unit)),
16747 N_Generic_Package_Declaration,
16748 N_Generic_Subprogram_Declaration,
16749 N_Package_Declaration,
16750 N_Subprogram_Declaration)
16751 then
16752 Error_Pragma
16753 (Fix_Error
16754 ("pragma% can only occur for package "
16755 & "or subprogram spec"));
16756 end if;
16758 -- Set flag in unit table
16760 Set_No_Elab_Code_All (Current_Sem_Unit);
16762 -- Set restriction No_Elaboration_Code if this is the main unit
16764 if Current_Sem_Unit = Main_Unit then
16765 Set_Restriction (No_Elaboration_Code, N);
16766 end if;
16768 -- If we are in the main unit or in an extended main source unit,
16769 -- then we also add it to the configuration restrictions so that
16770 -- it will apply to all units in the extended main source.
16772 if Current_Sem_Unit = Main_Unit
16773 or else In_Extended_Main_Source_Unit (N)
16774 then
16775 Add_To_Config_Boolean_Restrictions (No_Elaboration_Code);
16776 end if;
16778 -- If in main extended unit, activate transitive with test
16780 if In_Extended_Main_Source_Unit (N) then
16781 Opt.No_Elab_Code_All_Pragma := N;
16782 end if;
16783 end NECA;
16785 ---------------
16786 -- No_Inline --
16787 ---------------
16789 -- pragma No_Inline ( NAME {, NAME} );
16791 when Pragma_No_Inline =>
16792 GNAT_Pragma;
16793 Process_Inline (Suppressed);
16795 ---------------
16796 -- No_Return --
16797 ---------------
16799 -- pragma No_Return (procedure_LOCAL_NAME {, procedure_Local_Name});
16801 when Pragma_No_Return => No_Return : declare
16802 Id : Node_Id;
16803 E : Entity_Id;
16804 Found : Boolean;
16805 Arg : Node_Id;
16807 begin
16808 Ada_2005_Pragma;
16809 Check_At_Least_N_Arguments (1);
16811 -- Loop through arguments of pragma
16813 Arg := Arg1;
16814 while Present (Arg) loop
16815 Check_Arg_Is_Local_Name (Arg);
16816 Id := Get_Pragma_Arg (Arg);
16817 Analyze (Id);
16819 if not Is_Entity_Name (Id) then
16820 Error_Pragma_Arg ("entity name required", Arg);
16821 end if;
16823 if Etype (Id) = Any_Type then
16824 raise Pragma_Exit;
16825 end if;
16827 -- Loop to find matching procedures
16829 E := Entity (Id);
16830 Found := False;
16831 while Present (E)
16832 and then Scope (E) = Current_Scope
16833 loop
16834 if Ekind_In (E, E_Procedure, E_Generic_Procedure) then
16835 Set_No_Return (E);
16837 -- Set flag on any alias as well
16839 if Is_Overloadable (E) and then Present (Alias (E)) then
16840 Set_No_Return (Alias (E));
16841 end if;
16843 Found := True;
16844 end if;
16846 exit when From_Aspect_Specification (N);
16847 E := Homonym (E);
16848 end loop;
16850 -- If entity in not in current scope it may be the enclosing
16851 -- suprogram body to which the aspect applies.
16853 if not Found then
16854 if Entity (Id) = Current_Scope
16855 and then From_Aspect_Specification (N)
16856 then
16857 Set_No_Return (Entity (Id));
16858 else
16859 Error_Pragma_Arg ("no procedure& found for pragma%", Arg);
16860 end if;
16861 end if;
16863 Next (Arg);
16864 end loop;
16865 end No_Return;
16867 -----------------
16868 -- No_Run_Time --
16869 -----------------
16871 -- pragma No_Run_Time;
16873 -- Note: this pragma is retained for backwards compatibility. See
16874 -- body of Rtsfind for full details on its handling.
16876 when Pragma_No_Run_Time =>
16877 GNAT_Pragma;
16878 Check_Valid_Configuration_Pragma;
16879 Check_Arg_Count (0);
16881 No_Run_Time_Mode := True;
16882 Configurable_Run_Time_Mode := True;
16884 -- Set Duration to 32 bits if word size is 32
16886 if Ttypes.System_Word_Size = 32 then
16887 Duration_32_Bits_On_Target := True;
16888 end if;
16890 -- Set appropriate restrictions
16892 Set_Restriction (No_Finalization, N);
16893 Set_Restriction (No_Exception_Handlers, N);
16894 Set_Restriction (Max_Tasks, N, 0);
16895 Set_Restriction (No_Tasking, N);
16897 -----------------------
16898 -- No_Tagged_Streams --
16899 -----------------------
16901 -- pragma No_Tagged_Streams;
16902 -- pragma No_Tagged_Streams ([Entity => ]tagged_type_local_NAME);
16904 when Pragma_No_Tagged_Streams => No_Tagged_Strms : declare
16905 E_Id : Node_Id;
16906 E : Entity_Id;
16908 begin
16909 GNAT_Pragma;
16910 Check_At_Most_N_Arguments (1);
16912 -- One argument case
16914 if Arg_Count = 1 then
16915 Check_Optional_Identifier (Arg1, Name_Entity);
16916 Check_Arg_Is_Local_Name (Arg1);
16917 E_Id := Get_Pragma_Arg (Arg1);
16919 if Etype (E_Id) = Any_Type then
16920 return;
16921 end if;
16923 E := Entity (E_Id);
16925 Check_Duplicate_Pragma (E);
16927 if not Is_Tagged_Type (E) or else Is_Derived_Type (E) then
16928 Error_Pragma_Arg
16929 ("argument for pragma% must be root tagged type", Arg1);
16930 end if;
16932 if Rep_Item_Too_Early (E, N)
16933 or else
16934 Rep_Item_Too_Late (E, N)
16935 then
16936 return;
16937 else
16938 Set_No_Tagged_Streams_Pragma (E, N);
16939 end if;
16941 -- Zero argument case
16943 else
16944 Check_Is_In_Decl_Part_Or_Package_Spec;
16945 No_Tagged_Streams := N;
16946 end if;
16947 end No_Tagged_Strms;
16949 ------------------------
16950 -- No_Strict_Aliasing --
16951 ------------------------
16953 -- pragma No_Strict_Aliasing [([Entity =>] type_LOCAL_NAME)];
16955 when Pragma_No_Strict_Aliasing => No_Strict_Aliasing : declare
16956 E_Id : Entity_Id;
16958 begin
16959 GNAT_Pragma;
16960 Check_At_Most_N_Arguments (1);
16962 if Arg_Count = 0 then
16963 Check_Valid_Configuration_Pragma;
16964 Opt.No_Strict_Aliasing := True;
16966 else
16967 Check_Optional_Identifier (Arg2, Name_Entity);
16968 Check_Arg_Is_Local_Name (Arg1);
16969 E_Id := Entity (Get_Pragma_Arg (Arg1));
16971 if E_Id = Any_Type then
16972 return;
16973 elsif No (E_Id) or else not Is_Access_Type (E_Id) then
16974 Error_Pragma_Arg ("pragma% requires access type", Arg1);
16975 end if;
16977 Set_No_Strict_Aliasing (Implementation_Base_Type (E_Id));
16978 end if;
16979 end No_Strict_Aliasing;
16981 -----------------------
16982 -- Normalize_Scalars --
16983 -----------------------
16985 -- pragma Normalize_Scalars;
16987 when Pragma_Normalize_Scalars =>
16988 Check_Ada_83_Warning;
16989 Check_Arg_Count (0);
16990 Check_Valid_Configuration_Pragma;
16992 -- Normalize_Scalars creates false positives in CodePeer, and
16993 -- incorrect negative results in GNATprove mode, so ignore this
16994 -- pragma in these modes.
16996 if not (CodePeer_Mode or GNATprove_Mode) then
16997 Normalize_Scalars := True;
16998 Init_Or_Norm_Scalars := True;
16999 end if;
17001 -----------------
17002 -- Obsolescent --
17003 -----------------
17005 -- pragma Obsolescent;
17007 -- pragma Obsolescent (
17008 -- [Message =>] static_string_EXPRESSION
17009 -- [,[Version =>] Ada_05]]);
17011 -- pragma Obsolescent (
17012 -- [Entity =>] NAME
17013 -- [,[Message =>] static_string_EXPRESSION
17014 -- [,[Version =>] Ada_05]] );
17016 when Pragma_Obsolescent => Obsolescent : declare
17017 Ename : Node_Id;
17018 Decl : Node_Id;
17020 procedure Set_Obsolescent (E : Entity_Id);
17021 -- Given an entity Ent, mark it as obsolescent if appropriate
17023 ---------------------
17024 -- Set_Obsolescent --
17025 ---------------------
17027 procedure Set_Obsolescent (E : Entity_Id) is
17028 Active : Boolean;
17029 Ent : Entity_Id;
17030 S : String_Id;
17032 begin
17033 Active := True;
17034 Ent := E;
17036 -- Entity name was given
17038 if Present (Ename) then
17040 -- If entity name matches, we are fine. Save entity in
17041 -- pragma argument, for ASIS use.
17043 if Chars (Ename) = Chars (Ent) then
17044 Set_Entity (Ename, Ent);
17045 Generate_Reference (Ent, Ename);
17047 -- If entity name does not match, only possibility is an
17048 -- enumeration literal from an enumeration type declaration.
17050 elsif Ekind (Ent) /= E_Enumeration_Type then
17051 Error_Pragma
17052 ("pragma % entity name does not match declaration");
17054 else
17055 Ent := First_Literal (E);
17056 loop
17057 if No (Ent) then
17058 Error_Pragma
17059 ("pragma % entity name does not match any "
17060 & "enumeration literal");
17062 elsif Chars (Ent) = Chars (Ename) then
17063 Set_Entity (Ename, Ent);
17064 Generate_Reference (Ent, Ename);
17065 exit;
17067 else
17068 Ent := Next_Literal (Ent);
17069 end if;
17070 end loop;
17071 end if;
17072 end if;
17074 -- Ent points to entity to be marked
17076 if Arg_Count >= 1 then
17078 -- Deal with static string argument
17080 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
17081 S := Strval (Get_Pragma_Arg (Arg1));
17083 for J in 1 .. String_Length (S) loop
17084 if not In_Character_Range (Get_String_Char (S, J)) then
17085 Error_Pragma_Arg
17086 ("pragma% argument does not allow wide characters",
17087 Arg1);
17088 end if;
17089 end loop;
17091 Obsolescent_Warnings.Append
17092 ((Ent => Ent, Msg => Strval (Get_Pragma_Arg (Arg1))));
17094 -- Check for Ada_05 parameter
17096 if Arg_Count /= 1 then
17097 Check_Arg_Count (2);
17099 declare
17100 Argx : constant Node_Id := Get_Pragma_Arg (Arg2);
17102 begin
17103 Check_Arg_Is_Identifier (Argx);
17105 if Chars (Argx) /= Name_Ada_05 then
17106 Error_Msg_Name_2 := Name_Ada_05;
17107 Error_Pragma_Arg
17108 ("only allowed argument for pragma% is %", Argx);
17109 end if;
17111 if Ada_Version_Explicit < Ada_2005
17112 or else not Warn_On_Ada_2005_Compatibility
17113 then
17114 Active := False;
17115 end if;
17116 end;
17117 end if;
17118 end if;
17120 -- Set flag if pragma active
17122 if Active then
17123 Set_Is_Obsolescent (Ent);
17124 end if;
17126 return;
17127 end Set_Obsolescent;
17129 -- Start of processing for pragma Obsolescent
17131 begin
17132 GNAT_Pragma;
17134 Check_At_Most_N_Arguments (3);
17136 -- See if first argument specifies an entity name
17138 if Arg_Count >= 1
17139 and then
17140 (Chars (Arg1) = Name_Entity
17141 or else
17142 Nkind_In (Get_Pragma_Arg (Arg1), N_Character_Literal,
17143 N_Identifier,
17144 N_Operator_Symbol))
17145 then
17146 Ename := Get_Pragma_Arg (Arg1);
17148 -- Eliminate first argument, so we can share processing
17150 Arg1 := Arg2;
17151 Arg2 := Arg3;
17152 Arg_Count := Arg_Count - 1;
17154 -- No Entity name argument given
17156 else
17157 Ename := Empty;
17158 end if;
17160 if Arg_Count >= 1 then
17161 Check_Optional_Identifier (Arg1, Name_Message);
17163 if Arg_Count = 2 then
17164 Check_Optional_Identifier (Arg2, Name_Version);
17165 end if;
17166 end if;
17168 -- Get immediately preceding declaration
17170 Decl := Prev (N);
17171 while Present (Decl) and then Nkind (Decl) = N_Pragma loop
17172 Prev (Decl);
17173 end loop;
17175 -- Cases where we do not follow anything other than another pragma
17177 if No (Decl) then
17179 -- First case: library level compilation unit declaration with
17180 -- the pragma immediately following the declaration.
17182 if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
17183 Set_Obsolescent
17184 (Defining_Entity (Unit (Parent (Parent (N)))));
17185 return;
17187 -- Case 2: library unit placement for package
17189 else
17190 declare
17191 Ent : constant Entity_Id := Find_Lib_Unit_Name;
17192 begin
17193 if Is_Package_Or_Generic_Package (Ent) then
17194 Set_Obsolescent (Ent);
17195 return;
17196 end if;
17197 end;
17198 end if;
17200 -- Cases where we must follow a declaration
17202 else
17203 if Nkind (Decl) not in N_Declaration
17204 and then Nkind (Decl) not in N_Later_Decl_Item
17205 and then Nkind (Decl) not in N_Generic_Declaration
17206 and then Nkind (Decl) not in N_Renaming_Declaration
17207 then
17208 Error_Pragma
17209 ("pragma% misplaced, "
17210 & "must immediately follow a declaration");
17212 else
17213 Set_Obsolescent (Defining_Entity (Decl));
17214 return;
17215 end if;
17216 end if;
17217 end Obsolescent;
17219 --------------
17220 -- Optimize --
17221 --------------
17223 -- pragma Optimize (Time | Space | Off);
17225 -- The actual check for optimize is done in Gigi. Note that this
17226 -- pragma does not actually change the optimization setting, it
17227 -- simply checks that it is consistent with the pragma.
17229 when Pragma_Optimize =>
17230 Check_No_Identifiers;
17231 Check_Arg_Count (1);
17232 Check_Arg_Is_One_Of (Arg1, Name_Time, Name_Space, Name_Off);
17234 ------------------------
17235 -- Optimize_Alignment --
17236 ------------------------
17238 -- pragma Optimize_Alignment (Time | Space | Off);
17240 when Pragma_Optimize_Alignment => Optimize_Alignment : begin
17241 GNAT_Pragma;
17242 Check_No_Identifiers;
17243 Check_Arg_Count (1);
17244 Check_Valid_Configuration_Pragma;
17246 declare
17247 Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
17248 begin
17249 case Nam is
17250 when Name_Time =>
17251 Opt.Optimize_Alignment := 'T';
17252 when Name_Space =>
17253 Opt.Optimize_Alignment := 'S';
17254 when Name_Off =>
17255 Opt.Optimize_Alignment := 'O';
17256 when others =>
17257 Error_Pragma_Arg ("invalid argument for pragma%", Arg1);
17258 end case;
17259 end;
17261 -- Set indication that mode is set locally. If we are in fact in a
17262 -- configuration pragma file, this setting is harmless since the
17263 -- switch will get reset anyway at the start of each unit.
17265 Optimize_Alignment_Local := True;
17266 end Optimize_Alignment;
17268 -------------
17269 -- Ordered --
17270 -------------
17272 -- pragma Ordered (first_enumeration_subtype_LOCAL_NAME);
17274 when Pragma_Ordered => Ordered : declare
17275 Assoc : constant Node_Id := Arg1;
17276 Type_Id : Node_Id;
17277 Typ : Entity_Id;
17279 begin
17280 GNAT_Pragma;
17281 Check_No_Identifiers;
17282 Check_Arg_Count (1);
17283 Check_Arg_Is_Local_Name (Arg1);
17285 Type_Id := Get_Pragma_Arg (Assoc);
17286 Find_Type (Type_Id);
17287 Typ := Entity (Type_Id);
17289 if Typ = Any_Type then
17290 return;
17291 else
17292 Typ := Underlying_Type (Typ);
17293 end if;
17295 if not Is_Enumeration_Type (Typ) then
17296 Error_Pragma ("pragma% must specify enumeration type");
17297 end if;
17299 Check_First_Subtype (Arg1);
17300 Set_Has_Pragma_Ordered (Base_Type (Typ));
17301 end Ordered;
17303 -------------------
17304 -- Overflow_Mode --
17305 -------------------
17307 -- pragma Overflow_Mode
17308 -- ([General => ] MODE [, [Assertions => ] MODE]);
17310 -- MODE := STRICT | MINIMIZED | ELIMINATED
17312 -- Note: ELIMINATED is allowed only if Long_Long_Integer'Size is 64
17313 -- since System.Bignums makes this assumption. This is true of nearly
17314 -- all (all?) targets.
17316 when Pragma_Overflow_Mode => Overflow_Mode : declare
17317 function Get_Overflow_Mode
17318 (Name : Name_Id;
17319 Arg : Node_Id) return Overflow_Mode_Type;
17320 -- Function to process one pragma argument, Arg. If an identifier
17321 -- is present, it must be Name. Mode type is returned if a valid
17322 -- argument exists, otherwise an error is signalled.
17324 -----------------------
17325 -- Get_Overflow_Mode --
17326 -----------------------
17328 function Get_Overflow_Mode
17329 (Name : Name_Id;
17330 Arg : Node_Id) return Overflow_Mode_Type
17332 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
17334 begin
17335 Check_Optional_Identifier (Arg, Name);
17336 Check_Arg_Is_Identifier (Argx);
17338 if Chars (Argx) = Name_Strict then
17339 return Strict;
17341 elsif Chars (Argx) = Name_Minimized then
17342 return Minimized;
17344 elsif Chars (Argx) = Name_Eliminated then
17345 if Ttypes.Standard_Long_Long_Integer_Size /= 64 then
17346 Error_Pragma_Arg
17347 ("Eliminated not implemented on this target", Argx);
17348 else
17349 return Eliminated;
17350 end if;
17352 else
17353 Error_Pragma_Arg ("invalid argument for pragma%", Argx);
17354 end if;
17355 end Get_Overflow_Mode;
17357 -- Start of processing for Overflow_Mode
17359 begin
17360 GNAT_Pragma;
17361 Check_At_Least_N_Arguments (1);
17362 Check_At_Most_N_Arguments (2);
17364 -- Process first argument
17366 Scope_Suppress.Overflow_Mode_General :=
17367 Get_Overflow_Mode (Name_General, Arg1);
17369 -- Case of only one argument
17371 if Arg_Count = 1 then
17372 Scope_Suppress.Overflow_Mode_Assertions :=
17373 Scope_Suppress.Overflow_Mode_General;
17375 -- Case of two arguments present
17377 else
17378 Scope_Suppress.Overflow_Mode_Assertions :=
17379 Get_Overflow_Mode (Name_Assertions, Arg2);
17380 end if;
17381 end Overflow_Mode;
17383 --------------------------
17384 -- Overriding Renamings --
17385 --------------------------
17387 -- pragma Overriding_Renamings;
17389 when Pragma_Overriding_Renamings =>
17390 GNAT_Pragma;
17391 Check_Arg_Count (0);
17392 Check_Valid_Configuration_Pragma;
17393 Overriding_Renamings := True;
17395 ----------
17396 -- Pack --
17397 ----------
17399 -- pragma Pack (first_subtype_LOCAL_NAME);
17401 when Pragma_Pack => Pack : declare
17402 Assoc : constant Node_Id := Arg1;
17403 Type_Id : Node_Id;
17404 Typ : Entity_Id;
17405 Ctyp : Entity_Id;
17406 Ignore : Boolean := False;
17408 begin
17409 Check_No_Identifiers;
17410 Check_Arg_Count (1);
17411 Check_Arg_Is_Local_Name (Arg1);
17412 Type_Id := Get_Pragma_Arg (Assoc);
17414 if not Is_Entity_Name (Type_Id)
17415 or else not Is_Type (Entity (Type_Id))
17416 then
17417 Error_Pragma_Arg
17418 ("argument for pragma% must be type or subtype", Arg1);
17419 end if;
17421 Find_Type (Type_Id);
17422 Typ := Entity (Type_Id);
17424 if Typ = Any_Type
17425 or else Rep_Item_Too_Early (Typ, N)
17426 then
17427 return;
17428 else
17429 Typ := Underlying_Type (Typ);
17430 end if;
17432 if not Is_Array_Type (Typ) and then not Is_Record_Type (Typ) then
17433 Error_Pragma ("pragma% must specify array or record type");
17434 end if;
17436 Check_First_Subtype (Arg1);
17437 Check_Duplicate_Pragma (Typ);
17439 -- Array type
17441 if Is_Array_Type (Typ) then
17442 Ctyp := Component_Type (Typ);
17444 -- Ignore pack that does nothing
17446 if Known_Static_Esize (Ctyp)
17447 and then Known_Static_RM_Size (Ctyp)
17448 and then Esize (Ctyp) = RM_Size (Ctyp)
17449 and then Addressable (Esize (Ctyp))
17450 then
17451 Ignore := True;
17452 end if;
17454 -- Process OK pragma Pack. Note that if there is a separate
17455 -- component clause present, the Pack will be cancelled. This
17456 -- processing is in Freeze.
17458 if not Rep_Item_Too_Late (Typ, N) then
17460 -- In CodePeer mode, we do not need complex front-end
17461 -- expansions related to pragma Pack, so disable handling
17462 -- of pragma Pack.
17464 if CodePeer_Mode then
17465 null;
17467 -- Don't attempt any packing for VM targets. We possibly
17468 -- could deal with some cases of array bit-packing, but we
17469 -- don't bother, since this is not a typical kind of
17470 -- representation in the VM context anyway (and would not
17471 -- for example work nicely with the debugger).
17473 elsif VM_Target /= No_VM then
17474 if not GNAT_Mode then
17475 Error_Pragma
17476 ("??pragma% ignored in this configuration");
17477 end if;
17479 -- Normal case where we do the pack action
17481 else
17482 if not Ignore then
17483 Set_Is_Packed (Base_Type (Typ));
17484 Set_Has_Non_Standard_Rep (Base_Type (Typ));
17485 end if;
17487 Set_Has_Pragma_Pack (Base_Type (Typ));
17488 end if;
17489 end if;
17491 -- For record types, the pack is always effective
17493 else pragma Assert (Is_Record_Type (Typ));
17494 if not Rep_Item_Too_Late (Typ, N) then
17496 -- Ignore pack request with warning in VM mode (skip warning
17497 -- if we are compiling GNAT run time library).
17499 if VM_Target /= No_VM then
17500 if not GNAT_Mode then
17501 Error_Pragma
17502 ("??pragma% ignored in this configuration");
17503 end if;
17505 -- Normal case of pack request active
17507 else
17508 Set_Is_Packed (Base_Type (Typ));
17509 Set_Has_Pragma_Pack (Base_Type (Typ));
17510 Set_Has_Non_Standard_Rep (Base_Type (Typ));
17511 end if;
17512 end if;
17513 end if;
17514 end Pack;
17516 ----------
17517 -- Page --
17518 ----------
17520 -- pragma Page;
17522 -- There is nothing to do here, since we did all the processing for
17523 -- this pragma in Par.Prag (so that it works properly even in syntax
17524 -- only mode).
17526 when Pragma_Page =>
17527 null;
17529 -------------
17530 -- Part_Of --
17531 -------------
17533 -- pragma Part_Of (ABSTRACT_STATE);
17535 -- ABSTRACT_STATE ::= NAME
17537 when Pragma_Part_Of => Part_Of : declare
17538 procedure Propagate_Part_Of
17539 (Pack_Id : Entity_Id;
17540 State_Id : Entity_Id;
17541 Instance : Node_Id);
17542 -- Propagate the Part_Of indicator to all abstract states and
17543 -- variables declared in the visible state space of a package
17544 -- denoted by Pack_Id. State_Id is the encapsulating state.
17545 -- Instance is the package instantiation node.
17547 -----------------------
17548 -- Propagate_Part_Of --
17549 -----------------------
17551 procedure Propagate_Part_Of
17552 (Pack_Id : Entity_Id;
17553 State_Id : Entity_Id;
17554 Instance : Node_Id)
17556 Has_Item : Boolean := False;
17557 -- Flag set when the visible state space contains at least one
17558 -- abstract state or variable.
17560 procedure Propagate_Part_Of (Pack_Id : Entity_Id);
17561 -- Propagate the Part_Of indicator to all abstract states and
17562 -- variables declared in the visible state space of a package
17563 -- denoted by Pack_Id.
17565 -----------------------
17566 -- Propagate_Part_Of --
17567 -----------------------
17569 procedure Propagate_Part_Of (Pack_Id : Entity_Id) is
17570 Item_Id : Entity_Id;
17572 begin
17573 -- Traverse the entity chain of the package and set relevant
17574 -- attributes of abstract states and variables declared in
17575 -- the visible state space of the package.
17577 Item_Id := First_Entity (Pack_Id);
17578 while Present (Item_Id)
17579 and then not In_Private_Part (Item_Id)
17580 loop
17581 -- Do not consider internally generated items
17583 if not Comes_From_Source (Item_Id) then
17584 null;
17586 -- The Part_Of indicator turns an abstract state or
17587 -- variable into a constituent of the encapsulating
17588 -- state.
17590 elsif Ekind_In (Item_Id, E_Abstract_State,
17591 E_Variable)
17592 then
17593 Has_Item := True;
17595 Append_Elmt (Item_Id, Part_Of_Constituents (State_Id));
17596 Set_Encapsulating_State (Item_Id, State_Id);
17598 -- Recursively handle nested packages and instantiations
17600 elsif Ekind (Item_Id) = E_Package then
17601 Propagate_Part_Of (Item_Id);
17602 end if;
17604 Next_Entity (Item_Id);
17605 end loop;
17606 end Propagate_Part_Of;
17608 -- Start of processing for Propagate_Part_Of
17610 begin
17611 Propagate_Part_Of (Pack_Id);
17613 -- Detect a package instantiation that is subject to a Part_Of
17614 -- indicator, but has no visible state.
17616 if not Has_Item then
17617 SPARK_Msg_NE
17618 ("package instantiation & has Part_Of indicator but "
17619 & "lacks visible state", Instance, Pack_Id);
17620 end if;
17621 end Propagate_Part_Of;
17623 -- Local variables
17625 Item_Id : Entity_Id;
17626 Legal : Boolean;
17627 State : Node_Id;
17628 State_Id : Entity_Id;
17629 Stmt : Node_Id;
17631 -- Start of processing for Part_Of
17633 begin
17634 GNAT_Pragma;
17635 Check_No_Identifiers;
17636 Check_Arg_Count (1);
17638 -- Ensure the proper placement of the pragma. Part_Of must appear
17639 -- on a variable declaration or a package instantiation.
17641 Stmt := Prev (N);
17642 while Present (Stmt) loop
17644 -- Skip prior pragmas, but check for duplicates
17646 if Nkind (Stmt) = N_Pragma then
17647 if Pragma_Name (Stmt) = Pname then
17648 Error_Msg_Name_1 := Pname;
17649 Error_Msg_Sloc := Sloc (Stmt);
17650 Error_Msg_N ("pragma% duplicates pragma declared#", N);
17651 end if;
17653 -- Skip internally generated code
17655 elsif not Comes_From_Source (Stmt) then
17656 null;
17658 -- The pragma applies to an object declaration (possibly a
17659 -- variable) or a package instantiation. Stop the traversal
17660 -- and continue the analysis.
17662 elsif Nkind_In (Stmt, N_Object_Declaration,
17663 N_Package_Instantiation)
17664 then
17665 exit;
17667 -- The pragma does not apply to a legal construct, issue an
17668 -- error and stop the analysis.
17670 else
17671 Pragma_Misplaced;
17672 return;
17673 end if;
17675 Stmt := Prev (Stmt);
17676 end loop;
17678 -- When the context is an object declaration, ensure that we are
17679 -- dealing with a variable.
17681 if Nkind (Stmt) = N_Object_Declaration
17682 and then Ekind (Defining_Entity (Stmt)) /= E_Variable
17683 then
17684 SPARK_Msg_N ("indicator Part_Of must apply to a variable", N);
17685 return;
17686 end if;
17688 -- Extract the entity of the related object declaration or package
17689 -- instantiation. In the case of the instantiation, use the entity
17690 -- of the instance spec.
17692 if Nkind (Stmt) = N_Package_Instantiation then
17693 Stmt := Instance_Spec (Stmt);
17694 end if;
17696 Item_Id := Defining_Entity (Stmt);
17697 State := Get_Pragma_Arg (Arg1);
17699 -- Detect any discrepancies between the placement of the object
17700 -- or package instantiation with respect to state space and the
17701 -- encapsulating state.
17703 Analyze_Part_Of
17704 (Item_Id => Item_Id,
17705 State => State,
17706 Indic => N,
17707 Legal => Legal);
17709 if Legal then
17710 State_Id := Entity (State);
17712 -- Add the pragma to the contract of the item. This aids with
17713 -- the detection of a missing but required Part_Of indicator.
17715 Add_Contract_Item (N, Item_Id);
17717 -- The Part_Of indicator turns a variable into a constituent
17718 -- of the encapsulating state.
17720 if Ekind (Item_Id) = E_Variable then
17721 Append_Elmt (Item_Id, Part_Of_Constituents (State_Id));
17722 Set_Encapsulating_State (Item_Id, State_Id);
17724 -- Propagate the Part_Of indicator to the visible state space
17725 -- of the package instantiation.
17727 else
17728 Propagate_Part_Of
17729 (Pack_Id => Item_Id,
17730 State_Id => State_Id,
17731 Instance => Stmt);
17732 end if;
17733 end if;
17734 end Part_Of;
17736 ----------------------------------
17737 -- Partition_Elaboration_Policy --
17738 ----------------------------------
17740 -- pragma Partition_Elaboration_Policy (policy_IDENTIFIER);
17742 when Pragma_Partition_Elaboration_Policy => declare
17743 subtype PEP_Range is Name_Id
17744 range First_Partition_Elaboration_Policy_Name
17745 .. Last_Partition_Elaboration_Policy_Name;
17746 PEP_Val : PEP_Range;
17747 PEP : Character;
17749 begin
17750 Ada_2005_Pragma;
17751 Check_Arg_Count (1);
17752 Check_No_Identifiers;
17753 Check_Arg_Is_Partition_Elaboration_Policy (Arg1);
17754 Check_Valid_Configuration_Pragma;
17755 PEP_Val := Chars (Get_Pragma_Arg (Arg1));
17757 case PEP_Val is
17758 when Name_Concurrent =>
17759 PEP := 'C';
17760 when Name_Sequential =>
17761 PEP := 'S';
17762 end case;
17764 if Partition_Elaboration_Policy /= ' '
17765 and then Partition_Elaboration_Policy /= PEP
17766 then
17767 Error_Msg_Sloc := Partition_Elaboration_Policy_Sloc;
17768 Error_Pragma
17769 ("partition elaboration policy incompatible with policy#");
17771 -- Set new policy, but always preserve System_Location since we
17772 -- like the error message with the run time name.
17774 else
17775 Partition_Elaboration_Policy := PEP;
17777 if Partition_Elaboration_Policy_Sloc /= System_Location then
17778 Partition_Elaboration_Policy_Sloc := Loc;
17779 end if;
17780 end if;
17781 end;
17783 -------------
17784 -- Passive --
17785 -------------
17787 -- pragma Passive [(PASSIVE_FORM)];
17789 -- PASSIVE_FORM ::= Semaphore | No
17791 when Pragma_Passive =>
17792 GNAT_Pragma;
17794 if Nkind (Parent (N)) /= N_Task_Definition then
17795 Error_Pragma ("pragma% must be within task definition");
17796 end if;
17798 if Arg_Count /= 0 then
17799 Check_Arg_Count (1);
17800 Check_Arg_Is_One_Of (Arg1, Name_Semaphore, Name_No);
17801 end if;
17803 ----------------------------------
17804 -- Preelaborable_Initialization --
17805 ----------------------------------
17807 -- pragma Preelaborable_Initialization (DIRECT_NAME);
17809 when Pragma_Preelaborable_Initialization => Preelab_Init : declare
17810 Ent : Entity_Id;
17812 begin
17813 Ada_2005_Pragma;
17814 Check_Arg_Count (1);
17815 Check_No_Identifiers;
17816 Check_Arg_Is_Identifier (Arg1);
17817 Check_Arg_Is_Local_Name (Arg1);
17818 Check_First_Subtype (Arg1);
17819 Ent := Entity (Get_Pragma_Arg (Arg1));
17821 -- The pragma may come from an aspect on a private declaration,
17822 -- even if the freeze point at which this is analyzed in the
17823 -- private part after the full view.
17825 if Has_Private_Declaration (Ent)
17826 and then From_Aspect_Specification (N)
17827 then
17828 null;
17830 elsif Is_Private_Type (Ent)
17831 or else Is_Protected_Type (Ent)
17832 or else (Is_Generic_Type (Ent) and then Is_Derived_Type (Ent))
17833 then
17834 null;
17836 else
17837 Error_Pragma_Arg
17838 ("pragma % can only be applied to private, formal derived or "
17839 & "protected type",
17840 Arg1);
17841 end if;
17843 -- Give an error if the pragma is applied to a protected type that
17844 -- does not qualify (due to having entries, or due to components
17845 -- that do not qualify).
17847 if Is_Protected_Type (Ent)
17848 and then not Has_Preelaborable_Initialization (Ent)
17849 then
17850 Error_Msg_N
17851 ("protected type & does not have preelaborable "
17852 & "initialization", Ent);
17854 -- Otherwise mark the type as definitely having preelaborable
17855 -- initialization.
17857 else
17858 Set_Known_To_Have_Preelab_Init (Ent);
17859 end if;
17861 if Has_Pragma_Preelab_Init (Ent)
17862 and then Warn_On_Redundant_Constructs
17863 then
17864 Error_Pragma ("?r?duplicate pragma%!");
17865 else
17866 Set_Has_Pragma_Preelab_Init (Ent);
17867 end if;
17868 end Preelab_Init;
17870 --------------------
17871 -- Persistent_BSS --
17872 --------------------
17874 -- pragma Persistent_BSS [(object_NAME)];
17876 when Pragma_Persistent_BSS => Persistent_BSS : declare
17877 Decl : Node_Id;
17878 Ent : Entity_Id;
17879 Prag : Node_Id;
17881 begin
17882 GNAT_Pragma;
17883 Check_At_Most_N_Arguments (1);
17885 -- Case of application to specific object (one argument)
17887 if Arg_Count = 1 then
17888 Check_Arg_Is_Library_Level_Local_Name (Arg1);
17890 if not Is_Entity_Name (Get_Pragma_Arg (Arg1))
17891 or else not
17892 Ekind_In (Entity (Get_Pragma_Arg (Arg1)), E_Variable,
17893 E_Constant)
17894 then
17895 Error_Pragma_Arg ("pragma% only applies to objects", Arg1);
17896 end if;
17898 Ent := Entity (Get_Pragma_Arg (Arg1));
17899 Decl := Parent (Ent);
17901 -- Check for duplication before inserting in list of
17902 -- representation items.
17904 Check_Duplicate_Pragma (Ent);
17906 if Rep_Item_Too_Late (Ent, N) then
17907 return;
17908 end if;
17910 if Present (Expression (Decl)) then
17911 Error_Pragma_Arg
17912 ("object for pragma% cannot have initialization", Arg1);
17913 end if;
17915 if not Is_Potentially_Persistent_Type (Etype (Ent)) then
17916 Error_Pragma_Arg
17917 ("object type for pragma% is not potentially persistent",
17918 Arg1);
17919 end if;
17921 Prag :=
17922 Make_Linker_Section_Pragma
17923 (Ent, Sloc (N), ".persistent.bss");
17924 Insert_After (N, Prag);
17925 Analyze (Prag);
17927 -- Case of use as configuration pragma with no arguments
17929 else
17930 Check_Valid_Configuration_Pragma;
17931 Persistent_BSS_Mode := True;
17932 end if;
17933 end Persistent_BSS;
17935 -------------
17936 -- Polling --
17937 -------------
17939 -- pragma Polling (ON | OFF);
17941 when Pragma_Polling =>
17942 GNAT_Pragma;
17943 Check_Arg_Count (1);
17944 Check_No_Identifiers;
17945 Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
17946 Polling_Required := (Chars (Get_Pragma_Arg (Arg1)) = Name_On);
17948 ------------------
17949 -- Post[_Class] --
17950 ------------------
17952 -- pragma Post (Boolean_EXPRESSION);
17953 -- pragma Post_Class (Boolean_EXPRESSION);
17955 when Pragma_Post | Pragma_Post_Class => Post : declare
17956 PC_Pragma : Node_Id;
17958 begin
17959 GNAT_Pragma;
17960 Check_Arg_Count (1);
17961 Check_No_Identifiers;
17962 Check_Pre_Post;
17964 -- Rewrite Post[_Class] pragma as Postcondition pragma setting the
17965 -- flag Class_Present to True for the Post_Class case.
17967 Set_Class_Present (N, Prag_Id = Pragma_Post_Class);
17968 PC_Pragma := New_Copy (N);
17969 Set_Pragma_Identifier
17970 (PC_Pragma, Make_Identifier (Loc, Name_Postcondition));
17971 Rewrite (N, PC_Pragma);
17972 Set_Analyzed (N, False);
17973 Analyze (N);
17974 end Post;
17976 -------------------
17977 -- Postcondition --
17978 -------------------
17980 -- pragma Postcondition ([Check =>] Boolean_EXPRESSION
17981 -- [,[Message =>] String_EXPRESSION]);
17983 when Pragma_Postcondition => Postcondition : declare
17984 In_Body : Boolean;
17986 begin
17987 GNAT_Pragma;
17988 Check_At_Least_N_Arguments (1);
17989 Check_At_Most_N_Arguments (2);
17990 Check_Optional_Identifier (Arg1, Name_Check);
17992 -- Verify the proper placement of the pragma. The remainder of the
17993 -- processing is found in Sem_Ch6/Sem_Ch7.
17995 Check_Precondition_Postcondition (In_Body);
17997 -- When the pragma is a source construct appearing inside a body,
17998 -- preanalyze the boolean_expression to detect illegal forward
17999 -- references:
18001 -- procedure P is
18002 -- pragma Postcondition (X'Old ...);
18003 -- X : ...
18005 if Comes_From_Source (N) and then In_Body then
18006 Preanalyze_Spec_Expression (Expression (Arg1), Any_Boolean);
18007 end if;
18008 end Postcondition;
18010 -----------------
18011 -- Pre[_Class] --
18012 -----------------
18014 -- pragma Pre (Boolean_EXPRESSION);
18015 -- pragma Pre_Class (Boolean_EXPRESSION);
18017 when Pragma_Pre | Pragma_Pre_Class => Pre : declare
18018 PC_Pragma : Node_Id;
18020 begin
18021 GNAT_Pragma;
18022 Check_Arg_Count (1);
18023 Check_No_Identifiers;
18024 Check_Pre_Post;
18026 -- Rewrite Pre[_Class] pragma as Precondition pragma setting the
18027 -- flag Class_Present to True for the Pre_Class case.
18029 Set_Class_Present (N, Prag_Id = Pragma_Pre_Class);
18030 PC_Pragma := New_Copy (N);
18031 Set_Pragma_Identifier
18032 (PC_Pragma, Make_Identifier (Loc, Name_Precondition));
18033 Rewrite (N, PC_Pragma);
18034 Set_Analyzed (N, False);
18035 Analyze (N);
18036 end Pre;
18038 ------------------
18039 -- Precondition --
18040 ------------------
18042 -- pragma Precondition ([Check =>] Boolean_EXPRESSION
18043 -- [,[Message =>] String_EXPRESSION]);
18045 when Pragma_Precondition => Precondition : declare
18046 In_Body : Boolean;
18048 begin
18049 GNAT_Pragma;
18050 Check_At_Least_N_Arguments (1);
18051 Check_At_Most_N_Arguments (2);
18052 Check_Optional_Identifier (Arg1, Name_Check);
18053 Check_Precondition_Postcondition (In_Body);
18055 -- If in spec, nothing more to do. If in body, then we convert
18056 -- the pragma to an equivalent pragma Check. That works fine since
18057 -- pragma Check will analyze the condition in the proper context.
18059 -- The form of the pragma Check is either:
18061 -- pragma Check (Precondition, cond [, msg])
18062 -- or
18063 -- pragma Check (Pre, cond [, msg])
18065 -- We use the Pre form if this pragma derived from a Pre aspect.
18066 -- This is needed to make sure that the right set of Policy
18067 -- pragmas are checked.
18069 if In_Body then
18071 -- Rewrite as Check pragma
18073 Rewrite (N,
18074 Make_Pragma (Loc,
18075 Chars => Name_Check,
18076 Pragma_Argument_Associations => New_List (
18077 Make_Pragma_Argument_Association (Loc,
18078 Expression => Make_Identifier (Loc, Pname)),
18080 Make_Pragma_Argument_Association (Sloc (Arg1),
18081 Expression =>
18082 Relocate_Node (Get_Pragma_Arg (Arg1))))));
18084 if Arg_Count = 2 then
18085 Append_To (Pragma_Argument_Associations (N),
18086 Make_Pragma_Argument_Association (Sloc (Arg2),
18087 Expression =>
18088 Relocate_Node (Get_Pragma_Arg (Arg2))));
18089 end if;
18091 Analyze (N);
18092 end if;
18093 end Precondition;
18095 ---------------
18096 -- Predicate --
18097 ---------------
18099 -- pragma Predicate
18100 -- ([Entity =>] type_LOCAL_NAME,
18101 -- [Check =>] boolean_EXPRESSION);
18103 when Pragma_Predicate => Predicate : declare
18104 Type_Id : Node_Id;
18105 Typ : Entity_Id;
18106 Discard : Boolean;
18108 begin
18109 GNAT_Pragma;
18110 Check_Arg_Count (2);
18111 Check_Optional_Identifier (Arg1, Name_Entity);
18112 Check_Optional_Identifier (Arg2, Name_Check);
18114 Check_Arg_Is_Local_Name (Arg1);
18116 Type_Id := Get_Pragma_Arg (Arg1);
18117 Find_Type (Type_Id);
18118 Typ := Entity (Type_Id);
18120 if Typ = Any_Type then
18121 return;
18122 end if;
18124 -- The remaining processing is simply to link the pragma on to
18125 -- the rep item chain, for processing when the type is frozen.
18126 -- This is accomplished by a call to Rep_Item_Too_Late. We also
18127 -- mark the type as having predicates.
18129 Set_Has_Predicates (Typ);
18130 Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
18131 end Predicate;
18133 ------------------
18134 -- Preelaborate --
18135 ------------------
18137 -- pragma Preelaborate [(library_unit_NAME)];
18139 -- Set the flag Is_Preelaborated of program unit name entity
18141 when Pragma_Preelaborate => Preelaborate : declare
18142 Pa : constant Node_Id := Parent (N);
18143 Pk : constant Node_Kind := Nkind (Pa);
18144 Ent : Entity_Id;
18146 begin
18147 Check_Ada_83_Warning;
18148 Check_Valid_Library_Unit_Pragma;
18150 if Nkind (N) = N_Null_Statement then
18151 return;
18152 end if;
18154 Ent := Find_Lib_Unit_Name;
18155 Check_Duplicate_Pragma (Ent);
18157 -- This filters out pragmas inside generic parents that show up
18158 -- inside instantiations. Pragmas that come from aspects in the
18159 -- unit are not ignored.
18161 if Present (Ent) then
18162 if Pk = N_Package_Specification
18163 and then Present (Generic_Parent (Pa))
18164 and then not From_Aspect_Specification (N)
18165 then
18166 null;
18168 else
18169 if not Debug_Flag_U then
18170 Set_Is_Preelaborated (Ent);
18171 Set_Suppress_Elaboration_Warnings (Ent);
18172 end if;
18173 end if;
18174 end if;
18175 end Preelaborate;
18177 -------------------------------
18178 -- Prefix_Exception_Messages --
18179 -------------------------------
18181 -- pragma Prefix_Exception_Messages;
18183 when Pragma_Prefix_Exception_Messages =>
18184 GNAT_Pragma;
18185 Check_Valid_Configuration_Pragma;
18186 Check_Arg_Count (0);
18187 Prefix_Exception_Messages := True;
18189 --------------
18190 -- Priority --
18191 --------------
18193 -- pragma Priority (EXPRESSION);
18195 when Pragma_Priority => Priority : declare
18196 P : constant Node_Id := Parent (N);
18197 Arg : Node_Id;
18198 Ent : Entity_Id;
18200 begin
18201 Check_No_Identifiers;
18202 Check_Arg_Count (1);
18204 -- Subprogram case
18206 if Nkind (P) = N_Subprogram_Body then
18207 Check_In_Main_Program;
18209 Ent := Defining_Unit_Name (Specification (P));
18211 if Nkind (Ent) = N_Defining_Program_Unit_Name then
18212 Ent := Defining_Identifier (Ent);
18213 end if;
18215 Arg := Get_Pragma_Arg (Arg1);
18216 Analyze_And_Resolve (Arg, Standard_Integer);
18218 -- Must be static
18220 if not Is_OK_Static_Expression (Arg) then
18221 Flag_Non_Static_Expr
18222 ("main subprogram priority is not static!", Arg);
18223 raise Pragma_Exit;
18225 -- If constraint error, then we already signalled an error
18227 elsif Raises_Constraint_Error (Arg) then
18228 null;
18230 -- Otherwise check in range except if Relaxed_RM_Semantics
18231 -- where we ignore the value if out of range.
18233 else
18234 declare
18235 Val : constant Uint := Expr_Value (Arg);
18236 begin
18237 if not Relaxed_RM_Semantics
18238 and then
18239 (Val < 0
18240 or else Val > Expr_Value (Expression
18241 (Parent (RTE (RE_Max_Priority)))))
18242 then
18243 Error_Pragma_Arg
18244 ("main subprogram priority is out of range", Arg1);
18245 else
18246 Set_Main_Priority
18247 (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
18248 end if;
18249 end;
18250 end if;
18252 -- Load an arbitrary entity from System.Tasking.Stages or
18253 -- System.Tasking.Restricted.Stages (depending on the
18254 -- supported profile) to make sure that one of these packages
18255 -- is implicitly with'ed, since we need to have the tasking
18256 -- run time active for the pragma Priority to have any effect.
18257 -- Previously we with'ed the package System.Tasking, but this
18258 -- package does not trigger the required initialization of the
18259 -- run-time library.
18261 declare
18262 Discard : Entity_Id;
18263 pragma Warnings (Off, Discard);
18264 begin
18265 if Restricted_Profile then
18266 Discard := RTE (RE_Activate_Restricted_Tasks);
18267 else
18268 Discard := RTE (RE_Activate_Tasks);
18269 end if;
18270 end;
18272 -- Task or Protected, must be of type Integer
18274 elsif Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
18275 Arg := Get_Pragma_Arg (Arg1);
18276 Ent := Defining_Identifier (Parent (P));
18278 -- The expression must be analyzed in the special manner
18279 -- described in "Handling of Default and Per-Object
18280 -- Expressions" in sem.ads.
18282 Preanalyze_Spec_Expression (Arg, RTE (RE_Any_Priority));
18284 if not Is_OK_Static_Expression (Arg) then
18285 Check_Restriction (Static_Priorities, Arg);
18286 end if;
18288 -- Anything else is incorrect
18290 else
18291 Pragma_Misplaced;
18292 end if;
18294 -- Check duplicate pragma before we chain the pragma in the Rep
18295 -- Item chain of Ent.
18297 Check_Duplicate_Pragma (Ent);
18298 Record_Rep_Item (Ent, N);
18299 end Priority;
18301 -----------------------------------
18302 -- Priority_Specific_Dispatching --
18303 -----------------------------------
18305 -- pragma Priority_Specific_Dispatching (
18306 -- policy_IDENTIFIER,
18307 -- first_priority_EXPRESSION,
18308 -- last_priority_EXPRESSION);
18310 when Pragma_Priority_Specific_Dispatching =>
18311 Priority_Specific_Dispatching : declare
18312 Prio_Id : constant Entity_Id := RTE (RE_Any_Priority);
18313 -- This is the entity System.Any_Priority;
18315 DP : Character;
18316 Lower_Bound : Node_Id;
18317 Upper_Bound : Node_Id;
18318 Lower_Val : Uint;
18319 Upper_Val : Uint;
18321 begin
18322 Ada_2005_Pragma;
18323 Check_Arg_Count (3);
18324 Check_No_Identifiers;
18325 Check_Arg_Is_Task_Dispatching_Policy (Arg1);
18326 Check_Valid_Configuration_Pragma;
18327 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
18328 DP := Fold_Upper (Name_Buffer (1));
18330 Lower_Bound := Get_Pragma_Arg (Arg2);
18331 Check_Arg_Is_OK_Static_Expression (Lower_Bound, Standard_Integer);
18332 Lower_Val := Expr_Value (Lower_Bound);
18334 Upper_Bound := Get_Pragma_Arg (Arg3);
18335 Check_Arg_Is_OK_Static_Expression (Upper_Bound, Standard_Integer);
18336 Upper_Val := Expr_Value (Upper_Bound);
18338 -- It is not allowed to use Task_Dispatching_Policy and
18339 -- Priority_Specific_Dispatching in the same partition.
18341 if Task_Dispatching_Policy /= ' ' then
18342 Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
18343 Error_Pragma
18344 ("pragma% incompatible with Task_Dispatching_Policy#");
18346 -- Check lower bound in range
18348 elsif Lower_Val < Expr_Value (Type_Low_Bound (Prio_Id))
18349 or else
18350 Lower_Val > Expr_Value (Type_High_Bound (Prio_Id))
18351 then
18352 Error_Pragma_Arg
18353 ("first_priority is out of range", Arg2);
18355 -- Check upper bound in range
18357 elsif Upper_Val < Expr_Value (Type_Low_Bound (Prio_Id))
18358 or else
18359 Upper_Val > Expr_Value (Type_High_Bound (Prio_Id))
18360 then
18361 Error_Pragma_Arg
18362 ("last_priority is out of range", Arg3);
18364 -- Check that the priority range is valid
18366 elsif Lower_Val > Upper_Val then
18367 Error_Pragma
18368 ("last_priority_expression must be greater than or equal to "
18369 & "first_priority_expression");
18371 -- Store the new policy, but always preserve System_Location since
18372 -- we like the error message with the run-time name.
18374 else
18375 -- Check overlapping in the priority ranges specified in other
18376 -- Priority_Specific_Dispatching pragmas within the same
18377 -- partition. We can only check those we know about.
18379 for J in
18380 Specific_Dispatching.First .. Specific_Dispatching.Last
18381 loop
18382 if Specific_Dispatching.Table (J).First_Priority in
18383 UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
18384 or else Specific_Dispatching.Table (J).Last_Priority in
18385 UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
18386 then
18387 Error_Msg_Sloc :=
18388 Specific_Dispatching.Table (J).Pragma_Loc;
18389 Error_Pragma
18390 ("priority range overlaps with "
18391 & "Priority_Specific_Dispatching#");
18392 end if;
18393 end loop;
18395 -- The use of Priority_Specific_Dispatching is incompatible
18396 -- with Task_Dispatching_Policy.
18398 if Task_Dispatching_Policy /= ' ' then
18399 Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
18400 Error_Pragma
18401 ("Priority_Specific_Dispatching incompatible "
18402 & "with Task_Dispatching_Policy#");
18403 end if;
18405 -- The use of Priority_Specific_Dispatching forces ceiling
18406 -- locking policy.
18408 if Locking_Policy /= ' ' and then Locking_Policy /= 'C' then
18409 Error_Msg_Sloc := Locking_Policy_Sloc;
18410 Error_Pragma
18411 ("Priority_Specific_Dispatching incompatible "
18412 & "with Locking_Policy#");
18414 -- Set the Ceiling_Locking policy, but preserve System_Location
18415 -- since we like the error message with the run time name.
18417 else
18418 Locking_Policy := 'C';
18420 if Locking_Policy_Sloc /= System_Location then
18421 Locking_Policy_Sloc := Loc;
18422 end if;
18423 end if;
18425 -- Add entry in the table
18427 Specific_Dispatching.Append
18428 ((Dispatching_Policy => DP,
18429 First_Priority => UI_To_Int (Lower_Val),
18430 Last_Priority => UI_To_Int (Upper_Val),
18431 Pragma_Loc => Loc));
18432 end if;
18433 end Priority_Specific_Dispatching;
18435 -------------
18436 -- Profile --
18437 -------------
18439 -- pragma Profile (profile_IDENTIFIER);
18441 -- profile_IDENTIFIER => Restricted | Ravenscar | Rational
18443 when Pragma_Profile =>
18444 Ada_2005_Pragma;
18445 Check_Arg_Count (1);
18446 Check_Valid_Configuration_Pragma;
18447 Check_No_Identifiers;
18449 declare
18450 Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
18452 begin
18453 if Chars (Argx) = Name_Ravenscar then
18454 Set_Ravenscar_Profile (N);
18456 elsif Chars (Argx) = Name_Restricted then
18457 Set_Profile_Restrictions
18458 (Restricted,
18459 N, Warn => Treat_Restrictions_As_Warnings);
18461 elsif Chars (Argx) = Name_Rational then
18462 Set_Rational_Profile;
18464 elsif Chars (Argx) = Name_No_Implementation_Extensions then
18465 Set_Profile_Restrictions
18466 (No_Implementation_Extensions,
18467 N, Warn => Treat_Restrictions_As_Warnings);
18469 else
18470 Error_Pragma_Arg ("& is not a valid profile", Argx);
18471 end if;
18472 end;
18474 ----------------------
18475 -- Profile_Warnings --
18476 ----------------------
18478 -- pragma Profile_Warnings (profile_IDENTIFIER);
18480 -- profile_IDENTIFIER => Restricted | Ravenscar
18482 when Pragma_Profile_Warnings =>
18483 GNAT_Pragma;
18484 Check_Arg_Count (1);
18485 Check_Valid_Configuration_Pragma;
18486 Check_No_Identifiers;
18488 declare
18489 Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
18491 begin
18492 if Chars (Argx) = Name_Ravenscar then
18493 Set_Profile_Restrictions (Ravenscar, N, Warn => True);
18495 elsif Chars (Argx) = Name_Restricted then
18496 Set_Profile_Restrictions (Restricted, N, Warn => True);
18498 elsif Chars (Argx) = Name_No_Implementation_Extensions then
18499 Set_Profile_Restrictions
18500 (No_Implementation_Extensions, N, Warn => True);
18502 else
18503 Error_Pragma_Arg ("& is not a valid profile", Argx);
18504 end if;
18505 end;
18507 --------------------------
18508 -- Propagate_Exceptions --
18509 --------------------------
18511 -- pragma Propagate_Exceptions;
18513 -- Note: this pragma is obsolete and has no effect
18515 when Pragma_Propagate_Exceptions =>
18516 GNAT_Pragma;
18517 Check_Arg_Count (0);
18519 if Warn_On_Obsolescent_Feature then
18520 Error_Msg_N
18521 ("'G'N'A'T pragma Propagate'_Exceptions is now obsolete " &
18522 "and has no effect?j?", N);
18523 end if;
18525 -----------------------------
18526 -- Provide_Shift_Operators --
18527 -----------------------------
18529 -- pragma Provide_Shift_Operators (integer_subtype_LOCAL_NAME);
18531 when Pragma_Provide_Shift_Operators =>
18532 Provide_Shift_Operators : declare
18533 Ent : Entity_Id;
18535 procedure Declare_Shift_Operator (Nam : Name_Id);
18536 -- Insert declaration and pragma Instrinsic for named shift op
18538 ----------------------------
18539 -- Declare_Shift_Operator --
18540 ----------------------------
18542 procedure Declare_Shift_Operator (Nam : Name_Id) is
18543 Func : Node_Id;
18544 Import : Node_Id;
18546 begin
18547 Func :=
18548 Make_Subprogram_Declaration (Loc,
18549 Make_Function_Specification (Loc,
18550 Defining_Unit_Name =>
18551 Make_Defining_Identifier (Loc, Chars => Nam),
18553 Result_Definition =>
18554 Make_Identifier (Loc, Chars => Chars (Ent)),
18556 Parameter_Specifications => New_List (
18557 Make_Parameter_Specification (Loc,
18558 Defining_Identifier =>
18559 Make_Defining_Identifier (Loc, Name_Value),
18560 Parameter_Type =>
18561 Make_Identifier (Loc, Chars => Chars (Ent))),
18563 Make_Parameter_Specification (Loc,
18564 Defining_Identifier =>
18565 Make_Defining_Identifier (Loc, Name_Amount),
18566 Parameter_Type =>
18567 New_Occurrence_Of (Standard_Natural, Loc)))));
18569 Import :=
18570 Make_Pragma (Loc,
18571 Pragma_Identifier => Make_Identifier (Loc, Name_Import),
18572 Pragma_Argument_Associations => New_List (
18573 Make_Pragma_Argument_Association (Loc,
18574 Expression => Make_Identifier (Loc, Name_Intrinsic)),
18575 Make_Pragma_Argument_Association (Loc,
18576 Expression => Make_Identifier (Loc, Nam))));
18578 Insert_After (N, Import);
18579 Insert_After (N, Func);
18580 end Declare_Shift_Operator;
18582 -- Start of processing for Provide_Shift_Operators
18584 begin
18585 GNAT_Pragma;
18586 Check_Arg_Count (1);
18587 Check_Arg_Is_Local_Name (Arg1);
18589 Arg1 := Get_Pragma_Arg (Arg1);
18591 -- We must have an entity name
18593 if not Is_Entity_Name (Arg1) then
18594 Error_Pragma_Arg
18595 ("pragma % must apply to integer first subtype", Arg1);
18596 end if;
18598 -- If no Entity, means there was a prior error so ignore
18600 if Present (Entity (Arg1)) then
18601 Ent := Entity (Arg1);
18603 -- Apply error checks
18605 if not Is_First_Subtype (Ent) then
18606 Error_Pragma_Arg
18607 ("cannot apply pragma %",
18608 "\& is not a first subtype",
18609 Arg1);
18611 elsif not Is_Integer_Type (Ent) then
18612 Error_Pragma_Arg
18613 ("cannot apply pragma %",
18614 "\& is not an integer type",
18615 Arg1);
18617 elsif Has_Shift_Operator (Ent) then
18618 Error_Pragma_Arg
18619 ("cannot apply pragma %",
18620 "\& already has declared shift operators",
18621 Arg1);
18623 elsif Is_Frozen (Ent) then
18624 Error_Pragma_Arg
18625 ("pragma % appears too late",
18626 "\& is already frozen",
18627 Arg1);
18628 end if;
18630 -- Now declare the operators. We do this during analysis rather
18631 -- than expansion, since we want the operators available if we
18632 -- are operating in -gnatc or ASIS mode.
18634 Declare_Shift_Operator (Name_Rotate_Left);
18635 Declare_Shift_Operator (Name_Rotate_Right);
18636 Declare_Shift_Operator (Name_Shift_Left);
18637 Declare_Shift_Operator (Name_Shift_Right);
18638 Declare_Shift_Operator (Name_Shift_Right_Arithmetic);
18639 end if;
18640 end Provide_Shift_Operators;
18642 ------------------
18643 -- Psect_Object --
18644 ------------------
18646 -- pragma Psect_Object (
18647 -- [Internal =>] LOCAL_NAME,
18648 -- [, [External =>] EXTERNAL_SYMBOL]
18649 -- [, [Size =>] EXTERNAL_SYMBOL]);
18651 when Pragma_Psect_Object | Pragma_Common_Object =>
18652 Psect_Object : declare
18653 Args : Args_List (1 .. 3);
18654 Names : constant Name_List (1 .. 3) := (
18655 Name_Internal,
18656 Name_External,
18657 Name_Size);
18659 Internal : Node_Id renames Args (1);
18660 External : Node_Id renames Args (2);
18661 Size : Node_Id renames Args (3);
18663 Def_Id : Entity_Id;
18665 procedure Check_Arg (Arg : Node_Id);
18666 -- Checks that argument is either a string literal or an
18667 -- identifier, and posts error message if not.
18669 ---------------
18670 -- Check_Arg --
18671 ---------------
18673 procedure Check_Arg (Arg : Node_Id) is
18674 begin
18675 if not Nkind_In (Original_Node (Arg),
18676 N_String_Literal,
18677 N_Identifier)
18678 then
18679 Error_Pragma_Arg
18680 ("inappropriate argument for pragma %", Arg);
18681 end if;
18682 end Check_Arg;
18684 -- Start of processing for Common_Object/Psect_Object
18686 begin
18687 GNAT_Pragma;
18688 Gather_Associations (Names, Args);
18689 Process_Extended_Import_Export_Internal_Arg (Internal);
18691 Def_Id := Entity (Internal);
18693 if not Ekind_In (Def_Id, E_Constant, E_Variable) then
18694 Error_Pragma_Arg
18695 ("pragma% must designate an object", Internal);
18696 end if;
18698 Check_Arg (Internal);
18700 if Is_Imported (Def_Id) or else Is_Exported (Def_Id) then
18701 Error_Pragma_Arg
18702 ("cannot use pragma% for imported/exported object",
18703 Internal);
18704 end if;
18706 if Is_Concurrent_Type (Etype (Internal)) then
18707 Error_Pragma_Arg
18708 ("cannot specify pragma % for task/protected object",
18709 Internal);
18710 end if;
18712 if Has_Rep_Pragma (Def_Id, Name_Common_Object)
18713 or else
18714 Has_Rep_Pragma (Def_Id, Name_Psect_Object)
18715 then
18716 Error_Msg_N ("??duplicate Common/Psect_Object pragma", N);
18717 end if;
18719 if Ekind (Def_Id) = E_Constant then
18720 Error_Pragma_Arg
18721 ("cannot specify pragma % for a constant", Internal);
18722 end if;
18724 if Is_Record_Type (Etype (Internal)) then
18725 declare
18726 Ent : Entity_Id;
18727 Decl : Entity_Id;
18729 begin
18730 Ent := First_Entity (Etype (Internal));
18731 while Present (Ent) loop
18732 Decl := Declaration_Node (Ent);
18734 if Ekind (Ent) = E_Component
18735 and then Nkind (Decl) = N_Component_Declaration
18736 and then Present (Expression (Decl))
18737 and then Warn_On_Export_Import
18738 then
18739 Error_Msg_N
18740 ("?x?object for pragma % has defaults", Internal);
18741 exit;
18743 else
18744 Next_Entity (Ent);
18745 end if;
18746 end loop;
18747 end;
18748 end if;
18750 if Present (Size) then
18751 Check_Arg (Size);
18752 end if;
18754 if Present (External) then
18755 Check_Arg_Is_External_Name (External);
18756 end if;
18758 -- If all error tests pass, link pragma on to the rep item chain
18760 Record_Rep_Item (Def_Id, N);
18761 end Psect_Object;
18763 ----------
18764 -- Pure --
18765 ----------
18767 -- pragma Pure [(library_unit_NAME)];
18769 when Pragma_Pure => Pure : declare
18770 Ent : Entity_Id;
18772 begin
18773 Check_Ada_83_Warning;
18774 Check_Valid_Library_Unit_Pragma;
18776 if Nkind (N) = N_Null_Statement then
18777 return;
18778 end if;
18780 Ent := Find_Lib_Unit_Name;
18781 Set_Is_Pure (Ent);
18782 Set_Has_Pragma_Pure (Ent);
18783 Set_Suppress_Elaboration_Warnings (Ent);
18784 end Pure;
18786 -------------------
18787 -- Pure_Function --
18788 -------------------
18790 -- pragma Pure_Function ([Entity =>] function_LOCAL_NAME);
18792 when Pragma_Pure_Function => Pure_Function : declare
18793 E_Id : Node_Id;
18794 E : Entity_Id;
18795 Def_Id : Entity_Id;
18796 Effective : Boolean := False;
18798 begin
18799 GNAT_Pragma;
18800 Check_Arg_Count (1);
18801 Check_Optional_Identifier (Arg1, Name_Entity);
18802 Check_Arg_Is_Local_Name (Arg1);
18803 E_Id := Get_Pragma_Arg (Arg1);
18805 if Error_Posted (E_Id) then
18806 return;
18807 end if;
18809 -- Loop through homonyms (overloadings) of referenced entity
18811 E := Entity (E_Id);
18813 if Present (E) then
18814 loop
18815 Def_Id := Get_Base_Subprogram (E);
18817 if not Ekind_In (Def_Id, E_Function,
18818 E_Generic_Function,
18819 E_Operator)
18820 then
18821 Error_Pragma_Arg
18822 ("pragma% requires a function name", Arg1);
18823 end if;
18825 Set_Is_Pure (Def_Id);
18827 if not Has_Pragma_Pure_Function (Def_Id) then
18828 Set_Has_Pragma_Pure_Function (Def_Id);
18829 Effective := True;
18830 end if;
18832 exit when From_Aspect_Specification (N);
18833 E := Homonym (E);
18834 exit when No (E) or else Scope (E) /= Current_Scope;
18835 end loop;
18837 if not Effective
18838 and then Warn_On_Redundant_Constructs
18839 then
18840 Error_Msg_NE
18841 ("pragma Pure_Function on& is redundant?r?",
18842 N, Entity (E_Id));
18843 end if;
18844 end if;
18845 end Pure_Function;
18847 --------------------
18848 -- Queuing_Policy --
18849 --------------------
18851 -- pragma Queuing_Policy (policy_IDENTIFIER);
18853 when Pragma_Queuing_Policy => declare
18854 QP : Character;
18856 begin
18857 Check_Ada_83_Warning;
18858 Check_Arg_Count (1);
18859 Check_No_Identifiers;
18860 Check_Arg_Is_Queuing_Policy (Arg1);
18861 Check_Valid_Configuration_Pragma;
18862 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
18863 QP := Fold_Upper (Name_Buffer (1));
18865 if Queuing_Policy /= ' '
18866 and then Queuing_Policy /= QP
18867 then
18868 Error_Msg_Sloc := Queuing_Policy_Sloc;
18869 Error_Pragma ("queuing policy incompatible with policy#");
18871 -- Set new policy, but always preserve System_Location since we
18872 -- like the error message with the run time name.
18874 else
18875 Queuing_Policy := QP;
18877 if Queuing_Policy_Sloc /= System_Location then
18878 Queuing_Policy_Sloc := Loc;
18879 end if;
18880 end if;
18881 end;
18883 --------------
18884 -- Rational --
18885 --------------
18887 -- pragma Rational, for compatibility with foreign compiler
18889 when Pragma_Rational =>
18890 Set_Rational_Profile;
18892 ------------------------------------
18893 -- Refined_Depends/Refined_Global --
18894 ------------------------------------
18896 -- pragma Refined_Depends (DEPENDENCY_RELATION);
18898 -- DEPENDENCY_RELATION ::=
18899 -- null
18900 -- | DEPENDENCY_CLAUSE {, DEPENDENCY_CLAUSE}
18902 -- DEPENDENCY_CLAUSE ::=
18903 -- OUTPUT_LIST =>[+] INPUT_LIST
18904 -- | NULL_DEPENDENCY_CLAUSE
18906 -- NULL_DEPENDENCY_CLAUSE ::= null => INPUT_LIST
18908 -- OUTPUT_LIST ::= OUTPUT | (OUTPUT {, OUTPUT})
18910 -- INPUT_LIST ::= null | INPUT | (INPUT {, INPUT})
18912 -- OUTPUT ::= NAME | FUNCTION_RESULT
18913 -- INPUT ::= NAME
18915 -- where FUNCTION_RESULT is a function Result attribute_reference
18917 -- pragma Refined_Global (GLOBAL_SPECIFICATION);
18919 -- GLOBAL_SPECIFICATION ::=
18920 -- null
18921 -- | GLOBAL_LIST
18922 -- | MODED_GLOBAL_LIST {, MODED_GLOBAL_LIST}
18924 -- MODED_GLOBAL_LIST ::= MODE_SELECTOR => GLOBAL_LIST
18926 -- MODE_SELECTOR ::= In_Out | Input | Output | Proof_In
18927 -- GLOBAL_LIST ::= GLOBAL_ITEM | (GLOBAL_ITEM {, GLOBAL_ITEM})
18928 -- GLOBAL_ITEM ::= NAME
18930 when Pragma_Refined_Depends |
18931 Pragma_Refined_Global => Refined_Depends_Global :
18932 declare
18933 Body_Id : Entity_Id;
18934 Legal : Boolean;
18935 Spec_Id : Entity_Id;
18937 begin
18938 Analyze_Refined_Pragma (Spec_Id, Body_Id, Legal);
18940 -- Save the pragma in the contract of the subprogram body. The
18941 -- remaining analysis is performed at the end of the enclosing
18942 -- declarations.
18944 if Legal then
18945 Add_Contract_Item (N, Body_Id);
18946 end if;
18947 end Refined_Depends_Global;
18949 ------------------
18950 -- Refined_Post --
18951 ------------------
18953 -- pragma Refined_Post (boolean_EXPRESSION);
18955 when Pragma_Refined_Post => Refined_Post : declare
18956 Body_Id : Entity_Id;
18957 Legal : Boolean;
18958 Result_Seen : Boolean := False;
18959 Spec_Id : Entity_Id;
18961 begin
18962 Analyze_Refined_Pragma (Spec_Id, Body_Id, Legal);
18964 -- Analyze the boolean expression as a "spec expression"
18966 if Legal then
18967 Analyze_Pre_Post_Condition_In_Decl_Part (N, Spec_Id);
18969 -- Verify that the refined postcondition mentions attribute
18970 -- 'Result and its expression introduces a post-state.
18972 if Warn_On_Suspicious_Contract
18973 and then Ekind_In (Spec_Id, E_Function, E_Generic_Function)
18974 then
18975 Check_Result_And_Post_State (N, Result_Seen);
18977 if not Result_Seen then
18978 Error_Pragma
18979 ("pragma % does not mention function result?T?");
18980 end if;
18981 end if;
18983 -- Chain the pragma on the contract for easy retrieval
18985 Add_Contract_Item (N, Body_Id);
18986 end if;
18987 end Refined_Post;
18989 -------------------
18990 -- Refined_State --
18991 -------------------
18993 -- pragma Refined_State (REFINEMENT_LIST);
18995 -- REFINEMENT_LIST ::=
18996 -- REFINEMENT_CLAUSE
18997 -- | (REFINEMENT_CLAUSE {, REFINEMENT_CLAUSE})
18999 -- REFINEMENT_CLAUSE ::= state_NAME => CONSTITUENT_LIST
19001 -- CONSTITUENT_LIST ::=
19002 -- null
19003 -- | CONSTITUENT
19004 -- | (CONSTITUENT {, CONSTITUENT})
19006 -- CONSTITUENT ::= object_NAME | state_NAME
19008 when Pragma_Refined_State => Refined_State : declare
19009 Context : constant Node_Id := Parent (N);
19010 Spec_Id : Entity_Id;
19011 Stmt : Node_Id;
19013 begin
19014 GNAT_Pragma;
19015 Check_No_Identifiers;
19016 Check_Arg_Count (1);
19018 -- Ensure the proper placement of the pragma. Refined states must
19019 -- be associated with a package body.
19021 if Nkind (Context) /= N_Package_Body then
19022 Pragma_Misplaced;
19023 return;
19024 end if;
19026 Stmt := Prev (N);
19027 while Present (Stmt) loop
19029 -- Skip prior pragmas, but check for duplicates
19031 if Nkind (Stmt) = N_Pragma then
19032 if Pragma_Name (Stmt) = Pname then
19033 Error_Msg_Name_1 := Pname;
19034 Error_Msg_Sloc := Sloc (Stmt);
19035 Error_Msg_N ("pragma % duplicates pragma declared #", N);
19036 end if;
19038 -- Skip internally generated code
19040 elsif not Comes_From_Source (Stmt) then
19041 null;
19043 -- The pragma does not apply to a legal construct, issue an
19044 -- error and stop the analysis.
19046 else
19047 Pragma_Misplaced;
19048 return;
19049 end if;
19051 Stmt := Prev (Stmt);
19052 end loop;
19054 Spec_Id := Corresponding_Spec (Context);
19056 -- State refinement is allowed only when the corresponding package
19057 -- declaration has non-null pragma Abstract_State. Refinement not
19058 -- enforced when SPARK checks are suppressed (SPARK RM 7.2.2(3)).
19060 if SPARK_Mode /= Off
19061 and then
19062 (No (Abstract_States (Spec_Id))
19063 or else Has_Null_Abstract_State (Spec_Id))
19064 then
19065 Error_Msg_NE
19066 ("useless refinement, package & does not define abstract "
19067 & "states", N, Spec_Id);
19068 return;
19069 end if;
19071 -- The pragma must be analyzed at the end of the declarations as
19072 -- it has visibility over the whole declarative region. Save the
19073 -- pragma for later (see Analyze_Refined_Depends_In_Decl_Part) by
19074 -- adding it to the contract of the package body.
19076 Add_Contract_Item (N, Defining_Entity (Context));
19077 end Refined_State;
19079 -----------------------
19080 -- Relative_Deadline --
19081 -----------------------
19083 -- pragma Relative_Deadline (time_span_EXPRESSION);
19085 when Pragma_Relative_Deadline => Relative_Deadline : declare
19086 P : constant Node_Id := Parent (N);
19087 Arg : Node_Id;
19089 begin
19090 Ada_2005_Pragma;
19091 Check_No_Identifiers;
19092 Check_Arg_Count (1);
19094 Arg := Get_Pragma_Arg (Arg1);
19096 -- The expression must be analyzed in the special manner described
19097 -- in "Handling of Default and Per-Object Expressions" in sem.ads.
19099 Preanalyze_Spec_Expression (Arg, RTE (RE_Time_Span));
19101 -- Subprogram case
19103 if Nkind (P) = N_Subprogram_Body then
19104 Check_In_Main_Program;
19106 -- Only Task and subprogram cases allowed
19108 elsif Nkind (P) /= N_Task_Definition then
19109 Pragma_Misplaced;
19110 end if;
19112 -- Check duplicate pragma before we set the corresponding flag
19114 if Has_Relative_Deadline_Pragma (P) then
19115 Error_Pragma ("duplicate pragma% not allowed");
19116 end if;
19118 -- Set Has_Relative_Deadline_Pragma only for tasks. Note that
19119 -- Relative_Deadline pragma node cannot be inserted in the Rep
19120 -- Item chain of Ent since it is rewritten by the expander as a
19121 -- procedure call statement that will break the chain.
19123 Set_Has_Relative_Deadline_Pragma (P, True);
19124 end Relative_Deadline;
19126 ------------------------
19127 -- Remote_Access_Type --
19128 ------------------------
19130 -- pragma Remote_Access_Type ([Entity =>] formal_type_LOCAL_NAME);
19132 when Pragma_Remote_Access_Type => Remote_Access_Type : declare
19133 E : Entity_Id;
19135 begin
19136 GNAT_Pragma;
19137 Check_Arg_Count (1);
19138 Check_Optional_Identifier (Arg1, Name_Entity);
19139 Check_Arg_Is_Local_Name (Arg1);
19141 E := Entity (Get_Pragma_Arg (Arg1));
19143 if Nkind (Parent (E)) = N_Formal_Type_Declaration
19144 and then Ekind (E) = E_General_Access_Type
19145 and then Is_Class_Wide_Type (Directly_Designated_Type (E))
19146 and then Scope (Root_Type (Directly_Designated_Type (E)))
19147 = Scope (E)
19148 and then Is_Valid_Remote_Object_Type
19149 (Root_Type (Directly_Designated_Type (E)))
19150 then
19151 Set_Is_Remote_Types (E);
19153 else
19154 Error_Pragma_Arg
19155 ("pragma% applies only to formal access to classwide types",
19156 Arg1);
19157 end if;
19158 end Remote_Access_Type;
19160 ---------------------------
19161 -- Remote_Call_Interface --
19162 ---------------------------
19164 -- pragma Remote_Call_Interface [(library_unit_NAME)];
19166 when Pragma_Remote_Call_Interface => Remote_Call_Interface : declare
19167 Cunit_Node : Node_Id;
19168 Cunit_Ent : Entity_Id;
19169 K : Node_Kind;
19171 begin
19172 Check_Ada_83_Warning;
19173 Check_Valid_Library_Unit_Pragma;
19175 if Nkind (N) = N_Null_Statement then
19176 return;
19177 end if;
19179 Cunit_Node := Cunit (Current_Sem_Unit);
19180 K := Nkind (Unit (Cunit_Node));
19181 Cunit_Ent := Cunit_Entity (Current_Sem_Unit);
19183 if K = N_Package_Declaration
19184 or else K = N_Generic_Package_Declaration
19185 or else K = N_Subprogram_Declaration
19186 or else K = N_Generic_Subprogram_Declaration
19187 or else (K = N_Subprogram_Body
19188 and then Acts_As_Spec (Unit (Cunit_Node)))
19189 then
19190 null;
19191 else
19192 Error_Pragma (
19193 "pragma% must apply to package or subprogram declaration");
19194 end if;
19196 Set_Is_Remote_Call_Interface (Cunit_Ent);
19197 end Remote_Call_Interface;
19199 ------------------
19200 -- Remote_Types --
19201 ------------------
19203 -- pragma Remote_Types [(library_unit_NAME)];
19205 when Pragma_Remote_Types => Remote_Types : declare
19206 Cunit_Node : Node_Id;
19207 Cunit_Ent : Entity_Id;
19209 begin
19210 Check_Ada_83_Warning;
19211 Check_Valid_Library_Unit_Pragma;
19213 if Nkind (N) = N_Null_Statement then
19214 return;
19215 end if;
19217 Cunit_Node := Cunit (Current_Sem_Unit);
19218 Cunit_Ent := Cunit_Entity (Current_Sem_Unit);
19220 if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
19221 N_Generic_Package_Declaration)
19222 then
19223 Error_Pragma
19224 ("pragma% can only apply to a package declaration");
19225 end if;
19227 Set_Is_Remote_Types (Cunit_Ent);
19228 end Remote_Types;
19230 ---------------
19231 -- Ravenscar --
19232 ---------------
19234 -- pragma Ravenscar;
19236 when Pragma_Ravenscar =>
19237 GNAT_Pragma;
19238 Check_Arg_Count (0);
19239 Check_Valid_Configuration_Pragma;
19240 Set_Ravenscar_Profile (N);
19242 if Warn_On_Obsolescent_Feature then
19243 Error_Msg_N
19244 ("pragma Ravenscar is an obsolescent feature?j?", N);
19245 Error_Msg_N
19246 ("|use pragma Profile (Ravenscar) instead?j?", N);
19247 end if;
19249 -------------------------
19250 -- Restricted_Run_Time --
19251 -------------------------
19253 -- pragma Restricted_Run_Time;
19255 when Pragma_Restricted_Run_Time =>
19256 GNAT_Pragma;
19257 Check_Arg_Count (0);
19258 Check_Valid_Configuration_Pragma;
19259 Set_Profile_Restrictions
19260 (Restricted, N, Warn => Treat_Restrictions_As_Warnings);
19262 if Warn_On_Obsolescent_Feature then
19263 Error_Msg_N
19264 ("pragma Restricted_Run_Time is an obsolescent feature?j?",
19266 Error_Msg_N
19267 ("|use pragma Profile (Restricted) instead?j?", N);
19268 end if;
19270 ------------------
19271 -- Restrictions --
19272 ------------------
19274 -- pragma Restrictions (RESTRICTION {, RESTRICTION});
19276 -- RESTRICTION ::=
19277 -- restriction_IDENTIFIER
19278 -- | restriction_parameter_IDENTIFIER => EXPRESSION
19280 when Pragma_Restrictions =>
19281 Process_Restrictions_Or_Restriction_Warnings
19282 (Warn => Treat_Restrictions_As_Warnings);
19284 --------------------------
19285 -- Restriction_Warnings --
19286 --------------------------
19288 -- pragma Restriction_Warnings (RESTRICTION {, RESTRICTION});
19290 -- RESTRICTION ::=
19291 -- restriction_IDENTIFIER
19292 -- | restriction_parameter_IDENTIFIER => EXPRESSION
19294 when Pragma_Restriction_Warnings =>
19295 GNAT_Pragma;
19296 Process_Restrictions_Or_Restriction_Warnings (Warn => True);
19298 ----------------
19299 -- Reviewable --
19300 ----------------
19302 -- pragma Reviewable;
19304 when Pragma_Reviewable =>
19305 Check_Ada_83_Warning;
19306 Check_Arg_Count (0);
19308 -- Call dummy debugging function rv. This is done to assist front
19309 -- end debugging. By placing a Reviewable pragma in the source
19310 -- program, a breakpoint on rv catches this place in the source,
19311 -- allowing convenient stepping to the point of interest.
19315 --------------------------
19316 -- Short_Circuit_And_Or --
19317 --------------------------
19319 -- pragma Short_Circuit_And_Or;
19321 when Pragma_Short_Circuit_And_Or =>
19322 GNAT_Pragma;
19323 Check_Arg_Count (0);
19324 Check_Valid_Configuration_Pragma;
19325 Short_Circuit_And_Or := True;
19327 -------------------
19328 -- Share_Generic --
19329 -------------------
19331 -- pragma Share_Generic (GNAME {, GNAME});
19333 -- GNAME ::= generic_unit_NAME | generic_instance_NAME
19335 when Pragma_Share_Generic =>
19336 GNAT_Pragma;
19337 Process_Generic_List;
19339 ------------
19340 -- Shared --
19341 ------------
19343 -- pragma Shared (LOCAL_NAME);
19345 when Pragma_Shared =>
19346 GNAT_Pragma;
19347 Process_Atomic_Independent_Shared_Volatile;
19349 --------------------
19350 -- Shared_Passive --
19351 --------------------
19353 -- pragma Shared_Passive [(library_unit_NAME)];
19355 -- Set the flag Is_Shared_Passive of program unit name entity
19357 when Pragma_Shared_Passive => Shared_Passive : declare
19358 Cunit_Node : Node_Id;
19359 Cunit_Ent : Entity_Id;
19361 begin
19362 Check_Ada_83_Warning;
19363 Check_Valid_Library_Unit_Pragma;
19365 if Nkind (N) = N_Null_Statement then
19366 return;
19367 end if;
19369 Cunit_Node := Cunit (Current_Sem_Unit);
19370 Cunit_Ent := Cunit_Entity (Current_Sem_Unit);
19372 if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
19373 N_Generic_Package_Declaration)
19374 then
19375 Error_Pragma
19376 ("pragma% can only apply to a package declaration");
19377 end if;
19379 Set_Is_Shared_Passive (Cunit_Ent);
19380 end Shared_Passive;
19382 -----------------------
19383 -- Short_Descriptors --
19384 -----------------------
19386 -- pragma Short_Descriptors;
19388 -- Recognize and validate, but otherwise ignore
19390 when Pragma_Short_Descriptors =>
19391 GNAT_Pragma;
19392 Check_Arg_Count (0);
19393 Check_Valid_Configuration_Pragma;
19395 ------------------------------
19396 -- Simple_Storage_Pool_Type --
19397 ------------------------------
19399 -- pragma Simple_Storage_Pool_Type (type_LOCAL_NAME);
19401 when Pragma_Simple_Storage_Pool_Type =>
19402 Simple_Storage_Pool_Type : declare
19403 Type_Id : Node_Id;
19404 Typ : Entity_Id;
19406 begin
19407 GNAT_Pragma;
19408 Check_Arg_Count (1);
19409 Check_Arg_Is_Library_Level_Local_Name (Arg1);
19411 Type_Id := Get_Pragma_Arg (Arg1);
19412 Find_Type (Type_Id);
19413 Typ := Entity (Type_Id);
19415 if Typ = Any_Type then
19416 return;
19417 end if;
19419 -- We require the pragma to apply to a type declared in a package
19420 -- declaration, but not (immediately) within a package body.
19422 if Ekind (Current_Scope) /= E_Package
19423 or else In_Package_Body (Current_Scope)
19424 then
19425 Error_Pragma
19426 ("pragma% can only apply to type declared immediately "
19427 & "within a package declaration");
19428 end if;
19430 -- A simple storage pool type must be an immutably limited record
19431 -- or private type. If the pragma is given for a private type,
19432 -- the full type is similarly restricted (which is checked later
19433 -- in Freeze_Entity).
19435 if Is_Record_Type (Typ)
19436 and then not Is_Limited_View (Typ)
19437 then
19438 Error_Pragma
19439 ("pragma% can only apply to explicitly limited record type");
19441 elsif Is_Private_Type (Typ) and then not Is_Limited_Type (Typ) then
19442 Error_Pragma
19443 ("pragma% can only apply to a private type that is limited");
19445 elsif not Is_Record_Type (Typ)
19446 and then not Is_Private_Type (Typ)
19447 then
19448 Error_Pragma
19449 ("pragma% can only apply to limited record or private type");
19450 end if;
19452 Record_Rep_Item (Typ, N);
19453 end Simple_Storage_Pool_Type;
19455 ----------------------
19456 -- Source_File_Name --
19457 ----------------------
19459 -- There are five forms for this pragma:
19461 -- pragma Source_File_Name (
19462 -- [UNIT_NAME =>] unit_NAME,
19463 -- BODY_FILE_NAME => STRING_LITERAL
19464 -- [, [INDEX =>] INTEGER_LITERAL]);
19466 -- pragma Source_File_Name (
19467 -- [UNIT_NAME =>] unit_NAME,
19468 -- SPEC_FILE_NAME => STRING_LITERAL
19469 -- [, [INDEX =>] INTEGER_LITERAL]);
19471 -- pragma Source_File_Name (
19472 -- BODY_FILE_NAME => STRING_LITERAL
19473 -- [, DOT_REPLACEMENT => STRING_LITERAL]
19474 -- [, CASING => CASING_SPEC]);
19476 -- pragma Source_File_Name (
19477 -- SPEC_FILE_NAME => STRING_LITERAL
19478 -- [, DOT_REPLACEMENT => STRING_LITERAL]
19479 -- [, CASING => CASING_SPEC]);
19481 -- pragma Source_File_Name (
19482 -- SUBUNIT_FILE_NAME => STRING_LITERAL
19483 -- [, DOT_REPLACEMENT => STRING_LITERAL]
19484 -- [, CASING => CASING_SPEC]);
19486 -- CASING_SPEC ::= Uppercase | Lowercase | Mixedcase
19488 -- Pragma Source_File_Name_Project (SFNP) is equivalent to pragma
19489 -- Source_File_Name (SFN), however their usage is exclusive: SFN can
19490 -- only be used when no project file is used, while SFNP can only be
19491 -- used when a project file is used.
19493 -- No processing here. Processing was completed during parsing, since
19494 -- we need to have file names set as early as possible. Units are
19495 -- loaded well before semantic processing starts.
19497 -- The only processing we defer to this point is the check for
19498 -- correct placement.
19500 when Pragma_Source_File_Name =>
19501 GNAT_Pragma;
19502 Check_Valid_Configuration_Pragma;
19504 ------------------------------
19505 -- Source_File_Name_Project --
19506 ------------------------------
19508 -- See Source_File_Name for syntax
19510 -- No processing here. Processing was completed during parsing, since
19511 -- we need to have file names set as early as possible. Units are
19512 -- loaded well before semantic processing starts.
19514 -- The only processing we defer to this point is the check for
19515 -- correct placement.
19517 when Pragma_Source_File_Name_Project =>
19518 GNAT_Pragma;
19519 Check_Valid_Configuration_Pragma;
19521 -- Check that a pragma Source_File_Name_Project is used only in a
19522 -- configuration pragmas file.
19524 -- Pragmas Source_File_Name_Project should only be generated by
19525 -- the Project Manager in configuration pragmas files.
19527 -- This is really an ugly test. It seems to depend on some
19528 -- accidental and undocumented property. At the very least it
19529 -- needs to be documented, but it would be better to have a
19530 -- clean way of testing if we are in a configuration file???
19532 if Present (Parent (N)) then
19533 Error_Pragma
19534 ("pragma% can only appear in a configuration pragmas file");
19535 end if;
19537 ----------------------
19538 -- Source_Reference --
19539 ----------------------
19541 -- pragma Source_Reference (INTEGER_LITERAL [, STRING_LITERAL]);
19543 -- Nothing to do, all processing completed in Par.Prag, since we need
19544 -- the information for possible parser messages that are output.
19546 when Pragma_Source_Reference =>
19547 GNAT_Pragma;
19549 ----------------
19550 -- SPARK_Mode --
19551 ----------------
19553 -- pragma SPARK_Mode [(On | Off)];
19555 when Pragma_SPARK_Mode => Do_SPARK_Mode : declare
19556 Mode_Id : SPARK_Mode_Type;
19558 procedure Check_Pragma_Conformance
19559 (Context_Pragma : Node_Id;
19560 Entity_Pragma : Node_Id;
19561 Entity : Entity_Id);
19562 -- If Context_Pragma is not Empty, verify that the new pragma N
19563 -- is compatible with the pragma Context_Pragma that was inherited
19564 -- from the context:
19565 -- . if Context_Pragma is ON, then the new mode can be anything
19566 -- . if Context_Pragma is OFF, then the only allowed new mode is
19567 -- also OFF.
19569 -- If Entity is not Empty, verify that the new pragma N is
19570 -- compatible with Entity_Pragma, the SPARK_Mode previously set
19571 -- for Entity (which may be Empty):
19572 -- . if Entity_Pragma is ON, then the new mode can be anything
19573 -- . if Entity_Pragma is OFF, then the only allowed new mode is
19574 -- also OFF.
19575 -- . if Entity_Pragma is Empty, we always issue an error, as this
19576 -- corresponds to a case where a previous section of Entity
19577 -- had no SPARK_Mode set.
19579 procedure Check_Library_Level_Entity (E : Entity_Id);
19580 -- Verify that pragma is applied to library-level entity E
19582 procedure Set_SPARK_Flags;
19583 -- Sets SPARK_Mode from Mode_Id and SPARK_Mode_Pragma from N,
19584 -- and ensures that Dynamic_Elaboration_Checks are off if the
19585 -- call sets SPARK_Mode On.
19587 ------------------------------
19588 -- Check_Pragma_Conformance --
19589 ------------------------------
19591 procedure Check_Pragma_Conformance
19592 (Context_Pragma : Node_Id;
19593 Entity_Pragma : Node_Id;
19594 Entity : Entity_Id)
19596 begin
19597 if Present (Context_Pragma) then
19598 pragma Assert (Nkind (Context_Pragma) = N_Pragma);
19600 -- New mode less restrictive than the established mode
19602 if Get_SPARK_Mode_From_Pragma (Context_Pragma) = Off
19603 and then Get_SPARK_Mode_From_Pragma (N) = On
19604 then
19605 Error_Msg_N
19606 ("cannot change SPARK_Mode from Off to On", Arg1);
19607 Error_Msg_Sloc := Sloc (SPARK_Mode_Pragma);
19608 Error_Msg_N ("\SPARK_Mode was set to Off#", Arg1);
19609 raise Pragma_Exit;
19610 end if;
19611 end if;
19613 if Present (Entity) then
19614 if Present (Entity_Pragma) then
19615 if Get_SPARK_Mode_From_Pragma (Entity_Pragma) = Off
19616 and then Get_SPARK_Mode_From_Pragma (N) = On
19617 then
19618 Error_Msg_N ("incorrect use of SPARK_Mode", Arg1);
19619 Error_Msg_Sloc := Sloc (Entity_Pragma);
19620 Error_Msg_NE
19621 ("\value Off was set for SPARK_Mode on&#",
19622 Arg1, Entity);
19623 raise Pragma_Exit;
19624 end if;
19626 else
19627 Error_Msg_N ("incorrect use of SPARK_Mode", Arg1);
19628 Error_Msg_Sloc := Sloc (Entity);
19629 Error_Msg_NE
19630 ("\no value was set for SPARK_Mode on&#",
19631 Arg1, Entity);
19632 raise Pragma_Exit;
19633 end if;
19634 end if;
19635 end Check_Pragma_Conformance;
19637 --------------------------------
19638 -- Check_Library_Level_Entity --
19639 --------------------------------
19641 procedure Check_Library_Level_Entity (E : Entity_Id) is
19642 MsgF : constant String := "incorrect placement of pragma%";
19644 begin
19645 if not Is_Library_Level_Entity (E) then
19646 Error_Msg_Name_1 := Pname;
19647 Error_Msg_N (Fix_Error (MsgF), N);
19649 if Ekind_In (E, E_Generic_Package,
19650 E_Package,
19651 E_Package_Body)
19652 then
19653 Error_Msg_NE
19654 ("\& is not a library-level package", N, E);
19655 else
19656 Error_Msg_NE
19657 ("\& is not a library-level subprogram", N, E);
19658 end if;
19660 raise Pragma_Exit;
19661 end if;
19662 end Check_Library_Level_Entity;
19664 ---------------------
19665 -- Set_SPARK_Flags --
19666 ---------------------
19668 procedure Set_SPARK_Flags is
19669 begin
19670 SPARK_Mode := Mode_Id;
19671 SPARK_Mode_Pragma := N;
19673 if SPARK_Mode = On then
19674 Dynamic_Elaboration_Checks := False;
19675 end if;
19676 end Set_SPARK_Flags;
19678 -- Local variables
19680 Body_Id : Entity_Id;
19681 Context : Node_Id;
19682 Mode : Name_Id;
19683 Spec_Id : Entity_Id;
19684 Stmt : Node_Id;
19686 -- Start of processing for Do_SPARK_Mode
19688 begin
19689 -- When a SPARK_Mode pragma appears inside an instantiation whose
19690 -- enclosing context has SPARK_Mode set to "off", the pragma has
19691 -- no semantic effect.
19693 if Ignore_Pragma_SPARK_Mode then
19694 Rewrite (N, Make_Null_Statement (Loc));
19695 Analyze (N);
19696 return;
19697 end if;
19699 GNAT_Pragma;
19700 Check_No_Identifiers;
19701 Check_At_Most_N_Arguments (1);
19703 -- Check the legality of the mode (no argument = ON)
19705 if Arg_Count = 1 then
19706 Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
19707 Mode := Chars (Get_Pragma_Arg (Arg1));
19708 else
19709 Mode := Name_On;
19710 end if;
19712 Mode_Id := Get_SPARK_Mode_Type (Mode);
19713 Context := Parent (N);
19715 -- The pragma appears in a configuration pragmas file
19717 if No (Context) then
19718 Check_Valid_Configuration_Pragma;
19720 if Present (SPARK_Mode_Pragma) then
19721 Error_Msg_Sloc := Sloc (SPARK_Mode_Pragma);
19722 Error_Msg_N ("pragma% duplicates pragma declared#", N);
19723 raise Pragma_Exit;
19724 end if;
19726 Set_SPARK_Flags;
19728 -- The pragma acts as a configuration pragma in a compilation unit
19730 -- pragma SPARK_Mode ...;
19731 -- package Pack is ...;
19733 elsif Nkind (Context) = N_Compilation_Unit
19734 and then List_Containing (N) = Context_Items (Context)
19735 then
19736 Check_Valid_Configuration_Pragma;
19737 Set_SPARK_Flags;
19739 -- Otherwise the placement of the pragma within the tree dictates
19740 -- its associated construct. Inspect the declarative list where
19741 -- the pragma resides to find a potential construct.
19743 else
19744 Stmt := Prev (N);
19745 while Present (Stmt) loop
19747 -- Skip prior pragmas, but check for duplicates
19749 if Nkind (Stmt) = N_Pragma then
19750 if Pragma_Name (Stmt) = Pname then
19751 Error_Msg_Name_1 := Pname;
19752 Error_Msg_Sloc := Sloc (Stmt);
19753 Error_Msg_N ("pragma% duplicates pragma declared#", N);
19754 raise Pragma_Exit;
19755 end if;
19757 -- The pragma applies to a [generic] subprogram declaration.
19758 -- Note that this case covers an internally generated spec
19759 -- for a stand alone body.
19761 -- [generic]
19762 -- procedure Proc ...;
19763 -- pragma SPARK_Mode ..;
19765 elsif Nkind_In (Stmt, N_Generic_Subprogram_Declaration,
19766 N_Subprogram_Declaration)
19767 then
19768 Spec_Id := Defining_Entity (Stmt);
19769 Check_Library_Level_Entity (Spec_Id);
19770 Check_Pragma_Conformance
19771 (Context_Pragma => SPARK_Pragma (Spec_Id),
19772 Entity_Pragma => Empty,
19773 Entity => Empty);
19775 Set_SPARK_Pragma (Spec_Id, N);
19776 Set_SPARK_Pragma_Inherited (Spec_Id, False);
19777 return;
19779 -- Skip internally generated code
19781 elsif not Comes_From_Source (Stmt) then
19782 null;
19784 -- Otherwise the pragma does not apply to a legal construct
19785 -- or it does not appear at the top of a declarative or a
19786 -- statement list. Issue an error and stop the analysis.
19788 else
19789 Pragma_Misplaced;
19790 exit;
19791 end if;
19793 Prev (Stmt);
19794 end loop;
19796 -- The pragma applies to a package or a subprogram that acts as
19797 -- a compilation unit.
19799 -- procedure Proc ...;
19800 -- pragma SPARK_Mode ...;
19802 if Nkind (Context) = N_Compilation_Unit_Aux then
19803 Context := Unit (Parent (Context));
19804 end if;
19806 -- The pragma appears within package declarations
19808 if Nkind (Context) = N_Package_Specification then
19809 Spec_Id := Defining_Entity (Context);
19810 Check_Library_Level_Entity (Spec_Id);
19812 -- The pragma is at the top of the visible declarations
19814 -- package Pack is
19815 -- pragma SPARK_Mode ...;
19817 if List_Containing (N) = Visible_Declarations (Context) then
19818 Check_Pragma_Conformance
19819 (Context_Pragma => SPARK_Pragma (Spec_Id),
19820 Entity_Pragma => Empty,
19821 Entity => Empty);
19822 Set_SPARK_Flags;
19824 Set_SPARK_Pragma (Spec_Id, N);
19825 Set_SPARK_Pragma_Inherited (Spec_Id, False);
19826 Set_SPARK_Aux_Pragma (Spec_Id, N);
19827 Set_SPARK_Aux_Pragma_Inherited (Spec_Id, True);
19829 -- The pragma is at the top of the private declarations
19831 -- package Pack is
19832 -- private
19833 -- pragma SPARK_Mode ...;
19835 else
19836 Check_Pragma_Conformance
19837 (Context_Pragma => Empty,
19838 Entity_Pragma => SPARK_Pragma (Spec_Id),
19839 Entity => Spec_Id);
19840 Set_SPARK_Flags;
19842 Set_SPARK_Aux_Pragma (Spec_Id, N);
19843 Set_SPARK_Aux_Pragma_Inherited (Spec_Id, False);
19844 end if;
19846 -- The pragma appears at the top of package body declarations
19848 -- package body Pack is
19849 -- pragma SPARK_Mode ...;
19851 elsif Nkind (Context) = N_Package_Body then
19852 Spec_Id := Corresponding_Spec (Context);
19853 Body_Id := Defining_Entity (Context);
19854 Check_Library_Level_Entity (Body_Id);
19855 Check_Pragma_Conformance
19856 (Context_Pragma => SPARK_Pragma (Body_Id),
19857 Entity_Pragma => SPARK_Aux_Pragma (Spec_Id),
19858 Entity => Spec_Id);
19859 Set_SPARK_Flags;
19861 Set_SPARK_Pragma (Body_Id, N);
19862 Set_SPARK_Pragma_Inherited (Body_Id, False);
19863 Set_SPARK_Aux_Pragma (Body_Id, N);
19864 Set_SPARK_Aux_Pragma_Inherited (Body_Id, True);
19866 -- The pragma appears at the top of package body statements
19868 -- package body Pack is
19869 -- begin
19870 -- pragma SPARK_Mode;
19872 elsif Nkind (Context) = N_Handled_Sequence_Of_Statements
19873 and then Nkind (Parent (Context)) = N_Package_Body
19874 then
19875 Context := Parent (Context);
19876 Spec_Id := Corresponding_Spec (Context);
19877 Body_Id := Defining_Entity (Context);
19878 Check_Library_Level_Entity (Body_Id);
19879 Check_Pragma_Conformance
19880 (Context_Pragma => Empty,
19881 Entity_Pragma => SPARK_Pragma (Body_Id),
19882 Entity => Body_Id);
19883 Set_SPARK_Flags;
19885 Set_SPARK_Aux_Pragma (Body_Id, N);
19886 Set_SPARK_Aux_Pragma_Inherited (Body_Id, False);
19888 -- The pragma appeared as an aspect of a [generic] subprogram
19889 -- declaration that acts as a compilation unit.
19891 -- [generic]
19892 -- procedure Proc ...;
19893 -- pragma SPARK_Mode ...;
19895 elsif Nkind_In (Context, N_Generic_Subprogram_Declaration,
19896 N_Subprogram_Declaration)
19897 then
19898 Spec_Id := Defining_Entity (Context);
19899 Check_Library_Level_Entity (Spec_Id);
19900 Check_Pragma_Conformance
19901 (Context_Pragma => SPARK_Pragma (Spec_Id),
19902 Entity_Pragma => Empty,
19903 Entity => Empty);
19905 Set_SPARK_Pragma (Spec_Id, N);
19906 Set_SPARK_Pragma_Inherited (Spec_Id, False);
19908 -- The pragma appears at the top of subprogram body
19909 -- declarations.
19911 -- procedure Proc ... is
19912 -- pragma SPARK_Mode;
19914 elsif Nkind (Context) = N_Subprogram_Body then
19915 Spec_Id := Corresponding_Spec (Context);
19916 Context := Specification (Context);
19917 Body_Id := Defining_Entity (Context);
19919 -- Ignore pragma when applied to the special body created
19920 -- for inlining, recognized by its internal name _Parent.
19922 if Chars (Body_Id) = Name_uParent then
19923 return;
19924 end if;
19926 Check_Library_Level_Entity (Body_Id);
19928 -- The body is a completion of a previous declaration
19930 if Present (Spec_Id) then
19931 Check_Pragma_Conformance
19932 (Context_Pragma => SPARK_Pragma (Body_Id),
19933 Entity_Pragma => SPARK_Pragma (Spec_Id),
19934 Entity => Spec_Id);
19936 -- The body acts as spec
19938 else
19939 Check_Pragma_Conformance
19940 (Context_Pragma => SPARK_Pragma (Body_Id),
19941 Entity_Pragma => Empty,
19942 Entity => Empty);
19943 end if;
19945 Set_SPARK_Flags;
19947 Set_SPARK_Pragma (Body_Id, N);
19948 Set_SPARK_Pragma_Inherited (Body_Id, False);
19950 -- The pragma does not apply to a legal construct, issue error
19952 else
19953 Pragma_Misplaced;
19954 end if;
19955 end if;
19956 end Do_SPARK_Mode;
19958 --------------------------------
19959 -- Static_Elaboration_Desired --
19960 --------------------------------
19962 -- pragma Static_Elaboration_Desired (DIRECT_NAME);
19964 when Pragma_Static_Elaboration_Desired =>
19965 GNAT_Pragma;
19966 Check_At_Most_N_Arguments (1);
19968 if Is_Compilation_Unit (Current_Scope)
19969 and then Ekind (Current_Scope) = E_Package
19970 then
19971 Set_Static_Elaboration_Desired (Current_Scope, True);
19972 else
19973 Error_Pragma ("pragma% must apply to a library-level package");
19974 end if;
19976 ------------------
19977 -- Storage_Size --
19978 ------------------
19980 -- pragma Storage_Size (EXPRESSION);
19982 when Pragma_Storage_Size => Storage_Size : declare
19983 P : constant Node_Id := Parent (N);
19984 Arg : Node_Id;
19986 begin
19987 Check_No_Identifiers;
19988 Check_Arg_Count (1);
19990 -- The expression must be analyzed in the special manner described
19991 -- in "Handling of Default Expressions" in sem.ads.
19993 Arg := Get_Pragma_Arg (Arg1);
19994 Preanalyze_Spec_Expression (Arg, Any_Integer);
19996 if not Is_OK_Static_Expression (Arg) then
19997 Check_Restriction (Static_Storage_Size, Arg);
19998 end if;
20000 if Nkind (P) /= N_Task_Definition then
20001 Pragma_Misplaced;
20002 return;
20004 else
20005 if Has_Storage_Size_Pragma (P) then
20006 Error_Pragma ("duplicate pragma% not allowed");
20007 else
20008 Set_Has_Storage_Size_Pragma (P, True);
20009 end if;
20011 Record_Rep_Item (Defining_Identifier (Parent (P)), N);
20012 end if;
20013 end Storage_Size;
20015 ------------------
20016 -- Storage_Unit --
20017 ------------------
20019 -- pragma Storage_Unit (NUMERIC_LITERAL);
20021 -- Only permitted argument is System'Storage_Unit value
20023 when Pragma_Storage_Unit =>
20024 Check_No_Identifiers;
20025 Check_Arg_Count (1);
20026 Check_Arg_Is_Integer_Literal (Arg1);
20028 if Intval (Get_Pragma_Arg (Arg1)) /=
20029 UI_From_Int (Ttypes.System_Storage_Unit)
20030 then
20031 Error_Msg_Uint_1 := UI_From_Int (Ttypes.System_Storage_Unit);
20032 Error_Pragma_Arg
20033 ("the only allowed argument for pragma% is ^", Arg1);
20034 end if;
20036 --------------------
20037 -- Stream_Convert --
20038 --------------------
20040 -- pragma Stream_Convert (
20041 -- [Entity =>] type_LOCAL_NAME,
20042 -- [Read =>] function_NAME,
20043 -- [Write =>] function NAME);
20045 when Pragma_Stream_Convert => Stream_Convert : declare
20047 procedure Check_OK_Stream_Convert_Function (Arg : Node_Id);
20048 -- Check that the given argument is the name of a local function
20049 -- of one argument that is not overloaded earlier in the current
20050 -- local scope. A check is also made that the argument is a
20051 -- function with one parameter.
20053 --------------------------------------
20054 -- Check_OK_Stream_Convert_Function --
20055 --------------------------------------
20057 procedure Check_OK_Stream_Convert_Function (Arg : Node_Id) is
20058 Ent : Entity_Id;
20060 begin
20061 Check_Arg_Is_Local_Name (Arg);
20062 Ent := Entity (Get_Pragma_Arg (Arg));
20064 if Has_Homonym (Ent) then
20065 Error_Pragma_Arg
20066 ("argument for pragma% may not be overloaded", Arg);
20067 end if;
20069 if Ekind (Ent) /= E_Function
20070 or else No (First_Formal (Ent))
20071 or else Present (Next_Formal (First_Formal (Ent)))
20072 then
20073 Error_Pragma_Arg
20074 ("argument for pragma% must be function of one argument",
20075 Arg);
20076 end if;
20077 end Check_OK_Stream_Convert_Function;
20079 -- Start of processing for Stream_Convert
20081 begin
20082 GNAT_Pragma;
20083 Check_Arg_Order ((Name_Entity, Name_Read, Name_Write));
20084 Check_Arg_Count (3);
20085 Check_Optional_Identifier (Arg1, Name_Entity);
20086 Check_Optional_Identifier (Arg2, Name_Read);
20087 Check_Optional_Identifier (Arg3, Name_Write);
20088 Check_Arg_Is_Local_Name (Arg1);
20089 Check_OK_Stream_Convert_Function (Arg2);
20090 Check_OK_Stream_Convert_Function (Arg3);
20092 declare
20093 Typ : constant Entity_Id :=
20094 Underlying_Type (Entity (Get_Pragma_Arg (Arg1)));
20095 Read : constant Entity_Id := Entity (Get_Pragma_Arg (Arg2));
20096 Write : constant Entity_Id := Entity (Get_Pragma_Arg (Arg3));
20098 begin
20099 Check_First_Subtype (Arg1);
20101 -- Check for too early or too late. Note that we don't enforce
20102 -- the rule about primitive operations in this case, since, as
20103 -- is the case for explicit stream attributes themselves, these
20104 -- restrictions are not appropriate. Note that the chaining of
20105 -- the pragma by Rep_Item_Too_Late is actually the critical
20106 -- processing done for this pragma.
20108 if Rep_Item_Too_Early (Typ, N)
20109 or else
20110 Rep_Item_Too_Late (Typ, N, FOnly => True)
20111 then
20112 return;
20113 end if;
20115 -- Return if previous error
20117 if Etype (Typ) = Any_Type
20118 or else
20119 Etype (Read) = Any_Type
20120 or else
20121 Etype (Write) = Any_Type
20122 then
20123 return;
20124 end if;
20126 -- Error checks
20128 if Underlying_Type (Etype (Read)) /= Typ then
20129 Error_Pragma_Arg
20130 ("incorrect return type for function&", Arg2);
20131 end if;
20133 if Underlying_Type (Etype (First_Formal (Write))) /= Typ then
20134 Error_Pragma_Arg
20135 ("incorrect parameter type for function&", Arg3);
20136 end if;
20138 if Underlying_Type (Etype (First_Formal (Read))) /=
20139 Underlying_Type (Etype (Write))
20140 then
20141 Error_Pragma_Arg
20142 ("result type of & does not match Read parameter type",
20143 Arg3);
20144 end if;
20145 end;
20146 end Stream_Convert;
20148 ------------------
20149 -- Style_Checks --
20150 ------------------
20152 -- pragma Style_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
20154 -- This is processed by the parser since some of the style checks
20155 -- take place during source scanning and parsing. This means that
20156 -- we don't need to issue error messages here.
20158 when Pragma_Style_Checks => Style_Checks : declare
20159 A : constant Node_Id := Get_Pragma_Arg (Arg1);
20160 S : String_Id;
20161 C : Char_Code;
20163 begin
20164 GNAT_Pragma;
20165 Check_No_Identifiers;
20167 -- Two argument form
20169 if Arg_Count = 2 then
20170 Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
20172 declare
20173 E_Id : Node_Id;
20174 E : Entity_Id;
20176 begin
20177 E_Id := Get_Pragma_Arg (Arg2);
20178 Analyze (E_Id);
20180 if not Is_Entity_Name (E_Id) then
20181 Error_Pragma_Arg
20182 ("second argument of pragma% must be entity name",
20183 Arg2);
20184 end if;
20186 E := Entity (E_Id);
20188 if not Ignore_Style_Checks_Pragmas then
20189 if E = Any_Id then
20190 return;
20191 else
20192 loop
20193 Set_Suppress_Style_Checks
20194 (E, Chars (Get_Pragma_Arg (Arg1)) = Name_Off);
20195 exit when No (Homonym (E));
20196 E := Homonym (E);
20197 end loop;
20198 end if;
20199 end if;
20200 end;
20202 -- One argument form
20204 else
20205 Check_Arg_Count (1);
20207 if Nkind (A) = N_String_Literal then
20208 S := Strval (A);
20210 declare
20211 Slen : constant Natural := Natural (String_Length (S));
20212 Options : String (1 .. Slen);
20213 J : Natural;
20215 begin
20216 J := 1;
20217 loop
20218 C := Get_String_Char (S, Int (J));
20219 exit when not In_Character_Range (C);
20220 Options (J) := Get_Character (C);
20222 -- If at end of string, set options. As per discussion
20223 -- above, no need to check for errors, since we issued
20224 -- them in the parser.
20226 if J = Slen then
20227 if not Ignore_Style_Checks_Pragmas then
20228 Set_Style_Check_Options (Options);
20229 end if;
20231 exit;
20232 end if;
20234 J := J + 1;
20235 end loop;
20236 end;
20238 elsif Nkind (A) = N_Identifier then
20239 if Chars (A) = Name_All_Checks then
20240 if not Ignore_Style_Checks_Pragmas then
20241 if GNAT_Mode then
20242 Set_GNAT_Style_Check_Options;
20243 else
20244 Set_Default_Style_Check_Options;
20245 end if;
20246 end if;
20248 elsif Chars (A) = Name_On then
20249 if not Ignore_Style_Checks_Pragmas then
20250 Style_Check := True;
20251 end if;
20253 elsif Chars (A) = Name_Off then
20254 if not Ignore_Style_Checks_Pragmas then
20255 Style_Check := False;
20256 end if;
20257 end if;
20258 end if;
20259 end if;
20260 end Style_Checks;
20262 --------------
20263 -- Subtitle --
20264 --------------
20266 -- pragma Subtitle ([Subtitle =>] STRING_LITERAL);
20268 when Pragma_Subtitle =>
20269 GNAT_Pragma;
20270 Check_Arg_Count (1);
20271 Check_Optional_Identifier (Arg1, Name_Subtitle);
20272 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
20273 Store_Note (N);
20275 --------------
20276 -- Suppress --
20277 --------------
20279 -- pragma Suppress (IDENTIFIER [, [On =>] NAME]);
20281 when Pragma_Suppress =>
20282 Process_Suppress_Unsuppress (Suppress_Case => True);
20284 ------------------
20285 -- Suppress_All --
20286 ------------------
20288 -- pragma Suppress_All;
20290 -- The only check made here is that the pragma has no arguments.
20291 -- There are no placement rules, and the processing required (setting
20292 -- the Has_Pragma_Suppress_All flag in the compilation unit node was
20293 -- taken care of by the parser). Process_Compilation_Unit_Pragmas
20294 -- then creates and inserts a pragma Suppress (All_Checks).
20296 when Pragma_Suppress_All =>
20297 GNAT_Pragma;
20298 Check_Arg_Count (0);
20300 -------------------------
20301 -- Suppress_Debug_Info --
20302 -------------------------
20304 -- pragma Suppress_Debug_Info ([Entity =>] LOCAL_NAME);
20306 when Pragma_Suppress_Debug_Info =>
20307 GNAT_Pragma;
20308 Check_Arg_Count (1);
20309 Check_Optional_Identifier (Arg1, Name_Entity);
20310 Check_Arg_Is_Local_Name (Arg1);
20311 Set_Debug_Info_Off (Entity (Get_Pragma_Arg (Arg1)));
20313 ----------------------------------
20314 -- Suppress_Exception_Locations --
20315 ----------------------------------
20317 -- pragma Suppress_Exception_Locations;
20319 when Pragma_Suppress_Exception_Locations =>
20320 GNAT_Pragma;
20321 Check_Arg_Count (0);
20322 Check_Valid_Configuration_Pragma;
20323 Exception_Locations_Suppressed := True;
20325 -----------------------------
20326 -- Suppress_Initialization --
20327 -----------------------------
20329 -- pragma Suppress_Initialization ([Entity =>] type_Name);
20331 when Pragma_Suppress_Initialization => Suppress_Init : declare
20332 E_Id : Node_Id;
20333 E : Entity_Id;
20335 begin
20336 GNAT_Pragma;
20337 Check_Arg_Count (1);
20338 Check_Optional_Identifier (Arg1, Name_Entity);
20339 Check_Arg_Is_Local_Name (Arg1);
20341 E_Id := Get_Pragma_Arg (Arg1);
20343 if Etype (E_Id) = Any_Type then
20344 return;
20345 end if;
20347 E := Entity (E_Id);
20349 if not Is_Type (E) and then Ekind (E) /= E_Variable then
20350 Error_Pragma_Arg
20351 ("pragma% requires variable, type or subtype", Arg1);
20352 end if;
20354 if Rep_Item_Too_Early (E, N)
20355 or else
20356 Rep_Item_Too_Late (E, N, FOnly => True)
20357 then
20358 return;
20359 end if;
20361 -- For incomplete/private type, set flag on full view
20363 if Is_Incomplete_Or_Private_Type (E) then
20364 if No (Full_View (Base_Type (E))) then
20365 Error_Pragma_Arg
20366 ("argument of pragma% cannot be an incomplete type", Arg1);
20367 else
20368 Set_Suppress_Initialization (Full_View (Base_Type (E)));
20369 end if;
20371 -- For first subtype, set flag on base type
20373 elsif Is_First_Subtype (E) then
20374 Set_Suppress_Initialization (Base_Type (E));
20376 -- For other than first subtype, set flag on subtype or variable
20378 else
20379 Set_Suppress_Initialization (E);
20380 end if;
20381 end Suppress_Init;
20383 -----------------
20384 -- System_Name --
20385 -----------------
20387 -- pragma System_Name (DIRECT_NAME);
20389 -- Syntax check: one argument, which must be the identifier GNAT or
20390 -- the identifier GCC, no other identifiers are acceptable.
20392 when Pragma_System_Name =>
20393 GNAT_Pragma;
20394 Check_No_Identifiers;
20395 Check_Arg_Count (1);
20396 Check_Arg_Is_One_Of (Arg1, Name_Gcc, Name_Gnat);
20398 -----------------------------
20399 -- Task_Dispatching_Policy --
20400 -----------------------------
20402 -- pragma Task_Dispatching_Policy (policy_IDENTIFIER);
20404 when Pragma_Task_Dispatching_Policy => declare
20405 DP : Character;
20407 begin
20408 Check_Ada_83_Warning;
20409 Check_Arg_Count (1);
20410 Check_No_Identifiers;
20411 Check_Arg_Is_Task_Dispatching_Policy (Arg1);
20412 Check_Valid_Configuration_Pragma;
20413 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
20414 DP := Fold_Upper (Name_Buffer (1));
20416 if Task_Dispatching_Policy /= ' '
20417 and then Task_Dispatching_Policy /= DP
20418 then
20419 Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
20420 Error_Pragma
20421 ("task dispatching policy incompatible with policy#");
20423 -- Set new policy, but always preserve System_Location since we
20424 -- like the error message with the run time name.
20426 else
20427 Task_Dispatching_Policy := DP;
20429 if Task_Dispatching_Policy_Sloc /= System_Location then
20430 Task_Dispatching_Policy_Sloc := Loc;
20431 end if;
20432 end if;
20433 end;
20435 ---------------
20436 -- Task_Info --
20437 ---------------
20439 -- pragma Task_Info (EXPRESSION);
20441 when Pragma_Task_Info => Task_Info : declare
20442 P : constant Node_Id := Parent (N);
20443 Ent : Entity_Id;
20445 begin
20446 GNAT_Pragma;
20448 if Warn_On_Obsolescent_Feature then
20449 Error_Msg_N
20450 ("'G'N'A'T pragma Task_Info is now obsolete, use 'C'P'U "
20451 & "instead?j?", N);
20452 end if;
20454 if Nkind (P) /= N_Task_Definition then
20455 Error_Pragma ("pragma% must appear in task definition");
20456 end if;
20458 Check_No_Identifiers;
20459 Check_Arg_Count (1);
20461 Analyze_And_Resolve
20462 (Get_Pragma_Arg (Arg1), RTE (RE_Task_Info_Type));
20464 if Etype (Get_Pragma_Arg (Arg1)) = Any_Type then
20465 return;
20466 end if;
20468 Ent := Defining_Identifier (Parent (P));
20470 -- Check duplicate pragma before we chain the pragma in the Rep
20471 -- Item chain of Ent.
20473 if Has_Rep_Pragma
20474 (Ent, Name_Task_Info, Check_Parents => False)
20475 then
20476 Error_Pragma ("duplicate pragma% not allowed");
20477 end if;
20479 Record_Rep_Item (Ent, N);
20480 end Task_Info;
20482 ---------------
20483 -- Task_Name --
20484 ---------------
20486 -- pragma Task_Name (string_EXPRESSION);
20488 when Pragma_Task_Name => Task_Name : declare
20489 P : constant Node_Id := Parent (N);
20490 Arg : Node_Id;
20491 Ent : Entity_Id;
20493 begin
20494 Check_No_Identifiers;
20495 Check_Arg_Count (1);
20497 Arg := Get_Pragma_Arg (Arg1);
20499 -- The expression is used in the call to Create_Task, and must be
20500 -- expanded there, not in the context of the current spec. It must
20501 -- however be analyzed to capture global references, in case it
20502 -- appears in a generic context.
20504 Preanalyze_And_Resolve (Arg, Standard_String);
20506 if Nkind (P) /= N_Task_Definition then
20507 Pragma_Misplaced;
20508 end if;
20510 Ent := Defining_Identifier (Parent (P));
20512 -- Check duplicate pragma before we chain the pragma in the Rep
20513 -- Item chain of Ent.
20515 if Has_Rep_Pragma
20516 (Ent, Name_Task_Name, Check_Parents => False)
20517 then
20518 Error_Pragma ("duplicate pragma% not allowed");
20519 end if;
20521 Record_Rep_Item (Ent, N);
20522 end Task_Name;
20524 ------------------
20525 -- Task_Storage --
20526 ------------------
20528 -- pragma Task_Storage (
20529 -- [Task_Type =>] LOCAL_NAME,
20530 -- [Top_Guard =>] static_integer_EXPRESSION);
20532 when Pragma_Task_Storage => Task_Storage : declare
20533 Args : Args_List (1 .. 2);
20534 Names : constant Name_List (1 .. 2) := (
20535 Name_Task_Type,
20536 Name_Top_Guard);
20538 Task_Type : Node_Id renames Args (1);
20539 Top_Guard : Node_Id renames Args (2);
20541 Ent : Entity_Id;
20543 begin
20544 GNAT_Pragma;
20545 Gather_Associations (Names, Args);
20547 if No (Task_Type) then
20548 Error_Pragma
20549 ("missing task_type argument for pragma%");
20550 end if;
20552 Check_Arg_Is_Local_Name (Task_Type);
20554 Ent := Entity (Task_Type);
20556 if not Is_Task_Type (Ent) then
20557 Error_Pragma_Arg
20558 ("argument for pragma% must be task type", Task_Type);
20559 end if;
20561 if No (Top_Guard) then
20562 Error_Pragma_Arg
20563 ("pragma% takes two arguments", Task_Type);
20564 else
20565 Check_Arg_Is_OK_Static_Expression (Top_Guard, Any_Integer);
20566 end if;
20568 Check_First_Subtype (Task_Type);
20570 if Rep_Item_Too_Late (Ent, N) then
20571 raise Pragma_Exit;
20572 end if;
20573 end Task_Storage;
20575 ---------------
20576 -- Test_Case --
20577 ---------------
20579 -- pragma Test_Case
20580 -- ([Name =>] Static_String_EXPRESSION
20581 -- ,[Mode =>] MODE_TYPE
20582 -- [, Requires => Boolean_EXPRESSION]
20583 -- [, Ensures => Boolean_EXPRESSION]);
20585 -- MODE_TYPE ::= Nominal | Robustness
20587 when Pragma_Test_Case =>
20588 GNAT_Pragma;
20589 Check_Test_Case;
20591 --------------------------
20592 -- Thread_Local_Storage --
20593 --------------------------
20595 -- pragma Thread_Local_Storage ([Entity =>] LOCAL_NAME);
20597 when Pragma_Thread_Local_Storage => Thread_Local_Storage : declare
20598 Id : Node_Id;
20599 E : Entity_Id;
20601 begin
20602 GNAT_Pragma;
20603 Check_Arg_Count (1);
20604 Check_Optional_Identifier (Arg1, Name_Entity);
20605 Check_Arg_Is_Library_Level_Local_Name (Arg1);
20607 Id := Get_Pragma_Arg (Arg1);
20608 Analyze (Id);
20610 if not Is_Entity_Name (Id)
20611 or else Ekind (Entity (Id)) /= E_Variable
20612 then
20613 Error_Pragma_Arg ("local variable name required", Arg1);
20614 end if;
20616 E := Entity (Id);
20618 if Rep_Item_Too_Early (E, N)
20619 or else Rep_Item_Too_Late (E, N)
20620 then
20621 raise Pragma_Exit;
20622 end if;
20624 Set_Has_Pragma_Thread_Local_Storage (E);
20625 Set_Has_Gigi_Rep_Item (E);
20626 end Thread_Local_Storage;
20628 ----------------
20629 -- Time_Slice --
20630 ----------------
20632 -- pragma Time_Slice (static_duration_EXPRESSION);
20634 when Pragma_Time_Slice => Time_Slice : declare
20635 Val : Ureal;
20636 Nod : Node_Id;
20638 begin
20639 GNAT_Pragma;
20640 Check_Arg_Count (1);
20641 Check_No_Identifiers;
20642 Check_In_Main_Program;
20643 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_Duration);
20645 if not Error_Posted (Arg1) then
20646 Nod := Next (N);
20647 while Present (Nod) loop
20648 if Nkind (Nod) = N_Pragma
20649 and then Pragma_Name (Nod) = Name_Time_Slice
20650 then
20651 Error_Msg_Name_1 := Pname;
20652 Error_Msg_N ("duplicate pragma% not permitted", Nod);
20653 end if;
20655 Next (Nod);
20656 end loop;
20657 end if;
20659 -- Process only if in main unit
20661 if Get_Source_Unit (Loc) = Main_Unit then
20662 Opt.Time_Slice_Set := True;
20663 Val := Expr_Value_R (Get_Pragma_Arg (Arg1));
20665 if Val <= Ureal_0 then
20666 Opt.Time_Slice_Value := 0;
20668 elsif Val > UR_From_Uint (UI_From_Int (1000)) then
20669 Opt.Time_Slice_Value := 1_000_000_000;
20671 else
20672 Opt.Time_Slice_Value :=
20673 UI_To_Int (UR_To_Uint (Val * UI_From_Int (1_000_000)));
20674 end if;
20675 end if;
20676 end Time_Slice;
20678 -----------
20679 -- Title --
20680 -----------
20682 -- pragma Title (TITLING_OPTION [, TITLING OPTION]);
20684 -- TITLING_OPTION ::=
20685 -- [Title =>] STRING_LITERAL
20686 -- | [Subtitle =>] STRING_LITERAL
20688 when Pragma_Title => Title : declare
20689 Args : Args_List (1 .. 2);
20690 Names : constant Name_List (1 .. 2) := (
20691 Name_Title,
20692 Name_Subtitle);
20694 begin
20695 GNAT_Pragma;
20696 Gather_Associations (Names, Args);
20697 Store_Note (N);
20699 for J in 1 .. 2 loop
20700 if Present (Args (J)) then
20701 Check_Arg_Is_OK_Static_Expression
20702 (Args (J), Standard_String);
20703 end if;
20704 end loop;
20705 end Title;
20707 ----------------------------
20708 -- Type_Invariant[_Class] --
20709 ----------------------------
20711 -- pragma Type_Invariant[_Class]
20712 -- ([Entity =>] type_LOCAL_NAME,
20713 -- [Check =>] EXPRESSION);
20715 when Pragma_Type_Invariant |
20716 Pragma_Type_Invariant_Class =>
20717 Type_Invariant : declare
20718 I_Pragma : Node_Id;
20720 begin
20721 Check_Arg_Count (2);
20723 -- Rewrite Type_Invariant[_Class] pragma as an Invariant pragma,
20724 -- setting Class_Present for the Type_Invariant_Class case.
20726 Set_Class_Present (N, Prag_Id = Pragma_Type_Invariant_Class);
20727 I_Pragma := New_Copy (N);
20728 Set_Pragma_Identifier
20729 (I_Pragma, Make_Identifier (Loc, Name_Invariant));
20730 Rewrite (N, I_Pragma);
20731 Set_Analyzed (N, False);
20732 Analyze (N);
20733 end Type_Invariant;
20735 ---------------------
20736 -- Unchecked_Union --
20737 ---------------------
20739 -- pragma Unchecked_Union (first_subtype_LOCAL_NAME)
20741 when Pragma_Unchecked_Union => Unchecked_Union : declare
20742 Assoc : constant Node_Id := Arg1;
20743 Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
20744 Typ : Entity_Id;
20745 Tdef : Node_Id;
20746 Clist : Node_Id;
20747 Vpart : Node_Id;
20748 Comp : Node_Id;
20749 Variant : Node_Id;
20751 begin
20752 Ada_2005_Pragma;
20753 Check_No_Identifiers;
20754 Check_Arg_Count (1);
20755 Check_Arg_Is_Local_Name (Arg1);
20757 Find_Type (Type_Id);
20759 Typ := Entity (Type_Id);
20761 if Typ = Any_Type
20762 or else Rep_Item_Too_Early (Typ, N)
20763 then
20764 return;
20765 else
20766 Typ := Underlying_Type (Typ);
20767 end if;
20769 if Rep_Item_Too_Late (Typ, N) then
20770 return;
20771 end if;
20773 Check_First_Subtype (Arg1);
20775 -- Note remaining cases are references to a type in the current
20776 -- declarative part. If we find an error, we post the error on
20777 -- the relevant type declaration at an appropriate point.
20779 if not Is_Record_Type (Typ) then
20780 Error_Msg_N ("unchecked union must be record type", Typ);
20781 return;
20783 elsif Is_Tagged_Type (Typ) then
20784 Error_Msg_N ("unchecked union must not be tagged", Typ);
20785 return;
20787 elsif not Has_Discriminants (Typ) then
20788 Error_Msg_N
20789 ("unchecked union must have one discriminant", Typ);
20790 return;
20792 -- Note: in previous versions of GNAT we used to check for limited
20793 -- types and give an error, but in fact the standard does allow
20794 -- Unchecked_Union on limited types, so this check was removed.
20796 -- Similarly, GNAT used to require that all discriminants have
20797 -- default values, but this is not mandated by the RM.
20799 -- Proceed with basic error checks completed
20801 else
20802 Tdef := Type_Definition (Declaration_Node (Typ));
20803 Clist := Component_List (Tdef);
20805 -- Check presence of component list and variant part
20807 if No (Clist) or else No (Variant_Part (Clist)) then
20808 Error_Msg_N
20809 ("unchecked union must have variant part", Tdef);
20810 return;
20811 end if;
20813 -- Check components
20815 Comp := First (Component_Items (Clist));
20816 while Present (Comp) loop
20817 Check_Component (Comp, Typ);
20818 Next (Comp);
20819 end loop;
20821 -- Check variant part
20823 Vpart := Variant_Part (Clist);
20825 Variant := First (Variants (Vpart));
20826 while Present (Variant) loop
20827 Check_Variant (Variant, Typ);
20828 Next (Variant);
20829 end loop;
20830 end if;
20832 Set_Is_Unchecked_Union (Typ);
20833 Set_Convention (Typ, Convention_C);
20834 Set_Has_Unchecked_Union (Base_Type (Typ));
20835 Set_Is_Unchecked_Union (Base_Type (Typ));
20836 end Unchecked_Union;
20838 ------------------------
20839 -- Unimplemented_Unit --
20840 ------------------------
20842 -- pragma Unimplemented_Unit;
20844 -- Note: this only gives an error if we are generating code, or if
20845 -- we are in a generic library unit (where the pragma appears in the
20846 -- body, not in the spec).
20848 when Pragma_Unimplemented_Unit => Unimplemented_Unit : declare
20849 Cunitent : constant Entity_Id :=
20850 Cunit_Entity (Get_Source_Unit (Loc));
20851 Ent_Kind : constant Entity_Kind :=
20852 Ekind (Cunitent);
20854 begin
20855 GNAT_Pragma;
20856 Check_Arg_Count (0);
20858 if Operating_Mode = Generate_Code
20859 or else Ent_Kind = E_Generic_Function
20860 or else Ent_Kind = E_Generic_Procedure
20861 or else Ent_Kind = E_Generic_Package
20862 then
20863 Get_Name_String (Chars (Cunitent));
20864 Set_Casing (Mixed_Case);
20865 Write_Str (Name_Buffer (1 .. Name_Len));
20866 Write_Str (" is not supported in this configuration");
20867 Write_Eol;
20868 raise Unrecoverable_Error;
20869 end if;
20870 end Unimplemented_Unit;
20872 ------------------------
20873 -- Universal_Aliasing --
20874 ------------------------
20876 -- pragma Universal_Aliasing [([Entity =>] type_LOCAL_NAME)];
20878 when Pragma_Universal_Aliasing => Universal_Alias : declare
20879 E_Id : Entity_Id;
20881 begin
20882 GNAT_Pragma;
20883 Check_Arg_Count (1);
20884 Check_Optional_Identifier (Arg2, Name_Entity);
20885 Check_Arg_Is_Local_Name (Arg1);
20886 E_Id := Entity (Get_Pragma_Arg (Arg1));
20888 if E_Id = Any_Type then
20889 return;
20890 elsif No (E_Id) or else not Is_Type (E_Id) then
20891 Error_Pragma_Arg ("pragma% requires type", Arg1);
20892 end if;
20894 Set_Universal_Aliasing (Implementation_Base_Type (E_Id));
20895 Record_Rep_Item (E_Id, N);
20896 end Universal_Alias;
20898 --------------------
20899 -- Universal_Data --
20900 --------------------
20902 -- pragma Universal_Data [(library_unit_NAME)];
20904 when Pragma_Universal_Data =>
20905 GNAT_Pragma;
20907 -- If this is a configuration pragma, then set the universal
20908 -- addressing option, otherwise confirm that the pragma satisfies
20909 -- the requirements of library unit pragma placement and leave it
20910 -- to the GNAAMP back end to detect the pragma (avoids transitive
20911 -- setting of the option due to withed units).
20913 if Is_Configuration_Pragma then
20914 Universal_Addressing_On_AAMP := True;
20915 else
20916 Check_Valid_Library_Unit_Pragma;
20917 end if;
20919 if not AAMP_On_Target then
20920 Error_Pragma ("??pragma% ignored (applies only to AAMP)");
20921 end if;
20923 ----------------
20924 -- Unmodified --
20925 ----------------
20927 -- pragma Unmodified (LOCAL_NAME {, LOCAL_NAME});
20929 when Pragma_Unmodified => Unmodified : declare
20930 Arg_Node : Node_Id;
20931 Arg_Expr : Node_Id;
20932 Arg_Ent : Entity_Id;
20934 begin
20935 GNAT_Pragma;
20936 Check_At_Least_N_Arguments (1);
20938 -- Loop through arguments
20940 Arg_Node := Arg1;
20941 while Present (Arg_Node) loop
20942 Check_No_Identifier (Arg_Node);
20944 -- Note: the analyze call done by Check_Arg_Is_Local_Name will
20945 -- in fact generate reference, so that the entity will have a
20946 -- reference, which will inhibit any warnings about it not
20947 -- being referenced, and also properly show up in the ali file
20948 -- as a reference. But this reference is recorded before the
20949 -- Has_Pragma_Unreferenced flag is set, so that no warning is
20950 -- generated for this reference.
20952 Check_Arg_Is_Local_Name (Arg_Node);
20953 Arg_Expr := Get_Pragma_Arg (Arg_Node);
20955 if Is_Entity_Name (Arg_Expr) then
20956 Arg_Ent := Entity (Arg_Expr);
20958 if not Is_Assignable (Arg_Ent) then
20959 Error_Pragma_Arg
20960 ("pragma% can only be applied to a variable",
20961 Arg_Expr);
20962 else
20963 Set_Has_Pragma_Unmodified (Arg_Ent);
20964 end if;
20965 end if;
20967 Next (Arg_Node);
20968 end loop;
20969 end Unmodified;
20971 ------------------
20972 -- Unreferenced --
20973 ------------------
20975 -- pragma Unreferenced (LOCAL_NAME {, LOCAL_NAME});
20977 -- or when used in a context clause:
20979 -- pragma Unreferenced (library_unit_NAME {, library_unit_NAME}
20981 when Pragma_Unreferenced => Unreferenced : declare
20982 Arg_Node : Node_Id;
20983 Arg_Expr : Node_Id;
20984 Arg_Ent : Entity_Id;
20985 Citem : Node_Id;
20987 begin
20988 GNAT_Pragma;
20989 Check_At_Least_N_Arguments (1);
20991 -- Check case of appearing within context clause
20993 if Is_In_Context_Clause then
20995 -- The arguments must all be units mentioned in a with clause
20996 -- in the same context clause. Note we already checked (in
20997 -- Par.Prag) that the arguments are either identifiers or
20998 -- selected components.
21000 Arg_Node := Arg1;
21001 while Present (Arg_Node) loop
21002 Citem := First (List_Containing (N));
21003 while Citem /= N loop
21004 if Nkind (Citem) = N_With_Clause
21005 and then
21006 Same_Name (Name (Citem), Get_Pragma_Arg (Arg_Node))
21007 then
21008 Set_Has_Pragma_Unreferenced
21009 (Cunit_Entity
21010 (Get_Source_Unit
21011 (Library_Unit (Citem))));
21012 Set_Unit_Name
21013 (Get_Pragma_Arg (Arg_Node), Name (Citem));
21014 exit;
21015 end if;
21017 Next (Citem);
21018 end loop;
21020 if Citem = N then
21021 Error_Pragma_Arg
21022 ("argument of pragma% is not withed unit", Arg_Node);
21023 end if;
21025 Next (Arg_Node);
21026 end loop;
21028 -- Case of not in list of context items
21030 else
21031 Arg_Node := Arg1;
21032 while Present (Arg_Node) loop
21033 Check_No_Identifier (Arg_Node);
21035 -- Note: the analyze call done by Check_Arg_Is_Local_Name
21036 -- will in fact generate reference, so that the entity will
21037 -- have a reference, which will inhibit any warnings about
21038 -- it not being referenced, and also properly show up in the
21039 -- ali file as a reference. But this reference is recorded
21040 -- before the Has_Pragma_Unreferenced flag is set, so that
21041 -- no warning is generated for this reference.
21043 Check_Arg_Is_Local_Name (Arg_Node);
21044 Arg_Expr := Get_Pragma_Arg (Arg_Node);
21046 if Is_Entity_Name (Arg_Expr) then
21047 Arg_Ent := Entity (Arg_Expr);
21049 -- If the entity is overloaded, the pragma applies to the
21050 -- most recent overloading, as documented. In this case,
21051 -- name resolution does not generate a reference, so it
21052 -- must be done here explicitly.
21054 if Is_Overloaded (Arg_Expr) then
21055 Generate_Reference (Arg_Ent, N);
21056 end if;
21058 Set_Has_Pragma_Unreferenced (Arg_Ent);
21059 end if;
21061 Next (Arg_Node);
21062 end loop;
21063 end if;
21064 end Unreferenced;
21066 --------------------------
21067 -- Unreferenced_Objects --
21068 --------------------------
21070 -- pragma Unreferenced_Objects (LOCAL_NAME {, LOCAL_NAME});
21072 when Pragma_Unreferenced_Objects => Unreferenced_Objects : declare
21073 Arg_Node : Node_Id;
21074 Arg_Expr : Node_Id;
21076 begin
21077 GNAT_Pragma;
21078 Check_At_Least_N_Arguments (1);
21080 Arg_Node := Arg1;
21081 while Present (Arg_Node) loop
21082 Check_No_Identifier (Arg_Node);
21083 Check_Arg_Is_Local_Name (Arg_Node);
21084 Arg_Expr := Get_Pragma_Arg (Arg_Node);
21086 if not Is_Entity_Name (Arg_Expr)
21087 or else not Is_Type (Entity (Arg_Expr))
21088 then
21089 Error_Pragma_Arg
21090 ("argument for pragma% must be type or subtype", Arg_Node);
21091 end if;
21093 Set_Has_Pragma_Unreferenced_Objects (Entity (Arg_Expr));
21094 Next (Arg_Node);
21095 end loop;
21096 end Unreferenced_Objects;
21098 ------------------------------
21099 -- Unreserve_All_Interrupts --
21100 ------------------------------
21102 -- pragma Unreserve_All_Interrupts;
21104 when Pragma_Unreserve_All_Interrupts =>
21105 GNAT_Pragma;
21106 Check_Arg_Count (0);
21108 if In_Extended_Main_Code_Unit (Main_Unit_Entity) then
21109 Unreserve_All_Interrupts := True;
21110 end if;
21112 ----------------
21113 -- Unsuppress --
21114 ----------------
21116 -- pragma Unsuppress (IDENTIFIER [, [On =>] NAME]);
21118 when Pragma_Unsuppress =>
21119 Ada_2005_Pragma;
21120 Process_Suppress_Unsuppress (Suppress_Case => False);
21122 ----------------------------
21123 -- Unevaluated_Use_Of_Old --
21124 ----------------------------
21126 -- pragma Unevaluated_Use_Of_Old (Error | Warn | Allow);
21128 when Pragma_Unevaluated_Use_Of_Old =>
21129 GNAT_Pragma;
21130 Check_Arg_Count (1);
21131 Check_No_Identifiers;
21132 Check_Arg_Is_One_Of (Arg1, Name_Error, Name_Warn, Name_Allow);
21134 -- Suppress/Unsuppress can appear as a configuration pragma, or in
21135 -- a declarative part or a package spec.
21137 if not Is_Configuration_Pragma then
21138 Check_Is_In_Decl_Part_Or_Package_Spec;
21139 end if;
21141 -- Store proper setting of Uneval_Old
21143 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
21144 Uneval_Old := Fold_Upper (Name_Buffer (1));
21146 -------------------
21147 -- Use_VADS_Size --
21148 -------------------
21150 -- pragma Use_VADS_Size;
21152 when Pragma_Use_VADS_Size =>
21153 GNAT_Pragma;
21154 Check_Arg_Count (0);
21155 Check_Valid_Configuration_Pragma;
21156 Use_VADS_Size := True;
21158 ---------------------
21159 -- Validity_Checks --
21160 ---------------------
21162 -- pragma Validity_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
21164 when Pragma_Validity_Checks => Validity_Checks : declare
21165 A : constant Node_Id := Get_Pragma_Arg (Arg1);
21166 S : String_Id;
21167 C : Char_Code;
21169 begin
21170 GNAT_Pragma;
21171 Check_Arg_Count (1);
21172 Check_No_Identifiers;
21174 -- Pragma always active unless in CodePeer or GNATprove modes,
21175 -- which use a fixed configuration of validity checks.
21177 if not (CodePeer_Mode or GNATprove_Mode) then
21178 if Nkind (A) = N_String_Literal then
21179 S := Strval (A);
21181 declare
21182 Slen : constant Natural := Natural (String_Length (S));
21183 Options : String (1 .. Slen);
21184 J : Natural;
21186 begin
21187 -- Couldn't we use a for loop here over Options'Range???
21189 J := 1;
21190 loop
21191 C := Get_String_Char (S, Int (J));
21193 -- This is a weird test, it skips setting validity
21194 -- checks entirely if any element of S is out of
21195 -- range of Character, what is that about ???
21197 exit when not In_Character_Range (C);
21198 Options (J) := Get_Character (C);
21200 if J = Slen then
21201 Set_Validity_Check_Options (Options);
21202 exit;
21203 else
21204 J := J + 1;
21205 end if;
21206 end loop;
21207 end;
21209 elsif Nkind (A) = N_Identifier then
21210 if Chars (A) = Name_All_Checks then
21211 Set_Validity_Check_Options ("a");
21212 elsif Chars (A) = Name_On then
21213 Validity_Checks_On := True;
21214 elsif Chars (A) = Name_Off then
21215 Validity_Checks_On := False;
21216 end if;
21217 end if;
21218 end if;
21219 end Validity_Checks;
21221 --------------
21222 -- Volatile --
21223 --------------
21225 -- pragma Volatile (LOCAL_NAME);
21227 when Pragma_Volatile =>
21228 Process_Atomic_Independent_Shared_Volatile;
21230 -------------------------
21231 -- Volatile_Components --
21232 -------------------------
21234 -- pragma Volatile_Components (array_LOCAL_NAME);
21236 -- Volatile is handled by the same circuit as Atomic_Components
21238 ----------------------
21239 -- Warning_As_Error --
21240 ----------------------
21242 -- pragma Warning_As_Error (static_string_EXPRESSION);
21244 when Pragma_Warning_As_Error =>
21245 GNAT_Pragma;
21246 Check_Arg_Count (1);
21247 Check_No_Identifiers;
21248 Check_Valid_Configuration_Pragma;
21250 if not Is_Static_String_Expression (Arg1) then
21251 Error_Pragma_Arg
21252 ("argument of pragma% must be static string expression",
21253 Arg1);
21255 -- OK static string expression
21257 else
21258 Acquire_Warning_Match_String (Arg1);
21259 Warnings_As_Errors_Count := Warnings_As_Errors_Count + 1;
21260 Warnings_As_Errors (Warnings_As_Errors_Count) :=
21261 new String'(Name_Buffer (1 .. Name_Len));
21262 end if;
21264 --------------
21265 -- Warnings --
21266 --------------
21268 -- pragma Warnings (On | Off [,REASON]);
21269 -- pragma Warnings (On | Off, LOCAL_NAME [,REASON]);
21270 -- pragma Warnings (static_string_EXPRESSION [,REASON]);
21271 -- pragma Warnings (On | Off, STRING_LITERAL [,REASON]);
21273 -- REASON ::= Reason => Static_String_Expression
21275 when Pragma_Warnings => Warnings : declare
21276 Reason : String_Id;
21278 begin
21279 GNAT_Pragma;
21280 Check_At_Least_N_Arguments (1);
21282 -- See if last argument is labeled Reason. If so, make sure we
21283 -- have a static string expression, and acquire the REASON string.
21284 -- Then remove the REASON argument by decreasing Num_Args by one;
21285 -- Remaining processing looks only at first Num_Args arguments).
21287 declare
21288 Last_Arg : constant Node_Id :=
21289 Last (Pragma_Argument_Associations (N));
21291 begin
21292 if Nkind (Last_Arg) = N_Pragma_Argument_Association
21293 and then Chars (Last_Arg) = Name_Reason
21294 then
21295 Start_String;
21296 Get_Reason_String (Get_Pragma_Arg (Last_Arg));
21297 Reason := End_String;
21298 Arg_Count := Arg_Count - 1;
21300 -- Not allowed in compiler units (bootstrap issues)
21302 Check_Compiler_Unit ("Reason for pragma Warnings", N);
21304 -- No REASON string, set null string as reason
21306 else
21307 Reason := Null_String_Id;
21308 end if;
21309 end;
21311 -- Now proceed with REASON taken care of and eliminated
21313 Check_No_Identifiers;
21315 -- If debug flag -gnatd.i is set, pragma is ignored
21317 if Debug_Flag_Dot_I then
21318 return;
21319 end if;
21321 -- Process various forms of the pragma
21323 declare
21324 Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
21326 begin
21327 -- One argument case
21329 if Arg_Count = 1 then
21331 -- On/Off one argument case was processed by parser
21333 if Nkind (Argx) = N_Identifier
21334 and then Nam_In (Chars (Argx), Name_On, Name_Off)
21335 then
21336 null;
21338 -- One argument case must be ON/OFF or static string expr
21340 elsif not Is_Static_String_Expression (Arg1) then
21341 Error_Pragma_Arg
21342 ("argument of pragma% must be On/Off or static string "
21343 & "expression", Arg1);
21345 -- One argument string expression case
21347 else
21348 declare
21349 Lit : constant Node_Id := Expr_Value_S (Argx);
21350 Str : constant String_Id := Strval (Lit);
21351 Len : constant Nat := String_Length (Str);
21352 C : Char_Code;
21353 J : Nat;
21354 OK : Boolean;
21355 Chr : Character;
21357 begin
21358 J := 1;
21359 while J <= Len loop
21360 C := Get_String_Char (Str, J);
21361 OK := In_Character_Range (C);
21363 if OK then
21364 Chr := Get_Character (C);
21366 -- Dash case: only -Wxxx is accepted
21368 if J = 1
21369 and then J < Len
21370 and then Chr = '-'
21371 then
21372 J := J + 1;
21373 C := Get_String_Char (Str, J);
21374 Chr := Get_Character (C);
21375 exit when Chr = 'W';
21376 OK := False;
21378 -- Dot case
21380 elsif J < Len and then Chr = '.' then
21381 J := J + 1;
21382 C := Get_String_Char (Str, J);
21383 Chr := Get_Character (C);
21385 if not Set_Dot_Warning_Switch (Chr) then
21386 Error_Pragma_Arg
21387 ("invalid warning switch character "
21388 & '.' & Chr, Arg1);
21389 end if;
21391 -- Non-Dot case
21393 else
21394 OK := Set_Warning_Switch (Chr);
21395 end if;
21396 end if;
21398 if not OK then
21399 Error_Pragma_Arg
21400 ("invalid warning switch character " & Chr,
21401 Arg1);
21402 end if;
21404 J := J + 1;
21405 end loop;
21406 end;
21407 end if;
21409 -- Two or more arguments (must be two)
21411 else
21412 Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
21413 Check_Arg_Count (2);
21415 declare
21416 E_Id : Node_Id;
21417 E : Entity_Id;
21418 Err : Boolean;
21420 begin
21421 E_Id := Get_Pragma_Arg (Arg2);
21422 Analyze (E_Id);
21424 -- In the expansion of an inlined body, a reference to
21425 -- the formal may be wrapped in a conversion if the
21426 -- actual is a conversion. Retrieve the real entity name.
21428 if (In_Instance_Body or In_Inlined_Body)
21429 and then Nkind (E_Id) = N_Unchecked_Type_Conversion
21430 then
21431 E_Id := Expression (E_Id);
21432 end if;
21434 -- Entity name case
21436 if Is_Entity_Name (E_Id) then
21437 E := Entity (E_Id);
21439 if E = Any_Id then
21440 return;
21441 else
21442 loop
21443 Set_Warnings_Off
21444 (E, (Chars (Get_Pragma_Arg (Arg1)) =
21445 Name_Off));
21447 -- For OFF case, make entry in warnings off
21448 -- pragma table for later processing. But we do
21449 -- not do that within an instance, since these
21450 -- warnings are about what is needed in the
21451 -- template, not an instance of it.
21453 if Chars (Get_Pragma_Arg (Arg1)) = Name_Off
21454 and then Warn_On_Warnings_Off
21455 and then not In_Instance
21456 then
21457 Warnings_Off_Pragmas.Append ((N, E, Reason));
21458 end if;
21460 if Is_Enumeration_Type (E) then
21461 declare
21462 Lit : Entity_Id;
21463 begin
21464 Lit := First_Literal (E);
21465 while Present (Lit) loop
21466 Set_Warnings_Off (Lit);
21467 Next_Literal (Lit);
21468 end loop;
21469 end;
21470 end if;
21472 exit when No (Homonym (E));
21473 E := Homonym (E);
21474 end loop;
21475 end if;
21477 -- Error if not entity or static string expression case
21479 elsif not Is_Static_String_Expression (Arg2) then
21480 Error_Pragma_Arg
21481 ("second argument of pragma% must be entity name "
21482 & "or static string expression", Arg2);
21484 -- Static string expression case
21486 else
21487 Acquire_Warning_Match_String (Arg2);
21489 -- Note on configuration pragma case: If this is a
21490 -- configuration pragma, then for an OFF pragma, we
21491 -- just set Config True in the call, which is all
21492 -- that needs to be done. For the case of ON, this
21493 -- is normally an error, unless it is canceling the
21494 -- effect of a previous OFF pragma in the same file.
21495 -- In any other case, an error will be signalled (ON
21496 -- with no matching OFF).
21498 -- Note: We set Used if we are inside a generic to
21499 -- disable the test that the non-config case actually
21500 -- cancels a warning. That's because we can't be sure
21501 -- there isn't an instantiation in some other unit
21502 -- where a warning is suppressed.
21504 -- We could do a little better here by checking if the
21505 -- generic unit we are inside is public, but for now
21506 -- we don't bother with that refinement.
21508 if Chars (Argx) = Name_Off then
21509 Set_Specific_Warning_Off
21510 (Loc, Name_Buffer (1 .. Name_Len), Reason,
21511 Config => Is_Configuration_Pragma,
21512 Used => Inside_A_Generic or else In_Instance);
21514 elsif Chars (Argx) = Name_On then
21515 Set_Specific_Warning_On
21516 (Loc, Name_Buffer (1 .. Name_Len), Err);
21518 if Err then
21519 Error_Msg
21520 ("??pragma Warnings On with no matching "
21521 & "Warnings Off", Loc);
21522 end if;
21523 end if;
21524 end if;
21525 end;
21526 end if;
21527 end;
21528 end Warnings;
21530 -------------------
21531 -- Weak_External --
21532 -------------------
21534 -- pragma Weak_External ([Entity =>] LOCAL_NAME);
21536 when Pragma_Weak_External => Weak_External : declare
21537 Ent : Entity_Id;
21539 begin
21540 GNAT_Pragma;
21541 Check_Arg_Count (1);
21542 Check_Optional_Identifier (Arg1, Name_Entity);
21543 Check_Arg_Is_Library_Level_Local_Name (Arg1);
21544 Ent := Entity (Get_Pragma_Arg (Arg1));
21546 if Rep_Item_Too_Early (Ent, N) then
21547 return;
21548 else
21549 Ent := Underlying_Type (Ent);
21550 end if;
21552 -- The only processing required is to link this item on to the
21553 -- list of rep items for the given entity. This is accomplished
21554 -- by the call to Rep_Item_Too_Late (when no error is detected
21555 -- and False is returned).
21557 if Rep_Item_Too_Late (Ent, N) then
21558 return;
21559 else
21560 Set_Has_Gigi_Rep_Item (Ent);
21561 end if;
21562 end Weak_External;
21564 -----------------------------
21565 -- Wide_Character_Encoding --
21566 -----------------------------
21568 -- pragma Wide_Character_Encoding (IDENTIFIER);
21570 when Pragma_Wide_Character_Encoding =>
21571 GNAT_Pragma;
21573 -- Nothing to do, handled in parser. Note that we do not enforce
21574 -- configuration pragma placement, this pragma can appear at any
21575 -- place in the source, allowing mixed encodings within a single
21576 -- source program.
21578 null;
21580 --------------------
21581 -- Unknown_Pragma --
21582 --------------------
21584 -- Should be impossible, since the case of an unknown pragma is
21585 -- separately processed before the case statement is entered.
21587 when Unknown_Pragma =>
21588 raise Program_Error;
21589 end case;
21591 -- AI05-0144: detect dangerous order dependence. Disabled for now,
21592 -- until AI is formally approved.
21594 -- Check_Order_Dependence;
21596 exception
21597 when Pragma_Exit => null;
21598 end Analyze_Pragma;
21600 ---------------------------------------------
21601 -- Analyze_Pre_Post_Condition_In_Decl_Part --
21602 ---------------------------------------------
21604 procedure Analyze_Pre_Post_Condition_In_Decl_Part
21605 (Prag : Node_Id;
21606 Subp_Id : Entity_Id)
21608 Arg1 : constant Node_Id := First (Pragma_Argument_Associations (Prag));
21609 Nam : constant Name_Id := Original_Aspect_Name (Prag);
21610 Expr : Node_Id;
21612 Restore_Scope : Boolean := False;
21613 -- Gets set True if we do a Push_Scope needing a Pop_Scope on exit
21615 begin
21616 -- Ensure that the subprogram and its formals are visible when analyzing
21617 -- the expression of the pragma.
21619 if not In_Open_Scopes (Subp_Id) then
21620 Restore_Scope := True;
21621 Push_Scope (Subp_Id);
21622 Install_Formals (Subp_Id);
21623 end if;
21625 -- Preanalyze the boolean expression, we treat this as a spec expression
21626 -- (i.e. similar to a default expression).
21628 Expr := Get_Pragma_Arg (Arg1);
21630 -- In ASIS mode, for a pragma generated from a source aspect, analyze
21631 -- the original aspect expression, which is shared with the generated
21632 -- pragma.
21634 if ASIS_Mode and then Present (Corresponding_Aspect (Prag)) then
21635 Expr := Expression (Corresponding_Aspect (Prag));
21636 end if;
21638 Preanalyze_Assert_Expression (Expr, Standard_Boolean);
21640 -- For a class-wide condition, a reference to a controlling formal must
21641 -- be interpreted as having the class-wide type (or an access to such)
21642 -- so that the inherited condition can be properly applied to any
21643 -- overriding operation (see ARM12 6.6.1 (7)).
21645 if Class_Present (Prag) then
21646 Class_Wide_Condition : declare
21647 T : constant Entity_Id := Find_Dispatching_Type (Subp_Id);
21649 ACW : Entity_Id := Empty;
21650 -- Access to T'class, created if there is a controlling formal
21651 -- that is an access parameter.
21653 function Get_ACW return Entity_Id;
21654 -- If the expression has a reference to an controlling access
21655 -- parameter, create an access to T'class for the necessary
21656 -- conversions if one does not exist.
21658 function Process (N : Node_Id) return Traverse_Result;
21659 -- ARM 6.1.1: Within the expression for a Pre'Class or Post'Class
21660 -- aspect for a primitive subprogram of a tagged type T, a name
21661 -- that denotes a formal parameter of type T is interpreted as
21662 -- having type T'Class. Similarly, a name that denotes a formal
21663 -- accessparameter of type access-to-T is interpreted as having
21664 -- type access-to-T'Class. This ensures the expression is well-
21665 -- defined for a primitive subprogram of a type descended from T.
21666 -- Note that this replacement is not done for selector names in
21667 -- parameter associations. These carry an entity for reference
21668 -- purposes, but semantically they are just identifiers.
21670 -------------
21671 -- Get_ACW --
21672 -------------
21674 function Get_ACW return Entity_Id is
21675 Loc : constant Source_Ptr := Sloc (Prag);
21676 Decl : Node_Id;
21678 begin
21679 if No (ACW) then
21680 Decl :=
21681 Make_Full_Type_Declaration (Loc,
21682 Defining_Identifier => Make_Temporary (Loc, 'T'),
21683 Type_Definition =>
21684 Make_Access_To_Object_Definition (Loc,
21685 Subtype_Indication =>
21686 New_Occurrence_Of (Class_Wide_Type (T), Loc),
21687 All_Present => True));
21689 Insert_Before (Unit_Declaration_Node (Subp_Id), Decl);
21690 Analyze (Decl);
21691 ACW := Defining_Identifier (Decl);
21692 Freeze_Before (Unit_Declaration_Node (Subp_Id), ACW);
21693 end if;
21695 return ACW;
21696 end Get_ACW;
21698 -------------
21699 -- Process --
21700 -------------
21702 function Process (N : Node_Id) return Traverse_Result is
21703 Loc : constant Source_Ptr := Sloc (N);
21704 Typ : Entity_Id;
21706 begin
21707 if Is_Entity_Name (N)
21708 and then Present (Entity (N))
21709 and then Is_Formal (Entity (N))
21710 and then Nkind (Parent (N)) /= N_Type_Conversion
21711 and then
21712 (Nkind (Parent (N)) /= N_Parameter_Association
21713 or else N /= Selector_Name (Parent (N)))
21714 then
21715 if Etype (Entity (N)) = T then
21716 Typ := Class_Wide_Type (T);
21718 elsif Is_Access_Type (Etype (Entity (N)))
21719 and then Designated_Type (Etype (Entity (N))) = T
21720 then
21721 Typ := Get_ACW;
21722 else
21723 Typ := Empty;
21724 end if;
21726 if Present (Typ) then
21727 Rewrite (N,
21728 Make_Type_Conversion (Loc,
21729 Subtype_Mark =>
21730 New_Occurrence_Of (Typ, Loc),
21731 Expression => New_Occurrence_Of (Entity (N), Loc)));
21732 Set_Etype (N, Typ);
21733 end if;
21734 end if;
21736 return OK;
21737 end Process;
21739 procedure Replace_Type is new Traverse_Proc (Process);
21741 -- Start of processing for Class_Wide_Condition
21743 begin
21744 if not Present (T) then
21746 -- Pre'Class/Post'Class aspect cases
21748 if From_Aspect_Specification (Prag) then
21749 if Nam = Name_uPre then
21750 Error_Msg_Name_1 := Name_Pre;
21751 else
21752 Error_Msg_Name_1 := Name_Post;
21753 end if;
21755 Error_Msg_Name_2 := Name_Class;
21757 Error_Msg_N
21758 ("aspect `%''%` can only be specified for a primitive "
21759 & "operation of a tagged type",
21760 Corresponding_Aspect (Prag));
21762 -- Pre_Class, Post_Class pragma cases
21764 else
21765 if Nam = Name_uPre then
21766 Error_Msg_Name_1 := Name_Pre_Class;
21767 else
21768 Error_Msg_Name_1 := Name_Post_Class;
21769 end if;
21771 Error_Msg_N
21772 ("pragma% can only be specified for a primitive "
21773 & "operation of a tagged type",
21774 Corresponding_Aspect (Prag));
21775 end if;
21776 end if;
21778 Replace_Type (Get_Pragma_Arg (Arg1));
21779 end Class_Wide_Condition;
21780 end if;
21782 -- Remove the subprogram from the scope stack now that the pre-analysis
21783 -- of the precondition/postcondition is done.
21785 if Restore_Scope then
21786 End_Scope;
21787 end if;
21788 end Analyze_Pre_Post_Condition_In_Decl_Part;
21790 ------------------------------------------
21791 -- Analyze_Refined_Depends_In_Decl_Part --
21792 ------------------------------------------
21794 procedure Analyze_Refined_Depends_In_Decl_Part (N : Node_Id) is
21795 Body_Inputs : Elist_Id := No_Elist;
21796 Body_Outputs : Elist_Id := No_Elist;
21797 -- The inputs and outputs of the subprogram body synthesized from pragma
21798 -- Refined_Depends.
21800 Dependencies : List_Id := No_List;
21801 Depends : Node_Id;
21802 -- The corresponding Depends pragma along with its clauses
21804 Matched_Items : Elist_Id := No_Elist;
21805 -- A list containing the entities of all successfully matched items
21806 -- found in pragma Depends.
21808 Refinements : List_Id := No_List;
21809 -- The clauses of pragma Refined_Depends
21811 Spec_Id : Entity_Id;
21812 -- The entity of the subprogram subject to pragma Refined_Depends
21814 Spec_Inputs : Elist_Id := No_Elist;
21815 Spec_Outputs : Elist_Id := No_Elist;
21816 -- The inputs and outputs of the subprogram spec synthesized from pragma
21817 -- Depends.
21819 procedure Check_Dependency_Clause (Dep_Clause : Node_Id);
21820 -- Try to match a single dependency clause Dep_Clause against one or
21821 -- more refinement clauses found in list Refinements. Each successful
21822 -- match eliminates at least one refinement clause from Refinements.
21824 procedure Check_Output_States;
21825 -- Determine whether pragma Depends contains an output state with a
21826 -- visible refinement and if so, ensure that pragma Refined_Depends
21827 -- mentions all its constituents as outputs.
21829 procedure Normalize_Clauses (Clauses : List_Id);
21830 -- Given a list of dependence or refinement clauses Clauses, normalize
21831 -- each clause by creating multiple dependencies with exactly one input
21832 -- and one output.
21834 procedure Report_Extra_Clauses;
21835 -- Emit an error for each extra clause found in list Refinements
21837 -----------------------------
21838 -- Check_Dependency_Clause --
21839 -----------------------------
21841 procedure Check_Dependency_Clause (Dep_Clause : Node_Id) is
21842 Dep_Input : constant Node_Id := Expression (Dep_Clause);
21843 Dep_Output : constant Node_Id := First (Choices (Dep_Clause));
21845 function Is_In_Out_State_Clause return Boolean;
21846 -- Determine whether dependence clause Dep_Clause denotes an abstract
21847 -- state that depends on itself (State => State).
21849 function Is_Null_Refined_State (Item : Node_Id) return Boolean;
21850 -- Determine whether item Item denotes an abstract state with visible
21851 -- null refinement.
21853 procedure Match_Items
21854 (Dep_Item : Node_Id;
21855 Ref_Item : Node_Id;
21856 Matched : out Boolean);
21857 -- Try to match dependence item Dep_Item against refinement item
21858 -- Ref_Item. To match against a possible null refinement (see 2, 7),
21859 -- set Ref_Item to Empty. Flag Matched is set to True when one of
21860 -- the following conformance scenarios is in effect:
21861 -- 1) Both items denote null
21862 -- 2) Dep_Item denotes null and Ref_Item is Empty (special case)
21863 -- 3) Both items denote attribute 'Result
21864 -- 4) Both items denote the same formal parameter
21865 -- 5) Both items denote the same variable
21866 -- 6) Dep_Item is an abstract state with visible null refinement
21867 -- and Ref_Item denotes null.
21868 -- 7) Dep_Item is an abstract state with visible null refinement
21869 -- and Ref_Item is Empty (special case).
21870 -- 8) Dep_Item is an abstract state with visible non-null
21871 -- refinement and Ref_Item denotes one of its constituents.
21872 -- 9) Dep_Item is an abstract state without a visible refinement
21873 -- and Ref_Item denotes the same state.
21874 -- When scenario 8 is in effect, the entity of the abstract state
21875 -- denoted by Dep_Item is added to list Refined_States.
21877 procedure Record_Item (Item_Id : Entity_Id);
21878 -- Store the entity of an item denoted by Item_Id in Matched_Items
21880 ----------------------------
21881 -- Is_In_Out_State_Clause --
21882 ----------------------------
21884 function Is_In_Out_State_Clause return Boolean is
21885 Dep_Input_Id : Entity_Id;
21886 Dep_Output_Id : Entity_Id;
21888 begin
21889 -- Detect the following clause:
21890 -- State => State
21892 if Is_Entity_Name (Dep_Input)
21893 and then Is_Entity_Name (Dep_Output)
21894 then
21895 -- Handle abstract views generated for limited with clauses
21897 Dep_Input_Id := Available_View (Entity_Of (Dep_Input));
21898 Dep_Output_Id := Available_View (Entity_Of (Dep_Output));
21900 return
21901 Ekind (Dep_Input_Id) = E_Abstract_State
21902 and then Dep_Input_Id = Dep_Output_Id;
21903 else
21904 return False;
21905 end if;
21906 end Is_In_Out_State_Clause;
21908 ---------------------------
21909 -- Is_Null_Refined_State --
21910 ---------------------------
21912 function Is_Null_Refined_State (Item : Node_Id) return Boolean is
21913 Item_Id : Entity_Id;
21915 begin
21916 if Is_Entity_Name (Item) then
21918 -- Handle abstract views generated for limited with clauses
21920 Item_Id := Available_View (Entity_Of (Item));
21922 return Ekind (Item_Id) = E_Abstract_State
21923 and then Has_Null_Refinement (Item_Id);
21925 else
21926 return False;
21927 end if;
21928 end Is_Null_Refined_State;
21930 -----------------
21931 -- Match_Items --
21932 -----------------
21934 procedure Match_Items
21935 (Dep_Item : Node_Id;
21936 Ref_Item : Node_Id;
21937 Matched : out Boolean)
21939 Dep_Item_Id : Entity_Id;
21940 Ref_Item_Id : Entity_Id;
21942 begin
21943 -- Assume that the two items do not match
21945 Matched := False;
21947 -- A null matches null or Empty (special case)
21949 if Nkind (Dep_Item) = N_Null
21950 and then (No (Ref_Item) or else Nkind (Ref_Item) = N_Null)
21951 then
21952 Matched := True;
21954 -- Attribute 'Result matches attribute 'Result
21956 elsif Is_Attribute_Result (Dep_Item)
21957 and then Is_Attribute_Result (Dep_Item)
21958 then
21959 Matched := True;
21961 -- Abstract states, formal parameters and variables
21963 elsif Is_Entity_Name (Dep_Item) then
21965 -- Handle abstract views generated for limited with clauses
21967 Dep_Item_Id := Available_View (Entity_Of (Dep_Item));
21969 if Ekind (Dep_Item_Id) = E_Abstract_State then
21971 -- An abstract state with visible null refinement matches
21972 -- null or Empty (special case).
21974 if Has_Null_Refinement (Dep_Item_Id)
21975 and then (No (Ref_Item) or else Nkind (Ref_Item) = N_Null)
21976 then
21977 Record_Item (Dep_Item_Id);
21978 Matched := True;
21980 -- An abstract state with visible non-null refinement
21981 -- matches one of its constituents.
21983 elsif Has_Non_Null_Refinement (Dep_Item_Id) then
21984 if Is_Entity_Name (Ref_Item) then
21985 Ref_Item_Id := Entity_Of (Ref_Item);
21987 if Ekind_In (Ref_Item_Id, E_Abstract_State, E_Variable)
21988 and then Present (Encapsulating_State (Ref_Item_Id))
21989 and then Encapsulating_State (Ref_Item_Id) =
21990 Dep_Item_Id
21991 then
21992 Record_Item (Dep_Item_Id);
21993 Matched := True;
21994 end if;
21995 end if;
21997 -- An abstract state without a visible refinement matches
21998 -- itself.
22000 elsif Is_Entity_Name (Ref_Item)
22001 and then Entity_Of (Ref_Item) = Dep_Item_Id
22002 then
22003 Record_Item (Dep_Item_Id);
22004 Matched := True;
22005 end if;
22007 -- A formal parameter or a variable matches itself
22009 elsif Is_Entity_Name (Ref_Item)
22010 and then Entity_Of (Ref_Item) = Dep_Item_Id
22011 then
22012 Record_Item (Dep_Item_Id);
22013 Matched := True;
22014 end if;
22015 end if;
22016 end Match_Items;
22018 -----------------
22019 -- Record_Item --
22020 -----------------
22022 procedure Record_Item (Item_Id : Entity_Id) is
22023 begin
22024 if not Contains (Matched_Items, Item_Id) then
22025 Add_Item (Item_Id, Matched_Items);
22026 end if;
22027 end Record_Item;
22029 -- Local variables
22031 Clause_Matched : Boolean := False;
22032 Dummy : Boolean := False;
22033 Inputs_Match : Boolean;
22034 Next_Ref_Clause : Node_Id;
22035 Outputs_Match : Boolean;
22036 Ref_Clause : Node_Id;
22037 Ref_Input : Node_Id;
22038 Ref_Output : Node_Id;
22040 -- Start of processing for Check_Dependency_Clause
22042 begin
22043 -- Examine all refinement clauses and compare them against the
22044 -- dependence clause.
22046 Ref_Clause := First (Refinements);
22047 while Present (Ref_Clause) loop
22048 Next_Ref_Clause := Next (Ref_Clause);
22050 -- Obtain the attributes of the current refinement clause
22052 Ref_Input := Expression (Ref_Clause);
22053 Ref_Output := First (Choices (Ref_Clause));
22055 -- The current refinement clause matches the dependence clause
22056 -- when both outputs match and both inputs match. See routine
22057 -- Match_Items for all possible conformance scenarios.
22059 -- Depends Dep_Output => Dep_Input
22060 -- ^ ^
22061 -- match ? match ?
22062 -- v v
22063 -- Refined_Depends Ref_Output => Ref_Input
22065 Match_Items
22066 (Dep_Item => Dep_Input,
22067 Ref_Item => Ref_Input,
22068 Matched => Inputs_Match);
22070 Match_Items
22071 (Dep_Item => Dep_Output,
22072 Ref_Item => Ref_Output,
22073 Matched => Outputs_Match);
22075 -- An In_Out state clause may be matched against a refinement with
22076 -- a null input or null output as long as the non-null side of the
22077 -- relation contains a valid constituent of the In_Out_State.
22079 if Is_In_Out_State_Clause then
22081 -- Depends => (State => State)
22082 -- Refined_Depends => (null => Constit) -- OK
22084 if Inputs_Match
22085 and then not Outputs_Match
22086 and then Nkind (Ref_Output) = N_Null
22087 then
22088 Outputs_Match := True;
22089 end if;
22091 -- Depends => (State => State)
22092 -- Refined_Depends => (Constit => null) -- OK
22094 if not Inputs_Match
22095 and then Outputs_Match
22096 and then Nkind (Ref_Input) = N_Null
22097 then
22098 Inputs_Match := True;
22099 end if;
22100 end if;
22102 -- The current refinement clause is legally constructed following
22103 -- the rules in SPARK RM 7.2.5, therefore it can be removed from
22104 -- the pool of candidates. The seach continues because a single
22105 -- dependence clause may have multiple matching refinements.
22107 if Inputs_Match and then Outputs_Match then
22108 Clause_Matched := True;
22109 Remove (Ref_Clause);
22110 end if;
22112 Ref_Clause := Next_Ref_Clause;
22113 end loop;
22115 -- Depending on the order or composition of refinement clauses, an
22116 -- In_Out state clause may not be directly refinable.
22118 -- Depends => ((Output, State) => (Input, State))
22119 -- Refined_State => (State => (Constit_1, Constit_2))
22120 -- Refined_Depends => (Constit_1 => Input, Output => Constit_2)
22122 -- Matching normalized clause (State => State) fails because there is
22123 -- no direct refinement capable of satisfying this relation. Another
22124 -- similar case arises when clauses (Constit_1 => Input) and (Output
22125 -- => Constit_2) are matched first, leaving no candidates for clause
22126 -- (State => State). Both scenarios are legal as long as one of the
22127 -- previous clauses mentioned a valid constituent of State.
22129 if not Clause_Matched
22130 and then Is_In_Out_State_Clause
22131 and then
22132 Contains (Matched_Items, Available_View (Entity_Of (Dep_Input)))
22133 then
22134 Clause_Matched := True;
22135 end if;
22137 -- A clause where the input is an abstract state with visible null
22138 -- refinement is implicitly matched when the output has already been
22139 -- matched in a previous clause.
22141 -- Depends => (Output => State) -- implicitly OK
22142 -- Refined_State => (State => null)
22143 -- Refined_Depends => (Output => ...)
22145 if not Clause_Matched
22146 and then Is_Null_Refined_State (Dep_Input)
22147 and then Is_Entity_Name (Dep_Output)
22148 and then
22149 Contains (Matched_Items, Available_View (Entity_Of (Dep_Output)))
22150 then
22151 Clause_Matched := True;
22152 end if;
22154 -- A clause where the output is an abstract state with visible null
22155 -- refinement is implicitly matched when the input has already been
22156 -- matched in a previous clause.
22158 -- Depends => (State => Input) -- implicitly OK
22159 -- Refined_State => (State => null)
22160 -- Refined_Depends => (... => Input)
22162 if not Clause_Matched
22163 and then Is_Null_Refined_State (Dep_Output)
22164 and then Is_Entity_Name (Dep_Input)
22165 and then
22166 Contains (Matched_Items, Available_View (Entity_Of (Dep_Input)))
22167 then
22168 Clause_Matched := True;
22169 end if;
22171 -- At this point either all refinement clauses have been examined or
22172 -- pragma Refined_Depends contains a solitary null. Only an abstract
22173 -- state with null refinement can possibly match these cases.
22175 -- Depends => (State => null)
22176 -- Refined_State => (State => null)
22177 -- Refined_Depends => null -- OK
22179 if not Clause_Matched then
22180 Match_Items
22181 (Dep_Item => Dep_Input,
22182 Ref_Item => Empty,
22183 Matched => Inputs_Match);
22185 Match_Items
22186 (Dep_Item => Dep_Output,
22187 Ref_Item => Empty,
22188 Matched => Outputs_Match);
22190 Clause_Matched := Inputs_Match and Outputs_Match;
22191 end if;
22193 -- If the contents of Refined_Depends are legal, then the current
22194 -- dependence clause should be satisfied either by an explicit match
22195 -- or by one of the special cases.
22197 if not Clause_Matched then
22198 SPARK_Msg_NE
22199 ("dependence clause of subprogram & has no matching refinement "
22200 & "in body", Dep_Clause, Spec_Id);
22201 end if;
22202 end Check_Dependency_Clause;
22204 -------------------------
22205 -- Check_Output_States --
22206 -------------------------
22208 procedure Check_Output_States is
22209 procedure Check_Constituent_Usage (State_Id : Entity_Id);
22210 -- Determine whether all constituents of state State_Id with visible
22211 -- refinement are used as outputs in pragma Refined_Depends. Emit an
22212 -- error if this is not the case.
22214 -----------------------------
22215 -- Check_Constituent_Usage --
22216 -----------------------------
22218 procedure Check_Constituent_Usage (State_Id : Entity_Id) is
22219 Constit_Elmt : Elmt_Id;
22220 Constit_Id : Entity_Id;
22221 Posted : Boolean := False;
22223 begin
22224 Constit_Elmt := First_Elmt (Refinement_Constituents (State_Id));
22225 while Present (Constit_Elmt) loop
22226 Constit_Id := Node (Constit_Elmt);
22228 -- The constituent acts as an input (SPARK RM 7.2.5(3))
22230 if Present (Body_Inputs)
22231 and then Appears_In (Body_Inputs, Constit_Id)
22232 then
22233 Error_Msg_Name_1 := Chars (State_Id);
22234 SPARK_Msg_NE
22235 ("constituent & of state % must act as output in "
22236 & "dependence refinement", N, Constit_Id);
22238 -- The constituent is altogether missing (SPARK RM 7.2.5(3))
22240 elsif No (Body_Outputs)
22241 or else not Appears_In (Body_Outputs, Constit_Id)
22242 then
22243 if not Posted then
22244 Posted := True;
22245 SPARK_Msg_NE
22246 ("output state & must be replaced by all its "
22247 & "constituents in dependence refinement",
22248 N, State_Id);
22249 end if;
22251 SPARK_Msg_NE
22252 ("\constituent & is missing in output list",
22253 N, Constit_Id);
22254 end if;
22256 Next_Elmt (Constit_Elmt);
22257 end loop;
22258 end Check_Constituent_Usage;
22260 -- Local variables
22262 Item : Node_Id;
22263 Item_Elmt : Elmt_Id;
22264 Item_Id : Entity_Id;
22266 -- Start of processing for Check_Output_States
22268 begin
22269 -- Inspect the outputs of pragma Depends looking for a state with a
22270 -- visible refinement.
22272 if Present (Spec_Outputs) then
22273 Item_Elmt := First_Elmt (Spec_Outputs);
22274 while Present (Item_Elmt) loop
22275 Item := Node (Item_Elmt);
22277 -- Deal with the mixed nature of the input and output lists
22279 if Nkind (Item) = N_Defining_Identifier then
22280 Item_Id := Item;
22281 else
22282 Item_Id := Available_View (Entity_Of (Item));
22283 end if;
22285 if Ekind (Item_Id) = E_Abstract_State then
22287 -- The state acts as an input-output, skip it
22289 if Present (Spec_Inputs)
22290 and then Appears_In (Spec_Inputs, Item_Id)
22291 then
22292 null;
22294 -- Ensure that all of the constituents are utilized as
22295 -- outputs in pragma Refined_Depends.
22297 elsif Has_Non_Null_Refinement (Item_Id) then
22298 Check_Constituent_Usage (Item_Id);
22299 end if;
22300 end if;
22302 Next_Elmt (Item_Elmt);
22303 end loop;
22304 end if;
22305 end Check_Output_States;
22307 -----------------------
22308 -- Normalize_Clauses --
22309 -----------------------
22311 procedure Normalize_Clauses (Clauses : List_Id) is
22312 procedure Normalize_Inputs (Clause : Node_Id);
22313 -- Normalize clause Clause by creating multiple clauses for each
22314 -- input item of Clause. It is assumed that Clause has exactly one
22315 -- output. The transformation is as follows:
22317 -- Output => (Input_1, Input_2) -- original
22319 -- Output => Input_1 -- normalizations
22320 -- Output => Input_2
22322 procedure Normalize_Outputs (Clause : Node_Id);
22323 -- Normalize clause Clause by creating multiple clause for each
22324 -- output item of Clause. The transformation is as follows:
22326 -- (Output_1, Output_2) => Input -- original
22328 -- Output_1 => Input -- normalization
22329 -- Output_2 => Input
22331 ----------------------
22332 -- Normalize_Inputs --
22333 ----------------------
22335 procedure Normalize_Inputs (Clause : Node_Id) is
22336 Inputs : constant Node_Id := Expression (Clause);
22337 Loc : constant Source_Ptr := Sloc (Clause);
22338 Output : constant List_Id := Choices (Clause);
22339 Last_Input : Node_Id;
22340 Input : Node_Id;
22341 New_Clause : Node_Id;
22342 Next_Input : Node_Id;
22344 begin
22345 -- Normalization is performed only when the original clause has
22346 -- more than one input. Multiple inputs appear as an aggregate.
22348 if Nkind (Inputs) = N_Aggregate then
22349 Last_Input := Last (Expressions (Inputs));
22351 -- Create a new clause for each input
22353 Input := First (Expressions (Inputs));
22354 while Present (Input) loop
22355 Next_Input := Next (Input);
22357 -- Unhook the current input from the original input list
22358 -- because it will be relocated to a new clause.
22360 Remove (Input);
22362 -- Special processing for the last input. At this point the
22363 -- original aggregate has been stripped down to one element.
22364 -- Replace the aggregate by the element itself.
22366 if Input = Last_Input then
22367 Rewrite (Inputs, Input);
22369 -- Generate a clause of the form:
22370 -- Output => Input
22372 else
22373 New_Clause :=
22374 Make_Component_Association (Loc,
22375 Choices => New_Copy_List_Tree (Output),
22376 Expression => Input);
22378 -- The new clause contains replicated content that has
22379 -- already been analyzed, mark the clause as analyzed.
22381 Set_Analyzed (New_Clause);
22382 Insert_After (Clause, New_Clause);
22383 end if;
22385 Input := Next_Input;
22386 end loop;
22387 end if;
22388 end Normalize_Inputs;
22390 -----------------------
22391 -- Normalize_Outputs --
22392 -----------------------
22394 procedure Normalize_Outputs (Clause : Node_Id) is
22395 Inputs : constant Node_Id := Expression (Clause);
22396 Loc : constant Source_Ptr := Sloc (Clause);
22397 Outputs : constant Node_Id := First (Choices (Clause));
22398 Last_Output : Node_Id;
22399 New_Clause : Node_Id;
22400 Next_Output : Node_Id;
22401 Output : Node_Id;
22403 begin
22404 -- Multiple outputs appear as an aggregate. Nothing to do when
22405 -- the clause has exactly one output.
22407 if Nkind (Outputs) = N_Aggregate then
22408 Last_Output := Last (Expressions (Outputs));
22410 -- Create a clause for each output. Note that each time a new
22411 -- clause is created, the original output list slowly shrinks
22412 -- until there is one item left.
22414 Output := First (Expressions (Outputs));
22415 while Present (Output) loop
22416 Next_Output := Next (Output);
22418 -- Unhook the output from the original output list as it
22419 -- will be relocated to a new clause.
22421 Remove (Output);
22423 -- Special processing for the last output. At this point
22424 -- the original aggregate has been stripped down to one
22425 -- element. Replace the aggregate by the element itself.
22427 if Output = Last_Output then
22428 Rewrite (Outputs, Output);
22430 else
22431 -- Generate a clause of the form:
22432 -- (Output => Inputs)
22434 New_Clause :=
22435 Make_Component_Association (Loc,
22436 Choices => New_List (Output),
22437 Expression => New_Copy_Tree (Inputs));
22439 -- The new clause contains replicated content that has
22440 -- already been analyzed. There is not need to reanalyze
22441 -- them.
22443 Set_Analyzed (New_Clause);
22444 Insert_After (Clause, New_Clause);
22445 end if;
22447 Output := Next_Output;
22448 end loop;
22449 end if;
22450 end Normalize_Outputs;
22452 -- Local variables
22454 Clause : Node_Id;
22456 -- Start of processing for Normalize_Clauses
22458 begin
22459 Clause := First (Clauses);
22460 while Present (Clause) loop
22461 Normalize_Outputs (Clause);
22462 Next (Clause);
22463 end loop;
22465 Clause := First (Clauses);
22466 while Present (Clause) loop
22467 Normalize_Inputs (Clause);
22468 Next (Clause);
22469 end loop;
22470 end Normalize_Clauses;
22472 --------------------------
22473 -- Report_Extra_Clauses --
22474 --------------------------
22476 procedure Report_Extra_Clauses is
22477 Clause : Node_Id;
22479 begin
22480 if Present (Refinements) then
22481 Clause := First (Refinements);
22482 while Present (Clause) loop
22484 -- Do not complain about a null input refinement, since a null
22485 -- input legitimately matches anything.
22487 if Nkind (Clause) /= N_Component_Association
22488 or else Nkind (Expression (Clause)) /= N_Null
22489 then
22490 SPARK_Msg_N
22491 ("unmatched or extra clause in dependence refinement",
22492 Clause);
22493 end if;
22495 Next (Clause);
22496 end loop;
22497 end if;
22498 end Report_Extra_Clauses;
22500 -- Local variables
22502 Body_Decl : constant Node_Id := Find_Related_Subprogram_Or_Body (N);
22503 Body_Id : constant Entity_Id := Defining_Entity (Body_Decl);
22504 Errors : constant Nat := Serious_Errors_Detected;
22505 Refs : constant Node_Id :=
22506 Get_Pragma_Arg (First (Pragma_Argument_Associations (N)));
22507 Clause : Node_Id;
22508 Deps : Node_Id;
22509 Dummy : Boolean;
22511 -- Start of processing for Analyze_Refined_Depends_In_Decl_Part
22513 begin
22514 if Nkind (Body_Decl) = N_Subprogram_Body_Stub then
22515 Spec_Id := Corresponding_Spec_Of_Stub (Body_Decl);
22516 else
22517 Spec_Id := Corresponding_Spec (Body_Decl);
22518 end if;
22520 Depends := Get_Pragma (Spec_Id, Pragma_Depends);
22522 -- Subprogram declarations lacks pragma Depends. Refined_Depends is
22523 -- rendered useless as there is nothing to refine (SPARK RM 7.2.5(2)).
22525 if No (Depends) then
22526 SPARK_Msg_NE
22527 ("useless refinement, declaration of subprogram & lacks aspect or "
22528 & "pragma Depends", N, Spec_Id);
22529 return;
22530 end if;
22532 Deps := Get_Pragma_Arg (First (Pragma_Argument_Associations (Depends)));
22534 -- A null dependency relation renders the refinement useless because it
22535 -- cannot possibly mention abstract states with visible refinement. Note
22536 -- that the inverse is not true as states may be refined to null
22537 -- (SPARK RM 7.2.5(2)).
22539 if Nkind (Deps) = N_Null then
22540 SPARK_Msg_NE
22541 ("useless refinement, subprogram & does not depend on abstract "
22542 & "state with visible refinement", N, Spec_Id);
22543 return;
22544 end if;
22546 -- Analyze Refined_Depends as if it behaved as a regular pragma Depends.
22547 -- This ensures that the categorization of all refined dependency items
22548 -- is consistent with their role.
22550 Analyze_Depends_In_Decl_Part (N);
22552 -- Do not match dependencies against refinements if Refined_Depends is
22553 -- illegal to avoid emitting misleading error.
22555 if Serious_Errors_Detected = Errors then
22557 -- The related subprogram lacks pragma [Refined_]Global. Synthesize
22558 -- the inputs and outputs of the subprogram spec and body to verify
22559 -- the use of states with visible refinement and their constituents.
22561 if No (Get_Pragma (Spec_Id, Pragma_Global))
22562 or else No (Get_Pragma (Body_Id, Pragma_Refined_Global))
22563 then
22564 Collect_Subprogram_Inputs_Outputs
22565 (Subp_Id => Spec_Id,
22566 Synthesize => True,
22567 Subp_Inputs => Spec_Inputs,
22568 Subp_Outputs => Spec_Outputs,
22569 Global_Seen => Dummy);
22571 Collect_Subprogram_Inputs_Outputs
22572 (Subp_Id => Body_Id,
22573 Synthesize => True,
22574 Subp_Inputs => Body_Inputs,
22575 Subp_Outputs => Body_Outputs,
22576 Global_Seen => Dummy);
22578 -- For an output state with a visible refinement, ensure that all
22579 -- constituents appear as outputs in the dependency refinement.
22581 Check_Output_States;
22582 end if;
22584 -- Matching is disabled in ASIS because clauses are not normalized as
22585 -- this is a tree altering activity similar to expansion.
22587 if ASIS_Mode then
22588 return;
22589 end if;
22591 -- Multiple dependency clauses appear as component associations of an
22592 -- aggregate. Note that the clauses are copied because the algorithm
22593 -- modifies them and this should not be visible in Depends.
22595 pragma Assert (Nkind (Deps) = N_Aggregate);
22596 Dependencies := New_Copy_List_Tree (Component_Associations (Deps));
22597 Normalize_Clauses (Dependencies);
22599 if Nkind (Refs) = N_Null then
22600 Refinements := No_List;
22602 -- Multiple dependency clauses appear as component associations of an
22603 -- aggregate. Note that the clauses are copied because the algorithm
22604 -- modifies them and this should not be visible in Refined_Depends.
22606 else pragma Assert (Nkind (Refs) = N_Aggregate);
22607 Refinements := New_Copy_List_Tree (Component_Associations (Refs));
22608 Normalize_Clauses (Refinements);
22609 end if;
22611 -- At this point the clauses of pragmas Depends and Refined_Depends
22612 -- have been normalized into simple dependencies between one output
22613 -- and one input. Examine all clauses of pragma Depends looking for
22614 -- matching clauses in pragma Refined_Depends.
22616 Clause := First (Dependencies);
22617 while Present (Clause) loop
22618 Check_Dependency_Clause (Clause);
22619 Next (Clause);
22620 end loop;
22622 if Serious_Errors_Detected = Errors then
22623 Report_Extra_Clauses;
22624 end if;
22625 end if;
22626 end Analyze_Refined_Depends_In_Decl_Part;
22628 -----------------------------------------
22629 -- Analyze_Refined_Global_In_Decl_Part --
22630 -----------------------------------------
22632 procedure Analyze_Refined_Global_In_Decl_Part (N : Node_Id) is
22633 Global : Node_Id;
22634 -- The corresponding Global pragma
22636 Has_In_State : Boolean := False;
22637 Has_In_Out_State : Boolean := False;
22638 Has_Out_State : Boolean := False;
22639 Has_Proof_In_State : Boolean := False;
22640 -- These flags are set when the corresponding Global pragma has a state
22641 -- of mode Input, In_Out, Output or Proof_In respectively with a visible
22642 -- refinement.
22644 Has_Null_State : Boolean := False;
22645 -- This flag is set when the corresponding Global pragma has at least
22646 -- one state with a null refinement.
22648 In_Constits : Elist_Id := No_Elist;
22649 In_Out_Constits : Elist_Id := No_Elist;
22650 Out_Constits : Elist_Id := No_Elist;
22651 Proof_In_Constits : Elist_Id := No_Elist;
22652 -- These lists contain the entities of all Input, In_Out, Output and
22653 -- Proof_In constituents that appear in Refined_Global and participate
22654 -- in state refinement.
22656 In_Items : Elist_Id := No_Elist;
22657 In_Out_Items : Elist_Id := No_Elist;
22658 Out_Items : Elist_Id := No_Elist;
22659 Proof_In_Items : Elist_Id := No_Elist;
22660 -- These list contain the entities of all Input, In_Out, Output and
22661 -- Proof_In items defined in the corresponding Global pragma.
22663 procedure Check_In_Out_States;
22664 -- Determine whether the corresponding Global pragma mentions In_Out
22665 -- states with visible refinement and if so, ensure that one of the
22666 -- following completions apply to the constituents of the state:
22667 -- 1) there is at least one constituent of mode In_Out
22668 -- 2) there is at least one Input and one Output constituent
22669 -- 3) not all constituents are present and one of them is of mode
22670 -- Output.
22671 -- This routine may remove elements from In_Constits, In_Out_Constits,
22672 -- Out_Constits and Proof_In_Constits.
22674 procedure Check_Input_States;
22675 -- Determine whether the corresponding Global pragma mentions Input
22676 -- states with visible refinement and if so, ensure that at least one of
22677 -- its constituents appears as an Input item in Refined_Global.
22678 -- This routine may remove elements from In_Constits, In_Out_Constits,
22679 -- Out_Constits and Proof_In_Constits.
22681 procedure Check_Output_States;
22682 -- Determine whether the corresponding Global pragma mentions Output
22683 -- states with visible refinement and if so, ensure that all of its
22684 -- constituents appear as Output items in Refined_Global.
22685 -- This routine may remove elements from In_Constits, In_Out_Constits,
22686 -- Out_Constits and Proof_In_Constits.
22688 procedure Check_Proof_In_States;
22689 -- Determine whether the corresponding Global pragma mentions Proof_In
22690 -- states with visible refinement and if so, ensure that at least one of
22691 -- its constituents appears as a Proof_In item in Refined_Global.
22692 -- This routine may remove elements from In_Constits, In_Out_Constits,
22693 -- Out_Constits and Proof_In_Constits.
22695 procedure Check_Refined_Global_List
22696 (List : Node_Id;
22697 Global_Mode : Name_Id := Name_Input);
22698 -- Verify the legality of a single global list declaration. Global_Mode
22699 -- denotes the current mode in effect.
22701 procedure Collect_Global_Items (Prag : Node_Id);
22702 -- Gather all input, in out, output and Proof_In items of pragma Prag
22703 -- in lists In_Items, In_Out_Items, Out_Items and Proof_In_Items. Flags
22704 -- Has_In_State, Has_In_Out_State, Has_Out_State and Has_Proof_In_State
22705 -- are set when there is at least one abstract state with visible
22706 -- refinement available in the corresponding mode. Flag Has_Null_State
22707 -- is set when at least state has a null refinement.
22709 function Present_Then_Remove
22710 (List : Elist_Id;
22711 Item : Entity_Id) return Boolean;
22712 -- Search List for a particular entity Item. If Item has been found,
22713 -- remove it from List. This routine is used to strip lists In_Constits,
22714 -- In_Out_Constits and Out_Constits of valid constituents.
22716 procedure Report_Extra_Constituents;
22717 -- Emit an error for each constituent found in lists In_Constits,
22718 -- In_Out_Constits and Out_Constits.
22720 -------------------------
22721 -- Check_In_Out_States --
22722 -------------------------
22724 procedure Check_In_Out_States is
22725 procedure Check_Constituent_Usage (State_Id : Entity_Id);
22726 -- Determine whether one of the following coverage scenarios is in
22727 -- effect:
22728 -- 1) there is at least one constituent of mode In_Out
22729 -- 2) there is at least one Input and one Output constituent
22730 -- 3) not all constituents are present and one of them is of mode
22731 -- Output.
22732 -- If this is not the case, emit an error.
22734 -----------------------------
22735 -- Check_Constituent_Usage --
22736 -----------------------------
22738 procedure Check_Constituent_Usage (State_Id : Entity_Id) is
22739 Constit_Elmt : Elmt_Id;
22740 Constit_Id : Entity_Id;
22741 Has_Missing : Boolean := False;
22742 In_Out_Seen : Boolean := False;
22743 In_Seen : Boolean := False;
22744 Out_Seen : Boolean := False;
22746 begin
22747 -- Process all the constituents of the state and note their modes
22748 -- within the global refinement.
22750 Constit_Elmt := First_Elmt (Refinement_Constituents (State_Id));
22751 while Present (Constit_Elmt) loop
22752 Constit_Id := Node (Constit_Elmt);
22754 if Present_Then_Remove (In_Constits, Constit_Id) then
22755 In_Seen := True;
22757 elsif Present_Then_Remove (In_Out_Constits, Constit_Id) then
22758 In_Out_Seen := True;
22760 elsif Present_Then_Remove (Out_Constits, Constit_Id) then
22761 Out_Seen := True;
22763 -- A Proof_In constituent cannot participate in the completion
22764 -- of an Output state (SPARK RM 7.2.4(5)).
22766 elsif Present_Then_Remove (Proof_In_Constits, Constit_Id) then
22767 Error_Msg_Name_1 := Chars (State_Id);
22768 SPARK_Msg_NE
22769 ("constituent & of state % must have mode Input, In_Out "
22770 & "or Output in global refinement",
22771 N, Constit_Id);
22773 else
22774 Has_Missing := True;
22775 end if;
22777 Next_Elmt (Constit_Elmt);
22778 end loop;
22780 -- A single In_Out constituent is a valid completion
22782 if In_Out_Seen then
22783 null;
22785 -- A pair of one Input and one Output constituent is a valid
22786 -- completion.
22788 elsif In_Seen and then Out_Seen then
22789 null;
22791 -- A single Output constituent is a valid completion only when
22792 -- some of the other constituents are missing (SPARK RM 7.2.4(5)).
22794 elsif Has_Missing and then Out_Seen then
22795 null;
22797 else
22798 SPARK_Msg_NE
22799 ("global refinement of state & redefines the mode of its "
22800 & "constituents", N, State_Id);
22801 end if;
22802 end Check_Constituent_Usage;
22804 -- Local variables
22806 Item_Elmt : Elmt_Id;
22807 Item_Id : Entity_Id;
22809 -- Start of processing for Check_In_Out_States
22811 begin
22812 -- Inspect the In_Out items of the corresponding Global pragma
22813 -- looking for a state with a visible refinement.
22815 if Has_In_Out_State and then Present (In_Out_Items) then
22816 Item_Elmt := First_Elmt (In_Out_Items);
22817 while Present (Item_Elmt) loop
22818 Item_Id := Node (Item_Elmt);
22820 -- Ensure that one of the three coverage variants is satisfied
22822 if Ekind (Item_Id) = E_Abstract_State
22823 and then Has_Non_Null_Refinement (Item_Id)
22824 then
22825 Check_Constituent_Usage (Item_Id);
22826 end if;
22828 Next_Elmt (Item_Elmt);
22829 end loop;
22830 end if;
22831 end Check_In_Out_States;
22833 ------------------------
22834 -- Check_Input_States --
22835 ------------------------
22837 procedure Check_Input_States is
22838 procedure Check_Constituent_Usage (State_Id : Entity_Id);
22839 -- Determine whether at least one constituent of state State_Id with
22840 -- visible refinement is used and has mode Input. Ensure that the
22841 -- remaining constituents do not have In_Out, Output or Proof_In
22842 -- modes.
22844 -----------------------------
22845 -- Check_Constituent_Usage --
22846 -----------------------------
22848 procedure Check_Constituent_Usage (State_Id : Entity_Id) is
22849 Constit_Elmt : Elmt_Id;
22850 Constit_Id : Entity_Id;
22851 In_Seen : Boolean := False;
22853 begin
22854 Constit_Elmt := First_Elmt (Refinement_Constituents (State_Id));
22855 while Present (Constit_Elmt) loop
22856 Constit_Id := Node (Constit_Elmt);
22858 -- At least one of the constituents appears as an Input
22860 if Present_Then_Remove (In_Constits, Constit_Id) then
22861 In_Seen := True;
22863 -- The constituent appears in the global refinement, but has
22864 -- mode In_Out, Output or Proof_In (SPARK RM 7.2.4(5)).
22866 elsif Present_Then_Remove (In_Out_Constits, Constit_Id)
22867 or else Present_Then_Remove (Out_Constits, Constit_Id)
22868 or else Present_Then_Remove (Proof_In_Constits, Constit_Id)
22869 then
22870 Error_Msg_Name_1 := Chars (State_Id);
22871 SPARK_Msg_NE
22872 ("constituent & of state % must have mode Input in global "
22873 & "refinement", N, Constit_Id);
22874 end if;
22876 Next_Elmt (Constit_Elmt);
22877 end loop;
22879 -- Not one of the constituents appeared as Input
22881 if not In_Seen then
22882 SPARK_Msg_NE
22883 ("global refinement of state & must include at least one "
22884 & "constituent of mode Input", N, State_Id);
22885 end if;
22886 end Check_Constituent_Usage;
22888 -- Local variables
22890 Item_Elmt : Elmt_Id;
22891 Item_Id : Entity_Id;
22893 -- Start of processing for Check_Input_States
22895 begin
22896 -- Inspect the Input items of the corresponding Global pragma
22897 -- looking for a state with a visible refinement.
22899 if Has_In_State and then Present (In_Items) then
22900 Item_Elmt := First_Elmt (In_Items);
22901 while Present (Item_Elmt) loop
22902 Item_Id := Node (Item_Elmt);
22904 -- Ensure that at least one of the constituents is utilized and
22905 -- is of mode Input.
22907 if Ekind (Item_Id) = E_Abstract_State
22908 and then Has_Non_Null_Refinement (Item_Id)
22909 then
22910 Check_Constituent_Usage (Item_Id);
22911 end if;
22913 Next_Elmt (Item_Elmt);
22914 end loop;
22915 end if;
22916 end Check_Input_States;
22918 -------------------------
22919 -- Check_Output_States --
22920 -------------------------
22922 procedure Check_Output_States is
22923 procedure Check_Constituent_Usage (State_Id : Entity_Id);
22924 -- Determine whether all constituents of state State_Id with visible
22925 -- refinement are used and have mode Output. Emit an error if this is
22926 -- not the case.
22928 -----------------------------
22929 -- Check_Constituent_Usage --
22930 -----------------------------
22932 procedure Check_Constituent_Usage (State_Id : Entity_Id) is
22933 Constit_Elmt : Elmt_Id;
22934 Constit_Id : Entity_Id;
22935 Posted : Boolean := False;
22937 begin
22938 Constit_Elmt := First_Elmt (Refinement_Constituents (State_Id));
22939 while Present (Constit_Elmt) loop
22940 Constit_Id := Node (Constit_Elmt);
22942 if Present_Then_Remove (Out_Constits, Constit_Id) then
22943 null;
22945 -- The constituent appears in the global refinement, but has
22946 -- mode Input, In_Out or Proof_In (SPARK RM 7.2.4(5)).
22948 elsif Present_Then_Remove (In_Constits, Constit_Id)
22949 or else Present_Then_Remove (In_Out_Constits, Constit_Id)
22950 or else Present_Then_Remove (Proof_In_Constits, Constit_Id)
22951 then
22952 Error_Msg_Name_1 := Chars (State_Id);
22953 SPARK_Msg_NE
22954 ("constituent & of state % must have mode Output in "
22955 & "global refinement", N, Constit_Id);
22957 -- The constituent is altogether missing (SPARK RM 7.2.5(3))
22959 else
22960 if not Posted then
22961 Posted := True;
22962 SPARK_Msg_NE
22963 ("output state & must be replaced by all its "
22964 & "constituents in global refinement", N, State_Id);
22965 end if;
22967 SPARK_Msg_NE
22968 ("\constituent & is missing in output list",
22969 N, Constit_Id);
22970 end if;
22972 Next_Elmt (Constit_Elmt);
22973 end loop;
22974 end Check_Constituent_Usage;
22976 -- Local variables
22978 Item_Elmt : Elmt_Id;
22979 Item_Id : Entity_Id;
22981 -- Start of processing for Check_Output_States
22983 begin
22984 -- Inspect the Output items of the corresponding Global pragma
22985 -- looking for a state with a visible refinement.
22987 if Has_Out_State and then Present (Out_Items) then
22988 Item_Elmt := First_Elmt (Out_Items);
22989 while Present (Item_Elmt) loop
22990 Item_Id := Node (Item_Elmt);
22992 -- Ensure that all of the constituents are utilized and they
22993 -- have mode Output.
22995 if Ekind (Item_Id) = E_Abstract_State
22996 and then Has_Non_Null_Refinement (Item_Id)
22997 then
22998 Check_Constituent_Usage (Item_Id);
22999 end if;
23001 Next_Elmt (Item_Elmt);
23002 end loop;
23003 end if;
23004 end Check_Output_States;
23006 ---------------------------
23007 -- Check_Proof_In_States --
23008 ---------------------------
23010 procedure Check_Proof_In_States is
23011 procedure Check_Constituent_Usage (State_Id : Entity_Id);
23012 -- Determine whether at least one constituent of state State_Id with
23013 -- visible refinement is used and has mode Proof_In. Ensure that the
23014 -- remaining constituents do not have Input, In_Out or Output modes.
23016 -----------------------------
23017 -- Check_Constituent_Usage --
23018 -----------------------------
23020 procedure Check_Constituent_Usage (State_Id : Entity_Id) is
23021 Constit_Elmt : Elmt_Id;
23022 Constit_Id : Entity_Id;
23023 Proof_In_Seen : Boolean := False;
23025 begin
23026 Constit_Elmt := First_Elmt (Refinement_Constituents (State_Id));
23027 while Present (Constit_Elmt) loop
23028 Constit_Id := Node (Constit_Elmt);
23030 -- At least one of the constituents appears as Proof_In
23032 if Present_Then_Remove (Proof_In_Constits, Constit_Id) then
23033 Proof_In_Seen := True;
23035 -- The constituent appears in the global refinement, but has
23036 -- mode Input, In_Out or Output (SPARK RM 7.2.4(5)).
23038 elsif Present_Then_Remove (In_Constits, Constit_Id)
23039 or else Present_Then_Remove (In_Out_Constits, Constit_Id)
23040 or else Present_Then_Remove (Out_Constits, Constit_Id)
23041 then
23042 Error_Msg_Name_1 := Chars (State_Id);
23043 SPARK_Msg_NE
23044 ("constituent & of state % must have mode Proof_In in "
23045 & "global refinement", N, Constit_Id);
23046 end if;
23048 Next_Elmt (Constit_Elmt);
23049 end loop;
23051 -- Not one of the constituents appeared as Proof_In
23053 if not Proof_In_Seen then
23054 SPARK_Msg_NE
23055 ("global refinement of state & must include at least one "
23056 & "constituent of mode Proof_In", N, State_Id);
23057 end if;
23058 end Check_Constituent_Usage;
23060 -- Local variables
23062 Item_Elmt : Elmt_Id;
23063 Item_Id : Entity_Id;
23065 -- Start of processing for Check_Proof_In_States
23067 begin
23068 -- Inspect the Proof_In items of the corresponding Global pragma
23069 -- looking for a state with a visible refinement.
23071 if Has_Proof_In_State and then Present (Proof_In_Items) then
23072 Item_Elmt := First_Elmt (Proof_In_Items);
23073 while Present (Item_Elmt) loop
23074 Item_Id := Node (Item_Elmt);
23076 -- Ensure that at least one of the constituents is utilized and
23077 -- is of mode Proof_In
23079 if Ekind (Item_Id) = E_Abstract_State
23080 and then Has_Non_Null_Refinement (Item_Id)
23081 then
23082 Check_Constituent_Usage (Item_Id);
23083 end if;
23085 Next_Elmt (Item_Elmt);
23086 end loop;
23087 end if;
23088 end Check_Proof_In_States;
23090 -------------------------------
23091 -- Check_Refined_Global_List --
23092 -------------------------------
23094 procedure Check_Refined_Global_List
23095 (List : Node_Id;
23096 Global_Mode : Name_Id := Name_Input)
23098 procedure Check_Refined_Global_Item
23099 (Item : Node_Id;
23100 Global_Mode : Name_Id);
23101 -- Verify the legality of a single global item declaration. Parameter
23102 -- Global_Mode denotes the current mode in effect.
23104 -------------------------------
23105 -- Check_Refined_Global_Item --
23106 -------------------------------
23108 procedure Check_Refined_Global_Item
23109 (Item : Node_Id;
23110 Global_Mode : Name_Id)
23112 Item_Id : constant Entity_Id := Entity_Of (Item);
23114 procedure Inconsistent_Mode_Error (Expect : Name_Id);
23115 -- Issue a common error message for all mode mismatches. Expect
23116 -- denotes the expected mode.
23118 -----------------------------
23119 -- Inconsistent_Mode_Error --
23120 -----------------------------
23122 procedure Inconsistent_Mode_Error (Expect : Name_Id) is
23123 begin
23124 SPARK_Msg_NE
23125 ("global item & has inconsistent modes", Item, Item_Id);
23127 Error_Msg_Name_1 := Global_Mode;
23128 Error_Msg_Name_2 := Expect;
23129 SPARK_Msg_N ("\expected mode %, found mode %", Item);
23130 end Inconsistent_Mode_Error;
23132 -- Start of processing for Check_Refined_Global_Item
23134 begin
23135 -- When the state or variable acts as a constituent of another
23136 -- state with a visible refinement, collect it for the state
23137 -- completeness checks performed later on.
23139 if Present (Encapsulating_State (Item_Id))
23140 and then Has_Visible_Refinement (Encapsulating_State (Item_Id))
23141 then
23142 if Global_Mode = Name_Input then
23143 Add_Item (Item_Id, In_Constits);
23145 elsif Global_Mode = Name_In_Out then
23146 Add_Item (Item_Id, In_Out_Constits);
23148 elsif Global_Mode = Name_Output then
23149 Add_Item (Item_Id, Out_Constits);
23151 elsif Global_Mode = Name_Proof_In then
23152 Add_Item (Item_Id, Proof_In_Constits);
23153 end if;
23155 -- When not a constituent, ensure that both occurrences of the
23156 -- item in pragmas Global and Refined_Global match.
23158 elsif Contains (In_Items, Item_Id) then
23159 if Global_Mode /= Name_Input then
23160 Inconsistent_Mode_Error (Name_Input);
23161 end if;
23163 elsif Contains (In_Out_Items, Item_Id) then
23164 if Global_Mode /= Name_In_Out then
23165 Inconsistent_Mode_Error (Name_In_Out);
23166 end if;
23168 elsif Contains (Out_Items, Item_Id) then
23169 if Global_Mode /= Name_Output then
23170 Inconsistent_Mode_Error (Name_Output);
23171 end if;
23173 elsif Contains (Proof_In_Items, Item_Id) then
23174 null;
23176 -- The item does not appear in the corresponding Global pragma,
23177 -- it must be an extra (SPARK RM 7.2.4(3)).
23179 else
23180 SPARK_Msg_NE ("extra global item &", Item, Item_Id);
23181 end if;
23182 end Check_Refined_Global_Item;
23184 -- Local variables
23186 Item : Node_Id;
23188 -- Start of processing for Check_Refined_Global_List
23190 begin
23191 if Nkind (List) = N_Null then
23192 null;
23194 -- Single global item declaration
23196 elsif Nkind_In (List, N_Expanded_Name,
23197 N_Identifier,
23198 N_Selected_Component)
23199 then
23200 Check_Refined_Global_Item (List, Global_Mode);
23202 -- Simple global list or moded global list declaration
23204 elsif Nkind (List) = N_Aggregate then
23206 -- The declaration of a simple global list appear as a collection
23207 -- of expressions.
23209 if Present (Expressions (List)) then
23210 Item := First (Expressions (List));
23211 while Present (Item) loop
23212 Check_Refined_Global_Item (Item, Global_Mode);
23214 Next (Item);
23215 end loop;
23217 -- The declaration of a moded global list appears as a collection
23218 -- of component associations where individual choices denote
23219 -- modes.
23221 elsif Present (Component_Associations (List)) then
23222 Item := First (Component_Associations (List));
23223 while Present (Item) loop
23224 Check_Refined_Global_List
23225 (List => Expression (Item),
23226 Global_Mode => Chars (First (Choices (Item))));
23228 Next (Item);
23229 end loop;
23231 -- Invalid tree
23233 else
23234 raise Program_Error;
23235 end if;
23237 -- Invalid list
23239 else
23240 raise Program_Error;
23241 end if;
23242 end Check_Refined_Global_List;
23244 --------------------------
23245 -- Collect_Global_Items --
23246 --------------------------
23248 procedure Collect_Global_Items (Prag : Node_Id) is
23249 procedure Process_Global_List
23250 (List : Node_Id;
23251 Mode : Name_Id := Name_Input);
23252 -- Collect all items housed in a global list. Formal Mode denotes the
23253 -- current mode in effect.
23255 -------------------------
23256 -- Process_Global_List --
23257 -------------------------
23259 procedure Process_Global_List
23260 (List : Node_Id;
23261 Mode : Name_Id := Name_Input)
23263 procedure Process_Global_Item (Item : Node_Id; Mode : Name_Id);
23264 -- Add a single item to the appropriate list. Formal Mode denotes
23265 -- the current mode in effect.
23267 -------------------------
23268 -- Process_Global_Item --
23269 -------------------------
23271 procedure Process_Global_Item (Item : Node_Id; Mode : Name_Id) is
23272 Item_Id : constant Entity_Id :=
23273 Available_View (Entity_Of (Item));
23274 -- The above handles abstract views of variables and states
23275 -- built for limited with clauses.
23277 begin
23278 -- Signal that the global list contains at least one abstract
23279 -- state with a visible refinement. Note that the refinement
23280 -- may be null in which case there are no constituents.
23282 if Ekind (Item_Id) = E_Abstract_State then
23283 if Has_Null_Refinement (Item_Id) then
23284 Has_Null_State := True;
23286 elsif Has_Non_Null_Refinement (Item_Id) then
23287 if Mode = Name_Input then
23288 Has_In_State := True;
23289 elsif Mode = Name_In_Out then
23290 Has_In_Out_State := True;
23291 elsif Mode = Name_Output then
23292 Has_Out_State := True;
23293 elsif Mode = Name_Proof_In then
23294 Has_Proof_In_State := True;
23295 end if;
23296 end if;
23297 end if;
23299 -- Add the item to the proper list
23301 if Mode = Name_Input then
23302 Add_Item (Item_Id, In_Items);
23303 elsif Mode = Name_In_Out then
23304 Add_Item (Item_Id, In_Out_Items);
23305 elsif Mode = Name_Output then
23306 Add_Item (Item_Id, Out_Items);
23307 elsif Mode = Name_Proof_In then
23308 Add_Item (Item_Id, Proof_In_Items);
23309 end if;
23310 end Process_Global_Item;
23312 -- Local variables
23314 Item : Node_Id;
23316 -- Start of processing for Process_Global_List
23318 begin
23319 if Nkind (List) = N_Null then
23320 null;
23322 -- Single global item declaration
23324 elsif Nkind_In (List, N_Expanded_Name,
23325 N_Identifier,
23326 N_Selected_Component)
23327 then
23328 Process_Global_Item (List, Mode);
23330 -- Single global list or moded global list declaration
23332 elsif Nkind (List) = N_Aggregate then
23334 -- The declaration of a simple global list appear as a
23335 -- collection of expressions.
23337 if Present (Expressions (List)) then
23338 Item := First (Expressions (List));
23339 while Present (Item) loop
23340 Process_Global_Item (Item, Mode);
23341 Next (Item);
23342 end loop;
23344 -- The declaration of a moded global list appears as a
23345 -- collection of component associations where individual
23346 -- choices denote mode.
23348 elsif Present (Component_Associations (List)) then
23349 Item := First (Component_Associations (List));
23350 while Present (Item) loop
23351 Process_Global_List
23352 (List => Expression (Item),
23353 Mode => Chars (First (Choices (Item))));
23355 Next (Item);
23356 end loop;
23358 -- Invalid tree
23360 else
23361 raise Program_Error;
23362 end if;
23364 -- To accomodate partial decoration of disabled SPARK features,
23365 -- this routine may be called with illegal input. If this is the
23366 -- case, do not raise Program_Error.
23368 else
23369 null;
23370 end if;
23371 end Process_Global_List;
23373 -- Start of processing for Collect_Global_Items
23375 begin
23376 Process_Global_List
23377 (Get_Pragma_Arg (First (Pragma_Argument_Associations (Prag))));
23378 end Collect_Global_Items;
23380 -------------------------
23381 -- Present_Then_Remove --
23382 -------------------------
23384 function Present_Then_Remove
23385 (List : Elist_Id;
23386 Item : Entity_Id) return Boolean
23388 Elmt : Elmt_Id;
23390 begin
23391 if Present (List) then
23392 Elmt := First_Elmt (List);
23393 while Present (Elmt) loop
23394 if Node (Elmt) = Item then
23395 Remove_Elmt (List, Elmt);
23396 return True;
23397 end if;
23399 Next_Elmt (Elmt);
23400 end loop;
23401 end if;
23403 return False;
23404 end Present_Then_Remove;
23406 -------------------------------
23407 -- Report_Extra_Constituents --
23408 -------------------------------
23410 procedure Report_Extra_Constituents is
23411 procedure Report_Extra_Constituents_In_List (List : Elist_Id);
23412 -- Emit an error for every element of List
23414 ---------------------------------------
23415 -- Report_Extra_Constituents_In_List --
23416 ---------------------------------------
23418 procedure Report_Extra_Constituents_In_List (List : Elist_Id) is
23419 Constit_Elmt : Elmt_Id;
23421 begin
23422 if Present (List) then
23423 Constit_Elmt := First_Elmt (List);
23424 while Present (Constit_Elmt) loop
23425 SPARK_Msg_NE ("extra constituent &", N, Node (Constit_Elmt));
23426 Next_Elmt (Constit_Elmt);
23427 end loop;
23428 end if;
23429 end Report_Extra_Constituents_In_List;
23431 -- Start of processing for Report_Extra_Constituents
23433 begin
23434 Report_Extra_Constituents_In_List (In_Constits);
23435 Report_Extra_Constituents_In_List (In_Out_Constits);
23436 Report_Extra_Constituents_In_List (Out_Constits);
23437 Report_Extra_Constituents_In_List (Proof_In_Constits);
23438 end Report_Extra_Constituents;
23440 -- Local variables
23442 Body_Decl : constant Node_Id := Find_Related_Subprogram_Or_Body (N);
23443 Errors : constant Nat := Serious_Errors_Detected;
23444 Items : constant Node_Id :=
23445 Get_Pragma_Arg (First (Pragma_Argument_Associations (N)));
23446 Spec_Id : Entity_Id;
23448 -- Start of processing for Analyze_Refined_Global_In_Decl_Part
23450 begin
23451 if Nkind (Body_Decl) = N_Subprogram_Body_Stub then
23452 Spec_Id := Corresponding_Spec_Of_Stub (Body_Decl);
23453 else
23454 Spec_Id := Corresponding_Spec (Body_Decl);
23455 end if;
23457 Global := Get_Pragma (Spec_Id, Pragma_Global);
23459 -- The subprogram declaration lacks pragma Global. This renders
23460 -- Refined_Global useless as there is nothing to refine.
23462 if No (Global) then
23463 SPARK_Msg_NE
23464 ("useless refinement, declaration of subprogram & lacks aspect or "
23465 & "pragma Global", N, Spec_Id);
23466 return;
23467 end if;
23469 -- Extract all relevant items from the corresponding Global pragma
23471 Collect_Global_Items (Global);
23473 -- Corresponding Global pragma must mention at least one state witha
23474 -- visible refinement at the point Refined_Global is processed. States
23475 -- with null refinements need Refined_Global pragma (SPARK RM 7.2.4(2)).
23477 if not Has_In_State
23478 and then not Has_In_Out_State
23479 and then not Has_Out_State
23480 and then not Has_Proof_In_State
23481 and then not Has_Null_State
23482 then
23483 SPARK_Msg_NE
23484 ("useless refinement, subprogram & does not depend on abstract "
23485 & "state with visible refinement", N, Spec_Id);
23486 return;
23487 end if;
23489 -- The global refinement of inputs and outputs cannot be null when the
23490 -- corresponding Global pragma contains at least one item except in the
23491 -- case where we have states with null refinements.
23493 if Nkind (Items) = N_Null
23494 and then
23495 (Present (In_Items)
23496 or else Present (In_Out_Items)
23497 or else Present (Out_Items)
23498 or else Present (Proof_In_Items))
23499 and then not Has_Null_State
23500 then
23501 SPARK_Msg_NE
23502 ("refinement cannot be null, subprogram & has global items",
23503 N, Spec_Id);
23504 return;
23505 end if;
23507 -- Analyze Refined_Global as if it behaved as a regular pragma Global.
23508 -- This ensures that the categorization of all refined global items is
23509 -- consistent with their role.
23511 Analyze_Global_In_Decl_Part (N);
23513 -- Perform all refinement checks with respect to completeness and mode
23514 -- matching.
23516 if Serious_Errors_Detected = Errors then
23517 Check_Refined_Global_List (Items);
23518 end if;
23520 -- For Input states with visible refinement, at least one constituent
23521 -- must be used as an Input in the global refinement.
23523 if Serious_Errors_Detected = Errors then
23524 Check_Input_States;
23525 end if;
23527 -- Verify all possible completion variants for In_Out states with
23528 -- visible refinement.
23530 if Serious_Errors_Detected = Errors then
23531 Check_In_Out_States;
23532 end if;
23534 -- For Output states with visible refinement, all constituents must be
23535 -- used as Outputs in the global refinement.
23537 if Serious_Errors_Detected = Errors then
23538 Check_Output_States;
23539 end if;
23541 -- For Proof_In states with visible refinement, at least one constituent
23542 -- must be used as Proof_In in the global refinement.
23544 if Serious_Errors_Detected = Errors then
23545 Check_Proof_In_States;
23546 end if;
23548 -- Emit errors for all constituents that belong to other states with
23549 -- visible refinement that do not appear in Global.
23551 if Serious_Errors_Detected = Errors then
23552 Report_Extra_Constituents;
23553 end if;
23554 end Analyze_Refined_Global_In_Decl_Part;
23556 ----------------------------------------
23557 -- Analyze_Refined_State_In_Decl_Part --
23558 ----------------------------------------
23560 procedure Analyze_Refined_State_In_Decl_Part (N : Node_Id) is
23561 Available_States : Elist_Id := No_Elist;
23562 -- A list of all abstract states defined in the package declaration that
23563 -- are available for refinement. The list is used to report unrefined
23564 -- states.
23566 Body_Id : Entity_Id;
23567 -- The body entity of the package subject to pragma Refined_State
23569 Body_States : Elist_Id := No_Elist;
23570 -- A list of all hidden states that appear in the body of the related
23571 -- package. The list is used to report unused hidden states.
23573 Constituents_Seen : Elist_Id := No_Elist;
23574 -- A list that contains all constituents processed so far. The list is
23575 -- used to detect multiple uses of the same constituent.
23577 Refined_States_Seen : Elist_Id := No_Elist;
23578 -- A list that contains all refined states processed so far. The list is
23579 -- used to detect duplicate refinements.
23581 Spec_Id : Entity_Id;
23582 -- The spec entity of the package subject to pragma Refined_State
23584 procedure Analyze_Refinement_Clause (Clause : Node_Id);
23585 -- Perform full analysis of a single refinement clause
23587 function Collect_Body_States (Pack_Id : Entity_Id) return Elist_Id;
23588 -- Gather the entities of all abstract states and variables declared in
23589 -- the body state space of package Pack_Id.
23591 procedure Report_Unrefined_States (States : Elist_Id);
23592 -- Emit errors for all unrefined abstract states found in list States
23594 procedure Report_Unused_States (States : Elist_Id);
23595 -- Emit errors for all unused states found in list States
23597 -------------------------------
23598 -- Analyze_Refinement_Clause --
23599 -------------------------------
23601 procedure Analyze_Refinement_Clause (Clause : Node_Id) is
23602 AR_Constit : Entity_Id := Empty;
23603 AW_Constit : Entity_Id := Empty;
23604 ER_Constit : Entity_Id := Empty;
23605 EW_Constit : Entity_Id := Empty;
23606 -- The entities of external constituents that contain one of the
23607 -- following enabled properties: Async_Readers, Async_Writers,
23608 -- Effective_Reads and Effective_Writes.
23610 External_Constit_Seen : Boolean := False;
23611 -- Flag used to mark when at least one external constituent is part
23612 -- of the state refinement.
23614 Non_Null_Seen : Boolean := False;
23615 Null_Seen : Boolean := False;
23616 -- Flags used to detect multiple uses of null in a single clause or a
23617 -- mixture of null and non-null constituents.
23619 Part_Of_Constits : Elist_Id := No_Elist;
23620 -- A list of all candidate constituents subject to indicator Part_Of
23621 -- where the encapsulating state is the current state.
23623 State : Node_Id;
23624 State_Id : Entity_Id;
23625 -- The current state being refined
23627 procedure Analyze_Constituent (Constit : Node_Id);
23628 -- Perform full analysis of a single constituent
23630 procedure Check_External_Property
23631 (Prop_Nam : Name_Id;
23632 Enabled : Boolean;
23633 Constit : Entity_Id);
23634 -- Determine whether a property denoted by name Prop_Nam is present
23635 -- in both the refined state and constituent Constit. Flag Enabled
23636 -- should be set when the property applies to the refined state. If
23637 -- this is not the case, emit an error message.
23639 procedure Check_Matching_State;
23640 -- Determine whether the state being refined appears in list
23641 -- Available_States. Emit an error when attempting to re-refine the
23642 -- state or when the state is not defined in the package declaration,
23643 -- otherwise remove the state from Available_States.
23645 procedure Report_Unused_Constituents (Constits : Elist_Id);
23646 -- Emit errors for all unused Part_Of constituents in list Constits
23648 -------------------------
23649 -- Analyze_Constituent --
23650 -------------------------
23652 procedure Analyze_Constituent (Constit : Node_Id) is
23653 procedure Check_Ghost_Constituent (Constit_Id : Entity_Id);
23654 -- Verify that the constituent Constit_Id is a Ghost entity if the
23655 -- abstract state being refined is also Ghost. If this is the case
23656 -- verify that the Ghost policy in effect at the point of state
23657 -- and constituent declaration is the same.
23659 procedure Check_Matching_Constituent (Constit_Id : Entity_Id);
23660 -- Determine whether constituent Constit denoted by its entity
23661 -- Constit_Id appears in Hidden_States. Emit an error when the
23662 -- constituent is not a valid hidden state of the related package
23663 -- or when it is used more than once. Otherwise remove the
23664 -- constituent from Hidden_States.
23666 --------------------------------
23667 -- Check_Matching_Constituent --
23668 --------------------------------
23670 procedure Check_Matching_Constituent (Constit_Id : Entity_Id) is
23671 procedure Collect_Constituent;
23672 -- Add constituent Constit_Id to the refinements of State_Id
23674 -------------------------
23675 -- Collect_Constituent --
23676 -------------------------
23678 procedure Collect_Constituent is
23679 begin
23680 -- Add the constituent to the list of processed items to aid
23681 -- with the detection of duplicates.
23683 Add_Item (Constit_Id, Constituents_Seen);
23685 -- Collect the constituent in the list of refinement items
23686 -- and establish a relation between the refined state and
23687 -- the item.
23689 Append_Elmt (Constit_Id, Refinement_Constituents (State_Id));
23690 Set_Encapsulating_State (Constit_Id, State_Id);
23692 -- The state has at least one legal constituent, mark the
23693 -- start of the refinement region. The region ends when the
23694 -- body declarations end (see routine Analyze_Declarations).
23696 Set_Has_Visible_Refinement (State_Id);
23698 -- When the constituent is external, save its relevant
23699 -- property for further checks.
23701 if Async_Readers_Enabled (Constit_Id) then
23702 AR_Constit := Constit_Id;
23703 External_Constit_Seen := True;
23704 end if;
23706 if Async_Writers_Enabled (Constit_Id) then
23707 AW_Constit := Constit_Id;
23708 External_Constit_Seen := True;
23709 end if;
23711 if Effective_Reads_Enabled (Constit_Id) then
23712 ER_Constit := Constit_Id;
23713 External_Constit_Seen := True;
23714 end if;
23716 if Effective_Writes_Enabled (Constit_Id) then
23717 EW_Constit := Constit_Id;
23718 External_Constit_Seen := True;
23719 end if;
23720 end Collect_Constituent;
23722 -- Local variables
23724 State_Elmt : Elmt_Id;
23726 -- Start of processing for Check_Matching_Constituent
23728 begin
23729 -- Detect a duplicate use of a constituent
23731 if Contains (Constituents_Seen, Constit_Id) then
23732 SPARK_Msg_NE
23733 ("duplicate use of constituent &", Constit, Constit_Id);
23734 return;
23735 end if;
23737 -- The constituent is subject to a Part_Of indicator
23739 if Present (Encapsulating_State (Constit_Id)) then
23740 if Encapsulating_State (Constit_Id) = State_Id then
23741 Check_Ghost_Constituent (Constit_Id);
23742 Remove (Part_Of_Constits, Constit_Id);
23743 Collect_Constituent;
23745 -- The constituent is part of another state and is used
23746 -- incorrectly in the refinement of the current state.
23748 else
23749 Error_Msg_Name_1 := Chars (State_Id);
23750 SPARK_Msg_NE
23751 ("& cannot act as constituent of state %",
23752 Constit, Constit_Id);
23753 SPARK_Msg_NE
23754 ("\Part_Of indicator specifies & as encapsulating "
23755 & "state", Constit, Encapsulating_State (Constit_Id));
23756 end if;
23758 -- The only other source of legal constituents is the body
23759 -- state space of the related package.
23761 else
23762 if Present (Body_States) then
23763 State_Elmt := First_Elmt (Body_States);
23764 while Present (State_Elmt) loop
23766 -- Consume a valid constituent to signal that it has
23767 -- been encountered.
23769 if Node (State_Elmt) = Constit_Id then
23770 Check_Ghost_Constituent (Constit_Id);
23772 Remove_Elmt (Body_States, State_Elmt);
23773 Collect_Constituent;
23774 return;
23775 end if;
23777 Next_Elmt (State_Elmt);
23778 end loop;
23779 end if;
23781 -- If we get here, then the constituent is not a hidden
23782 -- state of the related package and may not be used in a
23783 -- refinement (SPARK RM 7.2.2(9)).
23785 Error_Msg_Name_1 := Chars (Spec_Id);
23786 SPARK_Msg_NE
23787 ("cannot use & in refinement, constituent is not a hidden "
23788 & "state of package %", Constit, Constit_Id);
23789 end if;
23790 end Check_Matching_Constituent;
23792 -----------------------------
23793 -- Check_Ghost_Constituent --
23794 -----------------------------
23796 procedure Check_Ghost_Constituent (Constit_Id : Entity_Id) is
23797 begin
23798 if Is_Ghost_Entity (State_Id) then
23799 if Is_Ghost_Entity (Constit_Id) then
23801 -- The Ghost policy in effect at the point of abstract
23802 -- state declaration and constituent must match
23803 -- (SPARK RM 6.9(16)).
23805 if Is_Checked_Ghost_Entity (State_Id)
23806 and then Is_Ignored_Ghost_Entity (Constit_Id)
23807 then
23808 Error_Msg_Sloc := Sloc (Constit);
23810 SPARK_Msg_N
23811 ("incompatible ghost policies in effect", State);
23812 SPARK_Msg_NE
23813 ("\abstract state & declared with ghost policy "
23814 & "Check", State, State_Id);
23815 SPARK_Msg_NE
23816 ("\constituent & declared # with ghost policy "
23817 & "Ignore", State, Constit_Id);
23819 elsif Is_Ignored_Ghost_Entity (State_Id)
23820 and then Is_Checked_Ghost_Entity (Constit_Id)
23821 then
23822 Error_Msg_Sloc := Sloc (Constit);
23824 SPARK_Msg_N
23825 ("incompatible ghost policies in effect", State);
23826 SPARK_Msg_NE
23827 ("\abstract state & declared with ghost policy "
23828 & "Ignore", State, State_Id);
23829 SPARK_Msg_NE
23830 ("\constituent & declared # with ghost policy "
23831 & "Check", State, Constit_Id);
23832 end if;
23834 -- A constituent of a Ghost abstract state must be a Ghost
23835 -- entity (SPARK RM 7.2.2(12)).
23837 else
23838 SPARK_Msg_NE
23839 ("constituent of ghost state & must be ghost",
23840 Constit, State_Id);
23841 end if;
23842 end if;
23843 end Check_Ghost_Constituent;
23845 -- Local variables
23847 Constit_Id : Entity_Id;
23849 -- Start of processing for Analyze_Constituent
23851 begin
23852 -- Detect multiple uses of null in a single refinement clause or a
23853 -- mixture of null and non-null constituents.
23855 if Nkind (Constit) = N_Null then
23856 if Null_Seen then
23857 SPARK_Msg_N
23858 ("multiple null constituents not allowed", Constit);
23860 elsif Non_Null_Seen then
23861 SPARK_Msg_N
23862 ("cannot mix null and non-null constituents", Constit);
23864 else
23865 Null_Seen := True;
23867 -- Collect the constituent in the list of refinement items
23869 Append_Elmt (Constit, Refinement_Constituents (State_Id));
23871 -- The state has at least one legal constituent, mark the
23872 -- start of the refinement region. The region ends when the
23873 -- body declarations end (see Analyze_Declarations).
23875 Set_Has_Visible_Refinement (State_Id);
23876 end if;
23878 -- Non-null constituents
23880 else
23881 Non_Null_Seen := True;
23883 if Null_Seen then
23884 SPARK_Msg_N
23885 ("cannot mix null and non-null constituents", Constit);
23886 end if;
23888 Analyze (Constit);
23889 Resolve_State (Constit);
23891 -- Ensure that the constituent denotes a valid state or a
23892 -- whole variable.
23894 if Is_Entity_Name (Constit) then
23895 Constit_Id := Entity_Of (Constit);
23897 if Ekind_In (Constit_Id, E_Abstract_State, E_Variable) then
23898 Check_Matching_Constituent (Constit_Id);
23900 else
23901 SPARK_Msg_NE
23902 ("constituent & must denote a variable or state (SPARK "
23903 & "RM 7.2.2(5))", Constit, Constit_Id);
23904 end if;
23906 -- The constituent is illegal
23908 else
23909 SPARK_Msg_N ("malformed constituent", Constit);
23910 end if;
23911 end if;
23912 end Analyze_Constituent;
23914 -----------------------------
23915 -- Check_External_Property --
23916 -----------------------------
23918 procedure Check_External_Property
23919 (Prop_Nam : Name_Id;
23920 Enabled : Boolean;
23921 Constit : Entity_Id)
23923 begin
23924 Error_Msg_Name_1 := Prop_Nam;
23926 -- The property is enabled in the related Abstract_State pragma
23927 -- that defines the state (SPARK RM 7.2.8(3)).
23929 if Enabled then
23930 if No (Constit) then
23931 SPARK_Msg_NE
23932 ("external state & requires at least one constituent with "
23933 & "property %", State, State_Id);
23934 end if;
23936 -- The property is missing in the declaration of the state, but
23937 -- a constituent is introducing it in the state refinement
23938 -- (SPARK RM 7.2.8(3)).
23940 elsif Present (Constit) then
23941 Error_Msg_Name_2 := Chars (Constit);
23942 SPARK_Msg_NE
23943 ("external state & lacks property % set by constituent %",
23944 State, State_Id);
23945 end if;
23946 end Check_External_Property;
23948 --------------------------
23949 -- Check_Matching_State --
23950 --------------------------
23952 procedure Check_Matching_State is
23953 State_Elmt : Elmt_Id;
23955 begin
23956 -- Detect a duplicate refinement of a state (SPARK RM 7.2.2(8))
23958 if Contains (Refined_States_Seen, State_Id) then
23959 SPARK_Msg_NE
23960 ("duplicate refinement of state &", State, State_Id);
23961 return;
23962 end if;
23964 -- Inspect the abstract states defined in the package declaration
23965 -- looking for a match.
23967 State_Elmt := First_Elmt (Available_States);
23968 while Present (State_Elmt) loop
23970 -- A valid abstract state is being refined in the body. Add
23971 -- the state to the list of processed refined states to aid
23972 -- with the detection of duplicate refinements. Remove the
23973 -- state from Available_States to signal that it has already
23974 -- been refined.
23976 if Node (State_Elmt) = State_Id then
23977 Add_Item (State_Id, Refined_States_Seen);
23978 Remove_Elmt (Available_States, State_Elmt);
23979 return;
23980 end if;
23982 Next_Elmt (State_Elmt);
23983 end loop;
23985 -- If we get here, we are refining a state that is not defined in
23986 -- the package declaration.
23988 Error_Msg_Name_1 := Chars (Spec_Id);
23989 SPARK_Msg_NE
23990 ("cannot refine state, & is not defined in package %",
23991 State, State_Id);
23992 end Check_Matching_State;
23994 --------------------------------
23995 -- Report_Unused_Constituents --
23996 --------------------------------
23998 procedure Report_Unused_Constituents (Constits : Elist_Id) is
23999 Constit_Elmt : Elmt_Id;
24000 Constit_Id : Entity_Id;
24001 Posted : Boolean := False;
24003 begin
24004 if Present (Constits) then
24005 Constit_Elmt := First_Elmt (Constits);
24006 while Present (Constit_Elmt) loop
24007 Constit_Id := Node (Constit_Elmt);
24009 -- Generate an error message of the form:
24011 -- state ... has unused Part_Of constituents
24012 -- abstract state ... defined at ...
24013 -- variable ... defined at ...
24015 if not Posted then
24016 Posted := True;
24017 SPARK_Msg_NE
24018 ("state & has unused Part_Of constituents",
24019 State, State_Id);
24020 end if;
24022 Error_Msg_Sloc := Sloc (Constit_Id);
24024 if Ekind (Constit_Id) = E_Abstract_State then
24025 SPARK_Msg_NE
24026 ("\abstract state & defined #", State, Constit_Id);
24027 else
24028 SPARK_Msg_NE
24029 ("\variable & defined #", State, Constit_Id);
24030 end if;
24032 Next_Elmt (Constit_Elmt);
24033 end loop;
24034 end if;
24035 end Report_Unused_Constituents;
24037 -- Local declarations
24039 Body_Ref : Node_Id;
24040 Body_Ref_Elmt : Elmt_Id;
24041 Constit : Node_Id;
24042 Extra_State : Node_Id;
24044 -- Start of processing for Analyze_Refinement_Clause
24046 begin
24047 -- A refinement clause appears as a component association where the
24048 -- sole choice is the state and the expressions are the constituents.
24049 -- This is a syntax error, always report.
24051 if Nkind (Clause) /= N_Component_Association then
24052 Error_Msg_N ("malformed state refinement clause", Clause);
24053 return;
24054 end if;
24056 -- Analyze the state name of a refinement clause
24058 State := First (Choices (Clause));
24060 Analyze (State);
24061 Resolve_State (State);
24063 -- Ensure that the state name denotes a valid abstract state that is
24064 -- defined in the spec of the related package.
24066 if Is_Entity_Name (State) then
24067 State_Id := Entity_Of (State);
24069 -- Catch any attempts to re-refine a state or refine a state that
24070 -- is not defined in the package declaration.
24072 if Ekind (State_Id) = E_Abstract_State then
24073 Check_Matching_State;
24074 else
24075 SPARK_Msg_NE
24076 ("& must denote an abstract state", State, State_Id);
24077 return;
24078 end if;
24080 -- References to a state with visible refinement are illegal.
24081 -- When nested packages are involved, detecting such references is
24082 -- tricky because pragma Refined_State is analyzed later than the
24083 -- offending pragma Depends or Global. References that occur in
24084 -- such nested context are stored in a list. Emit errors for all
24085 -- references found in Body_References (SPARK RM 6.1.4(8)).
24087 if Present (Body_References (State_Id)) then
24088 Body_Ref_Elmt := First_Elmt (Body_References (State_Id));
24089 while Present (Body_Ref_Elmt) loop
24090 Body_Ref := Node (Body_Ref_Elmt);
24092 SPARK_Msg_N ("reference to & not allowed", Body_Ref);
24093 Error_Msg_Sloc := Sloc (State);
24094 SPARK_Msg_N ("\refinement of & is visible#", Body_Ref);
24096 Next_Elmt (Body_Ref_Elmt);
24097 end loop;
24098 end if;
24100 -- The state name is illegal. This is a syntax error, always report.
24102 else
24103 Error_Msg_N ("malformed state name in refinement clause", State);
24104 return;
24105 end if;
24107 -- A refinement clause may only refine one state at a time
24109 Extra_State := Next (State);
24111 if Present (Extra_State) then
24112 SPARK_Msg_N
24113 ("refinement clause cannot cover multiple states", Extra_State);
24114 end if;
24116 -- Replicate the Part_Of constituents of the refined state because
24117 -- the algorithm will consume items.
24119 Part_Of_Constits := New_Copy_Elist (Part_Of_Constituents (State_Id));
24121 -- Analyze all constituents of the refinement. Multiple constituents
24122 -- appear as an aggregate.
24124 Constit := Expression (Clause);
24126 if Nkind (Constit) = N_Aggregate then
24127 if Present (Component_Associations (Constit)) then
24128 SPARK_Msg_N
24129 ("constituents of refinement clause must appear in "
24130 & "positional form", Constit);
24132 else pragma Assert (Present (Expressions (Constit)));
24133 Constit := First (Expressions (Constit));
24134 while Present (Constit) loop
24135 Analyze_Constituent (Constit);
24137 Next (Constit);
24138 end loop;
24139 end if;
24141 -- Various forms of a single constituent. Note that these may include
24142 -- malformed constituents.
24144 else
24145 Analyze_Constituent (Constit);
24146 end if;
24148 -- A refined external state is subject to special rules with respect
24149 -- to its properties and constituents.
24151 if Is_External_State (State_Id) then
24153 -- The set of properties that all external constituents yield must
24154 -- match that of the refined state. There are two cases to detect:
24155 -- the refined state lacks a property or has an extra property.
24157 if External_Constit_Seen then
24158 Check_External_Property
24159 (Prop_Nam => Name_Async_Readers,
24160 Enabled => Async_Readers_Enabled (State_Id),
24161 Constit => AR_Constit);
24163 Check_External_Property
24164 (Prop_Nam => Name_Async_Writers,
24165 Enabled => Async_Writers_Enabled (State_Id),
24166 Constit => AW_Constit);
24168 Check_External_Property
24169 (Prop_Nam => Name_Effective_Reads,
24170 Enabled => Effective_Reads_Enabled (State_Id),
24171 Constit => ER_Constit);
24173 Check_External_Property
24174 (Prop_Nam => Name_Effective_Writes,
24175 Enabled => Effective_Writes_Enabled (State_Id),
24176 Constit => EW_Constit);
24178 -- An external state may be refined to null (SPARK RM 7.2.8(2))
24180 elsif Null_Seen then
24181 null;
24183 -- The external state has constituents, but none of them are
24184 -- external (SPARK RM 7.2.8(2)).
24186 else
24187 SPARK_Msg_NE
24188 ("external state & requires at least one external "
24189 & "constituent or null refinement", State, State_Id);
24190 end if;
24192 -- When a refined state is not external, it should not have external
24193 -- constituents (SPARK RM 7.2.8(1)).
24195 elsif External_Constit_Seen then
24196 SPARK_Msg_NE
24197 ("non-external state & cannot contain external constituents in "
24198 & "refinement", State, State_Id);
24199 end if;
24201 -- Ensure that all Part_Of candidate constituents have been mentioned
24202 -- in the refinement clause.
24204 Report_Unused_Constituents (Part_Of_Constits);
24205 end Analyze_Refinement_Clause;
24207 -------------------------
24208 -- Collect_Body_States --
24209 -------------------------
24211 function Collect_Body_States (Pack_Id : Entity_Id) return Elist_Id is
24212 Result : Elist_Id := No_Elist;
24213 -- A list containing all body states of Pack_Id
24215 procedure Collect_Visible_States (Pack_Id : Entity_Id);
24216 -- Gather the entities of all abstract states and variables declared
24217 -- in the visible state space of package Pack_Id.
24219 ----------------------------
24220 -- Collect_Visible_States --
24221 ----------------------------
24223 procedure Collect_Visible_States (Pack_Id : Entity_Id) is
24224 Item_Id : Entity_Id;
24226 begin
24227 -- Traverse the entity chain of the package and inspect all
24228 -- visible items.
24230 Item_Id := First_Entity (Pack_Id);
24231 while Present (Item_Id) and then not In_Private_Part (Item_Id) loop
24233 -- Do not consider internally generated items as those cannot
24234 -- be named and participate in refinement.
24236 if not Comes_From_Source (Item_Id) then
24237 null;
24239 elsif Ekind_In (Item_Id, E_Abstract_State, E_Variable) then
24240 Add_Item (Item_Id, Result);
24242 -- Recursively gather the visible states of a nested package
24244 elsif Ekind (Item_Id) = E_Package then
24245 Collect_Visible_States (Item_Id);
24246 end if;
24248 Next_Entity (Item_Id);
24249 end loop;
24250 end Collect_Visible_States;
24252 -- Local variables
24254 Pack_Body : constant Node_Id :=
24255 Declaration_Node (Body_Entity (Pack_Id));
24256 Decl : Node_Id;
24257 Item_Id : Entity_Id;
24259 -- Start of processing for Collect_Body_States
24261 begin
24262 -- Inspect the declarations of the body looking for source variables,
24263 -- packages and package instantiations.
24265 Decl := First (Declarations (Pack_Body));
24266 while Present (Decl) loop
24267 if Nkind (Decl) = N_Object_Declaration then
24268 Item_Id := Defining_Entity (Decl);
24270 -- Capture source variables only as internally generated
24271 -- temporaries cannot be named and participate in refinement.
24273 if Ekind (Item_Id) = E_Variable
24274 and then Comes_From_Source (Item_Id)
24275 then
24276 Add_Item (Item_Id, Result);
24277 end if;
24279 elsif Nkind (Decl) = N_Package_Declaration then
24280 Item_Id := Defining_Entity (Decl);
24282 -- Capture the visible abstract states and variables of a
24283 -- source package [instantiation].
24285 if Comes_From_Source (Item_Id) then
24286 Collect_Visible_States (Item_Id);
24287 end if;
24288 end if;
24290 Next (Decl);
24291 end loop;
24293 return Result;
24294 end Collect_Body_States;
24296 -----------------------------
24297 -- Report_Unrefined_States --
24298 -----------------------------
24300 procedure Report_Unrefined_States (States : Elist_Id) is
24301 State_Elmt : Elmt_Id;
24303 begin
24304 if Present (States) then
24305 State_Elmt := First_Elmt (States);
24306 while Present (State_Elmt) loop
24307 SPARK_Msg_N
24308 ("abstract state & must be refined", Node (State_Elmt));
24310 Next_Elmt (State_Elmt);
24311 end loop;
24312 end if;
24313 end Report_Unrefined_States;
24315 --------------------------
24316 -- Report_Unused_States --
24317 --------------------------
24319 procedure Report_Unused_States (States : Elist_Id) is
24320 Posted : Boolean := False;
24321 State_Elmt : Elmt_Id;
24322 State_Id : Entity_Id;
24324 begin
24325 if Present (States) then
24326 State_Elmt := First_Elmt (States);
24327 while Present (State_Elmt) loop
24328 State_Id := Node (State_Elmt);
24330 -- Generate an error message of the form:
24332 -- body of package ... has unused hidden states
24333 -- abstract state ... defined at ...
24334 -- variable ... defined at ...
24336 if not Posted then
24337 Posted := True;
24338 SPARK_Msg_N
24339 ("body of package & has unused hidden states", Body_Id);
24340 end if;
24342 Error_Msg_Sloc := Sloc (State_Id);
24344 if Ekind (State_Id) = E_Abstract_State then
24345 SPARK_Msg_NE
24346 ("\abstract state & defined #", Body_Id, State_Id);
24347 else
24348 SPARK_Msg_NE
24349 ("\variable & defined #", Body_Id, State_Id);
24350 end if;
24352 Next_Elmt (State_Elmt);
24353 end loop;
24354 end if;
24355 end Report_Unused_States;
24357 -- Local declarations
24359 Body_Decl : constant Node_Id := Parent (N);
24360 Clauses : constant Node_Id :=
24361 Get_Pragma_Arg (First (Pragma_Argument_Associations (N)));
24362 Clause : Node_Id;
24364 -- Start of processing for Analyze_Refined_State_In_Decl_Part
24366 begin
24367 Set_Analyzed (N);
24369 Body_Id := Defining_Entity (Body_Decl);
24370 Spec_Id := Corresponding_Spec (Body_Decl);
24372 -- Replicate the abstract states declared by the package because the
24373 -- matching algorithm will consume states.
24375 Available_States := New_Copy_Elist (Abstract_States (Spec_Id));
24377 -- Gather all abstract states and variables declared in the visible
24378 -- state space of the package body. These items must be utilized as
24379 -- constituents in a state refinement.
24381 Body_States := Collect_Body_States (Spec_Id);
24383 -- Multiple non-null state refinements appear as an aggregate
24385 if Nkind (Clauses) = N_Aggregate then
24386 if Present (Expressions (Clauses)) then
24387 SPARK_Msg_N
24388 ("state refinements must appear as component associations",
24389 Clauses);
24391 else pragma Assert (Present (Component_Associations (Clauses)));
24392 Clause := First (Component_Associations (Clauses));
24393 while Present (Clause) loop
24394 Analyze_Refinement_Clause (Clause);
24396 Next (Clause);
24397 end loop;
24398 end if;
24400 -- Various forms of a single state refinement. Note that these may
24401 -- include malformed refinements.
24403 else
24404 Analyze_Refinement_Clause (Clauses);
24405 end if;
24407 -- List all abstract states that were left unrefined
24409 Report_Unrefined_States (Available_States);
24411 -- Ensure that all abstract states and variables declared in the body
24412 -- state space of the related package are utilized as constituents.
24414 Report_Unused_States (Body_States);
24415 end Analyze_Refined_State_In_Decl_Part;
24417 ------------------------------------
24418 -- Analyze_Test_Case_In_Decl_Part --
24419 ------------------------------------
24421 procedure Analyze_Test_Case_In_Decl_Part (N : Node_Id; S : Entity_Id) is
24422 begin
24423 -- Install formals and push subprogram spec onto scope stack so that we
24424 -- can see the formals from the pragma.
24426 Push_Scope (S);
24427 Install_Formals (S);
24429 -- Preanalyze the boolean expressions, we treat these as spec
24430 -- expressions (i.e. similar to a default expression).
24432 if Pragma_Name (N) = Name_Test_Case then
24433 Preanalyze_CTC_Args
24435 Get_Requires_From_CTC_Pragma (N),
24436 Get_Ensures_From_CTC_Pragma (N));
24437 end if;
24439 -- Remove the subprogram from the scope stack now that the pre-analysis
24440 -- of the expressions in the contract case or test case is done.
24442 End_Scope;
24443 end Analyze_Test_Case_In_Decl_Part;
24445 ----------------
24446 -- Appears_In --
24447 ----------------
24449 function Appears_In (List : Elist_Id; Item_Id : Entity_Id) return Boolean is
24450 Elmt : Elmt_Id;
24451 Id : Entity_Id;
24453 begin
24454 if Present (List) then
24455 Elmt := First_Elmt (List);
24456 while Present (Elmt) loop
24457 if Nkind (Node (Elmt)) = N_Defining_Identifier then
24458 Id := Node (Elmt);
24459 else
24460 Id := Entity_Of (Node (Elmt));
24461 end if;
24463 if Id = Item_Id then
24464 return True;
24465 end if;
24467 Next_Elmt (Elmt);
24468 end loop;
24469 end if;
24471 return False;
24472 end Appears_In;
24474 -----------------------------
24475 -- Check_Applicable_Policy --
24476 -----------------------------
24478 procedure Check_Applicable_Policy (N : Node_Id) is
24479 PP : Node_Id;
24480 Policy : Name_Id;
24482 Ename : constant Name_Id := Original_Aspect_Name (N);
24484 begin
24485 -- No effect if not valid assertion kind name
24487 if not Is_Valid_Assertion_Kind (Ename) then
24488 return;
24489 end if;
24491 -- Loop through entries in check policy list
24493 PP := Opt.Check_Policy_List;
24494 while Present (PP) loop
24495 declare
24496 PPA : constant List_Id := Pragma_Argument_Associations (PP);
24497 Pnm : constant Name_Id := Chars (Get_Pragma_Arg (First (PPA)));
24499 begin
24500 if Ename = Pnm
24501 or else Pnm = Name_Assertion
24502 or else (Pnm = Name_Statement_Assertions
24503 and then Nam_In (Ename, Name_Assert,
24504 Name_Assert_And_Cut,
24505 Name_Assume,
24506 Name_Loop_Invariant,
24507 Name_Loop_Variant))
24508 then
24509 Policy := Chars (Get_Pragma_Arg (Last (PPA)));
24511 case Policy is
24512 when Name_Off | Name_Ignore =>
24513 Set_Is_Ignored (N, True);
24514 Set_Is_Checked (N, False);
24516 when Name_On | Name_Check =>
24517 Set_Is_Checked (N, True);
24518 Set_Is_Ignored (N, False);
24520 when Name_Disable =>
24521 Set_Is_Ignored (N, True);
24522 Set_Is_Checked (N, False);
24523 Set_Is_Disabled (N, True);
24525 -- That should be exhaustive, the null here is a defence
24526 -- against a malformed tree from previous errors.
24528 when others =>
24529 null;
24530 end case;
24532 return;
24533 end if;
24535 PP := Next_Pragma (PP);
24536 end;
24537 end loop;
24539 -- If there are no specific entries that matched, then we let the
24540 -- setting of assertions govern. Note that this provides the needed
24541 -- compatibility with the RM for the cases of assertion, invariant,
24542 -- precondition, predicate, and postcondition.
24544 if Assertions_Enabled then
24545 Set_Is_Checked (N, True);
24546 Set_Is_Ignored (N, False);
24547 else
24548 Set_Is_Checked (N, False);
24549 Set_Is_Ignored (N, True);
24550 end if;
24551 end Check_Applicable_Policy;
24553 -------------------------------
24554 -- Check_External_Properties --
24555 -------------------------------
24557 procedure Check_External_Properties
24558 (Item : Node_Id;
24559 AR : Boolean;
24560 AW : Boolean;
24561 ER : Boolean;
24562 EW : Boolean)
24564 begin
24565 -- All properties enabled
24567 if AR and AW and ER and EW then
24568 null;
24570 -- Async_Readers + Effective_Writes
24571 -- Async_Readers + Async_Writers + Effective_Writes
24573 elsif AR and EW and not ER then
24574 null;
24576 -- Async_Writers + Effective_Reads
24577 -- Async_Readers + Async_Writers + Effective_Reads
24579 elsif AW and ER and not EW then
24580 null;
24582 -- Async_Readers + Async_Writers
24584 elsif AR and AW and not ER and not EW then
24585 null;
24587 -- Async_Readers
24589 elsif AR and not AW and not ER and not EW then
24590 null;
24592 -- Async_Writers
24594 elsif AW and not AR and not ER and not EW then
24595 null;
24597 else
24598 SPARK_Msg_N
24599 ("illegal combination of external properties (SPARK RM 7.1.2(6))",
24600 Item);
24601 end if;
24602 end Check_External_Properties;
24604 ----------------
24605 -- Check_Kind --
24606 ----------------
24608 function Check_Kind (Nam : Name_Id) return Name_Id is
24609 PP : Node_Id;
24611 begin
24612 -- Loop through entries in check policy list
24614 PP := Opt.Check_Policy_List;
24615 while Present (PP) loop
24616 declare
24617 PPA : constant List_Id := Pragma_Argument_Associations (PP);
24618 Pnm : constant Name_Id := Chars (Get_Pragma_Arg (First (PPA)));
24620 begin
24621 if Nam = Pnm
24622 or else (Pnm = Name_Assertion
24623 and then Is_Valid_Assertion_Kind (Nam))
24624 or else (Pnm = Name_Statement_Assertions
24625 and then Nam_In (Nam, Name_Assert,
24626 Name_Assert_And_Cut,
24627 Name_Assume,
24628 Name_Loop_Invariant,
24629 Name_Loop_Variant))
24630 then
24631 case (Chars (Get_Pragma_Arg (Last (PPA)))) is
24632 when Name_On | Name_Check =>
24633 return Name_Check;
24634 when Name_Off | Name_Ignore =>
24635 return Name_Ignore;
24636 when Name_Disable =>
24637 return Name_Disable;
24638 when others =>
24639 raise Program_Error;
24640 end case;
24642 else
24643 PP := Next_Pragma (PP);
24644 end if;
24645 end;
24646 end loop;
24648 -- If there are no specific entries that matched, then we let the
24649 -- setting of assertions govern. Note that this provides the needed
24650 -- compatibility with the RM for the cases of assertion, invariant,
24651 -- precondition, predicate, and postcondition.
24653 if Assertions_Enabled then
24654 return Name_Check;
24655 else
24656 return Name_Ignore;
24657 end if;
24658 end Check_Kind;
24660 ---------------------------
24661 -- Check_Missing_Part_Of --
24662 ---------------------------
24664 procedure Check_Missing_Part_Of (Item_Id : Entity_Id) is
24665 function Has_Visible_State (Pack_Id : Entity_Id) return Boolean;
24666 -- Determine whether a package denoted by Pack_Id declares at least one
24667 -- visible state.
24669 -----------------------
24670 -- Has_Visible_State --
24671 -----------------------
24673 function Has_Visible_State (Pack_Id : Entity_Id) return Boolean is
24674 Item_Id : Entity_Id;
24676 begin
24677 -- Traverse the entity chain of the package trying to find at least
24678 -- one visible abstract state, variable or a package [instantiation]
24679 -- that declares a visible state.
24681 Item_Id := First_Entity (Pack_Id);
24682 while Present (Item_Id)
24683 and then not In_Private_Part (Item_Id)
24684 loop
24685 -- Do not consider internally generated items
24687 if not Comes_From_Source (Item_Id) then
24688 null;
24690 -- A visible state has been found
24692 elsif Ekind_In (Item_Id, E_Abstract_State, E_Variable) then
24693 return True;
24695 -- Recursively peek into nested packages and instantiations
24697 elsif Ekind (Item_Id) = E_Package
24698 and then Has_Visible_State (Item_Id)
24699 then
24700 return True;
24701 end if;
24703 Next_Entity (Item_Id);
24704 end loop;
24706 return False;
24707 end Has_Visible_State;
24709 -- Local variables
24711 Pack_Id : Entity_Id;
24712 Placement : State_Space_Kind;
24714 -- Start of processing for Check_Missing_Part_Of
24716 begin
24717 -- Do not consider abstract states, variables or package instantiations
24718 -- coming from an instance as those always inherit the Part_Of indicator
24719 -- of the instance itself.
24721 if In_Instance then
24722 return;
24724 -- Do not consider internally generated entities as these can never
24725 -- have a Part_Of indicator.
24727 elsif not Comes_From_Source (Item_Id) then
24728 return;
24730 -- Perform these checks only when SPARK_Mode is enabled as they will
24731 -- interfere with standard Ada rules and produce false positives.
24733 elsif SPARK_Mode /= On then
24734 return;
24735 end if;
24737 -- Find where the abstract state, variable or package instantiation
24738 -- lives with respect to the state space.
24740 Find_Placement_In_State_Space
24741 (Item_Id => Item_Id,
24742 Placement => Placement,
24743 Pack_Id => Pack_Id);
24745 -- Items that appear in a non-package construct (subprogram, block, etc)
24746 -- do not require a Part_Of indicator because they can never act as a
24747 -- hidden state.
24749 if Placement = Not_In_Package then
24750 null;
24752 -- An item declared in the body state space of a package always act as a
24753 -- constituent and does not need explicit Part_Of indicator.
24755 elsif Placement = Body_State_Space then
24756 null;
24758 -- In general an item declared in the visible state space of a package
24759 -- does not require a Part_Of indicator. The only exception is when the
24760 -- related package is a private child unit in which case Part_Of must
24761 -- denote a state in the parent unit or in one of its descendants.
24763 elsif Placement = Visible_State_Space then
24764 if Is_Child_Unit (Pack_Id)
24765 and then Is_Private_Descendant (Pack_Id)
24766 then
24767 -- A package instantiation does not need a Part_Of indicator when
24768 -- the related generic template has no visible state.
24770 if Ekind (Item_Id) = E_Package
24771 and then Is_Generic_Instance (Item_Id)
24772 and then not Has_Visible_State (Item_Id)
24773 then
24774 null;
24776 -- All other cases require Part_Of
24778 else
24779 Error_Msg_N
24780 ("indicator Part_Of is required in this context "
24781 & "(SPARK RM 7.2.6(3))", Item_Id);
24782 Error_Msg_Name_1 := Chars (Pack_Id);
24783 Error_Msg_N
24784 ("\& is declared in the visible part of private child "
24785 & "unit %", Item_Id);
24786 end if;
24787 end if;
24789 -- When the item appears in the private state space of a packge, it must
24790 -- be a part of some state declared by the said package.
24792 else pragma Assert (Placement = Private_State_Space);
24794 -- The related package does not declare a state, the item cannot act
24795 -- as a Part_Of constituent.
24797 if No (Get_Pragma (Pack_Id, Pragma_Abstract_State)) then
24798 null;
24800 -- A package instantiation does not need a Part_Of indicator when the
24801 -- related generic template has no visible state.
24803 elsif Ekind (Pack_Id) = E_Package
24804 and then Is_Generic_Instance (Pack_Id)
24805 and then not Has_Visible_State (Pack_Id)
24806 then
24807 null;
24809 -- All other cases require Part_Of
24811 else
24812 Error_Msg_N
24813 ("indicator Part_Of is required in this context "
24814 & "(SPARK RM 7.2.6(2))", Item_Id);
24815 Error_Msg_Name_1 := Chars (Pack_Id);
24816 Error_Msg_N
24817 ("\& is declared in the private part of package %", Item_Id);
24818 end if;
24819 end if;
24820 end Check_Missing_Part_Of;
24822 ---------------------------------
24823 -- Check_SPARK_Aspect_For_ASIS --
24824 ---------------------------------
24826 procedure Check_SPARK_Aspect_For_ASIS (N : Node_Id) is
24827 Expr : Node_Id;
24829 begin
24830 if ASIS_Mode and then From_Aspect_Specification (N) then
24831 Expr := Expression (Corresponding_Aspect (N));
24832 if Nkind (Expr) /= N_Aggregate then
24833 Preanalyze_And_Resolve (Expr);
24835 else
24836 declare
24837 Comps : constant List_Id := Component_Associations (Expr);
24838 Exprs : constant List_Id := Expressions (Expr);
24839 C : Node_Id;
24840 E : Node_Id;
24842 begin
24843 E := First (Exprs);
24844 while Present (E) loop
24845 Analyze (E);
24846 Next (E);
24847 end loop;
24849 C := First (Comps);
24850 while Present (C) loop
24851 Analyze (Expression (C));
24852 Next (C);
24853 end loop;
24854 end;
24855 end if;
24856 end if;
24857 end Check_SPARK_Aspect_For_ASIS;
24859 -------------------------------------
24860 -- Check_State_And_Constituent_Use --
24861 -------------------------------------
24863 procedure Check_State_And_Constituent_Use
24864 (States : Elist_Id;
24865 Constits : Elist_Id;
24866 Context : Node_Id)
24868 function Find_Encapsulating_State
24869 (Constit_Id : Entity_Id) return Entity_Id;
24870 -- Given the entity of a constituent, try to find a corresponding
24871 -- encapsulating state that appears in the same context. The routine
24872 -- returns Empty is no such state is found.
24874 ------------------------------
24875 -- Find_Encapsulating_State --
24876 ------------------------------
24878 function Find_Encapsulating_State
24879 (Constit_Id : Entity_Id) return Entity_Id
24881 State_Id : Entity_Id;
24883 begin
24884 -- Since a constituent may be part of a larger constituent set, climb
24885 -- the encapsulated state chain looking for a state that appears in
24886 -- the same context.
24888 State_Id := Encapsulating_State (Constit_Id);
24889 while Present (State_Id) loop
24890 if Contains (States, State_Id) then
24891 return State_Id;
24892 end if;
24894 State_Id := Encapsulating_State (State_Id);
24895 end loop;
24897 return Empty;
24898 end Find_Encapsulating_State;
24900 -- Local variables
24902 Constit_Elmt : Elmt_Id;
24903 Constit_Id : Entity_Id;
24904 State_Id : Entity_Id;
24906 -- Start of processing for Check_State_And_Constituent_Use
24908 begin
24909 -- Nothing to do if there are no states or constituents
24911 if No (States) or else No (Constits) then
24912 return;
24913 end if;
24915 -- Inspect the list of constituents and try to determine whether its
24916 -- encapsulating state is in list States.
24918 Constit_Elmt := First_Elmt (Constits);
24919 while Present (Constit_Elmt) loop
24920 Constit_Id := Node (Constit_Elmt);
24922 -- Determine whether the constituent is part of an encapsulating
24923 -- state that appears in the same context and if this is the case,
24924 -- emit an error (SPARK RM 7.2.6(7)).
24926 State_Id := Find_Encapsulating_State (Constit_Id);
24928 if Present (State_Id) then
24929 Error_Msg_Name_1 := Chars (Constit_Id);
24930 SPARK_Msg_NE
24931 ("cannot mention state & and its constituent % in the same "
24932 & "context", Context, State_Id);
24933 exit;
24934 end if;
24936 Next_Elmt (Constit_Elmt);
24937 end loop;
24938 end Check_State_And_Constituent_Use;
24940 ---------------------------------------
24941 -- Collect_Subprogram_Inputs_Outputs --
24942 ---------------------------------------
24944 procedure Collect_Subprogram_Inputs_Outputs
24945 (Subp_Id : Entity_Id;
24946 Synthesize : Boolean := False;
24947 Subp_Inputs : in out Elist_Id;
24948 Subp_Outputs : in out Elist_Id;
24949 Global_Seen : out Boolean)
24951 procedure Collect_Dependency_Clause (Clause : Node_Id);
24952 -- Collect all relevant items from a dependency clause
24954 procedure Collect_Global_List
24955 (List : Node_Id;
24956 Mode : Name_Id := Name_Input);
24957 -- Collect all relevant items from a global list
24959 -------------------------------
24960 -- Collect_Dependency_Clause --
24961 -------------------------------
24963 procedure Collect_Dependency_Clause (Clause : Node_Id) is
24964 procedure Collect_Dependency_Item
24965 (Item : Node_Id;
24966 Is_Input : Boolean);
24967 -- Add an item to the proper subprogram input or output collection
24969 -----------------------------
24970 -- Collect_Dependency_Item --
24971 -----------------------------
24973 procedure Collect_Dependency_Item
24974 (Item : Node_Id;
24975 Is_Input : Boolean)
24977 Extra : Node_Id;
24979 begin
24980 -- Nothing to collect when the item is null
24982 if Nkind (Item) = N_Null then
24983 null;
24985 -- Ditto for attribute 'Result
24987 elsif Is_Attribute_Result (Item) then
24988 null;
24990 -- Multiple items appear as an aggregate
24992 elsif Nkind (Item) = N_Aggregate then
24993 Extra := First (Expressions (Item));
24994 while Present (Extra) loop
24995 Collect_Dependency_Item (Extra, Is_Input);
24996 Next (Extra);
24997 end loop;
24999 -- Otherwise this is a solitary item
25001 else
25002 if Is_Input then
25003 Add_Item (Item, Subp_Inputs);
25004 else
25005 Add_Item (Item, Subp_Outputs);
25006 end if;
25007 end if;
25008 end Collect_Dependency_Item;
25010 -- Start of processing for Collect_Dependency_Clause
25012 begin
25013 if Nkind (Clause) = N_Null then
25014 null;
25016 -- A dependency cause appears as component association
25018 elsif Nkind (Clause) = N_Component_Association then
25019 Collect_Dependency_Item
25020 (Expression (Clause), Is_Input => True);
25021 Collect_Dependency_Item
25022 (First (Choices (Clause)), Is_Input => False);
25024 -- To accomodate partial decoration of disabled SPARK features, this
25025 -- routine may be called with illegal input. If this is the case, do
25026 -- not raise Program_Error.
25028 else
25029 null;
25030 end if;
25031 end Collect_Dependency_Clause;
25033 -------------------------
25034 -- Collect_Global_List --
25035 -------------------------
25037 procedure Collect_Global_List
25038 (List : Node_Id;
25039 Mode : Name_Id := Name_Input)
25041 procedure Collect_Global_Item (Item : Node_Id; Mode : Name_Id);
25042 -- Add an item to the proper subprogram input or output collection
25044 -------------------------
25045 -- Collect_Global_Item --
25046 -------------------------
25048 procedure Collect_Global_Item (Item : Node_Id; Mode : Name_Id) is
25049 begin
25050 if Nam_In (Mode, Name_In_Out, Name_Input) then
25051 Add_Item (Item, Subp_Inputs);
25052 end if;
25054 if Nam_In (Mode, Name_In_Out, Name_Output) then
25055 Add_Item (Item, Subp_Outputs);
25056 end if;
25057 end Collect_Global_Item;
25059 -- Local variables
25061 Assoc : Node_Id;
25062 Item : Node_Id;
25064 -- Start of processing for Collect_Global_List
25066 begin
25067 if Nkind (List) = N_Null then
25068 null;
25070 -- Single global item declaration
25072 elsif Nkind_In (List, N_Expanded_Name,
25073 N_Identifier,
25074 N_Selected_Component)
25075 then
25076 Collect_Global_Item (List, Mode);
25078 -- Simple global list or moded global list declaration
25080 elsif Nkind (List) = N_Aggregate then
25081 if Present (Expressions (List)) then
25082 Item := First (Expressions (List));
25083 while Present (Item) loop
25084 Collect_Global_Item (Item, Mode);
25085 Next (Item);
25086 end loop;
25088 else
25089 Assoc := First (Component_Associations (List));
25090 while Present (Assoc) loop
25091 Collect_Global_List
25092 (List => Expression (Assoc),
25093 Mode => Chars (First (Choices (Assoc))));
25094 Next (Assoc);
25095 end loop;
25096 end if;
25098 -- To accomodate partial decoration of disabled SPARK features, this
25099 -- routine may be called with illegal input. If this is the case, do
25100 -- not raise Program_Error.
25102 else
25103 null;
25104 end if;
25105 end Collect_Global_List;
25107 -- Local variables
25109 Subp_Decl : constant Node_Id := Unit_Declaration_Node (Subp_Id);
25110 Clause : Node_Id;
25111 Clauses : Node_Id;
25112 Depends : Node_Id;
25113 Formal : Entity_Id;
25114 Global : Node_Id;
25115 List : Node_Id;
25116 Spec_Id : Entity_Id;
25118 -- Start of processing for Collect_Subprogram_Inputs_Outputs
25120 begin
25121 Global_Seen := False;
25123 -- Find the entity of the corresponding spec when processing a body
25125 if Nkind (Subp_Decl) = N_Subprogram_Body
25126 and then Present (Corresponding_Spec (Subp_Decl))
25127 then
25128 Spec_Id := Corresponding_Spec (Subp_Decl);
25130 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
25131 and then Present (Corresponding_Spec_Of_Stub (Subp_Decl))
25132 then
25133 Spec_Id := Corresponding_Spec_Of_Stub (Subp_Decl);
25135 else
25136 Spec_Id := Subp_Id;
25137 end if;
25139 -- Process all formal parameters
25141 Formal := First_Formal (Spec_Id);
25142 while Present (Formal) loop
25143 if Ekind_In (Formal, E_In_Out_Parameter, E_In_Parameter) then
25144 Add_Item (Formal, Subp_Inputs);
25145 end if;
25147 if Ekind_In (Formal, E_In_Out_Parameter, E_Out_Parameter) then
25148 Add_Item (Formal, Subp_Outputs);
25150 -- Out parameters can act as inputs when the related type is
25151 -- tagged, unconstrained array, unconstrained record or record
25152 -- with unconstrained components.
25154 if Ekind (Formal) = E_Out_Parameter
25155 and then Is_Unconstrained_Or_Tagged_Item (Formal)
25156 then
25157 Add_Item (Formal, Subp_Inputs);
25158 end if;
25159 end if;
25161 Next_Formal (Formal);
25162 end loop;
25164 -- When processing a subprogram body, look for pragmas Refined_Depends
25165 -- and Refined_Global as they specify the inputs and outputs.
25167 if Ekind (Subp_Id) = E_Subprogram_Body then
25168 Depends := Get_Pragma (Subp_Id, Pragma_Refined_Depends);
25169 Global := Get_Pragma (Subp_Id, Pragma_Refined_Global);
25171 -- Subprogram declaration case, look for pragmas Depends and Global
25173 else
25174 Depends := Get_Pragma (Spec_Id, Pragma_Depends);
25175 Global := Get_Pragma (Spec_Id, Pragma_Global);
25176 end if;
25178 -- Pragma [Refined_]Global takes precedence over [Refined_]Depends
25179 -- because it provides finer granularity of inputs and outputs.
25181 if Present (Global) then
25182 Global_Seen := True;
25183 List := Expression (First (Pragma_Argument_Associations (Global)));
25185 -- The pragma may not have been analyzed because of the arbitrary
25186 -- declaration order of aspects. Make sure that it is analyzed for
25187 -- the purposes of item extraction.
25189 if not Analyzed (List) then
25190 if Pragma_Name (Global) = Name_Refined_Global then
25191 Analyze_Refined_Global_In_Decl_Part (Global);
25192 else
25193 Analyze_Global_In_Decl_Part (Global);
25194 end if;
25195 end if;
25197 Collect_Global_List (List);
25199 -- When the related subprogram lacks pragma [Refined_]Global, fall back
25200 -- to [Refined_]Depends if the caller requests this behavior. Synthesize
25201 -- the inputs and outputs from [Refined_]Depends.
25203 elsif Synthesize and then Present (Depends) then
25204 Clauses :=
25205 Get_Pragma_Arg (First (Pragma_Argument_Associations (Depends)));
25207 -- Multiple dependency clauses appear as an aggregate
25209 if Nkind (Clauses) = N_Aggregate then
25210 Clause := First (Component_Associations (Clauses));
25211 while Present (Clause) loop
25212 Collect_Dependency_Clause (Clause);
25213 Next (Clause);
25214 end loop;
25216 -- Otherwise this is a single dependency clause
25218 else
25219 Collect_Dependency_Clause (Clauses);
25220 end if;
25221 end if;
25222 end Collect_Subprogram_Inputs_Outputs;
25224 ---------------------------------
25225 -- Delay_Config_Pragma_Analyze --
25226 ---------------------------------
25228 function Delay_Config_Pragma_Analyze (N : Node_Id) return Boolean is
25229 begin
25230 return Nam_In (Pragma_Name (N), Name_Interrupt_State,
25231 Name_Priority_Specific_Dispatching);
25232 end Delay_Config_Pragma_Analyze;
25234 -------------------------------------
25235 -- Find_Related_Subprogram_Or_Body --
25236 -------------------------------------
25238 function Find_Related_Subprogram_Or_Body
25239 (Prag : Node_Id;
25240 Do_Checks : Boolean := False) return Node_Id
25242 Context : constant Node_Id := Parent (Prag);
25243 Nam : constant Name_Id := Pragma_Name (Prag);
25244 Stmt : Node_Id;
25246 Look_For_Body : constant Boolean :=
25247 Nam_In (Nam, Name_Refined_Depends,
25248 Name_Refined_Global,
25249 Name_Refined_Post);
25250 -- Refinement pragmas must be associated with a subprogram body [stub]
25252 begin
25253 pragma Assert (Nkind (Prag) = N_Pragma);
25255 -- If the pragma is a byproduct of aspect expansion, return the related
25256 -- context of the original aspect.
25258 if Present (Corresponding_Aspect (Prag)) then
25259 return Parent (Corresponding_Aspect (Prag));
25260 end if;
25262 -- Otherwise the pragma is a source construct, most likely part of a
25263 -- declarative list. Skip preceding declarations while looking for a
25264 -- proper subprogram declaration.
25266 pragma Assert (Is_List_Member (Prag));
25268 Stmt := Prev (Prag);
25269 while Present (Stmt) loop
25271 -- Skip prior pragmas, but check for duplicates
25273 if Nkind (Stmt) = N_Pragma then
25274 if Do_Checks and then Pragma_Name (Stmt) = Nam then
25275 Error_Msg_Name_1 := Nam;
25276 Error_Msg_Sloc := Sloc (Stmt);
25277 Error_Msg_N ("pragma % duplicates pragma declared #", Prag);
25278 end if;
25280 -- Emit an error when a refinement pragma appears on an expression
25281 -- function without a completion.
25283 elsif Do_Checks
25284 and then Look_For_Body
25285 and then Nkind (Stmt) = N_Subprogram_Declaration
25286 and then Nkind (Original_Node (Stmt)) = N_Expression_Function
25287 and then not Has_Completion (Defining_Entity (Stmt))
25288 then
25289 Error_Msg_Name_1 := Nam;
25290 Error_Msg_N
25291 ("pragma % cannot apply to a stand alone expression function",
25292 Prag);
25294 return Empty;
25296 -- The refinement pragma applies to a subprogram body stub
25298 elsif Look_For_Body
25299 and then Nkind (Stmt) = N_Subprogram_Body_Stub
25300 then
25301 return Stmt;
25303 -- Skip internally generated code
25305 elsif not Comes_From_Source (Stmt) then
25306 null;
25308 -- Return the current construct which is either a subprogram body,
25309 -- a subprogram declaration or is illegal.
25311 else
25312 return Stmt;
25313 end if;
25315 Prev (Stmt);
25316 end loop;
25318 -- If we fall through, then the pragma was either the first declaration
25319 -- or it was preceded by other pragmas and no source constructs.
25321 -- The pragma is associated with a library-level subprogram
25323 if Nkind (Context) = N_Compilation_Unit_Aux then
25324 return Unit (Parent (Context));
25326 -- The pragma appears inside the declarative part of a subprogram body
25328 elsif Nkind (Context) = N_Subprogram_Body then
25329 return Context;
25331 -- No candidate subprogram [body] found
25333 else
25334 return Empty;
25335 end if;
25336 end Find_Related_Subprogram_Or_Body;
25338 -------------------------
25339 -- Get_Base_Subprogram --
25340 -------------------------
25342 function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id is
25343 Result : Entity_Id;
25345 begin
25346 -- Follow subprogram renaming chain
25348 Result := Def_Id;
25350 if Is_Subprogram (Result)
25351 and then
25352 Nkind (Parent (Declaration_Node (Result))) =
25353 N_Subprogram_Renaming_Declaration
25354 and then Present (Alias (Result))
25355 then
25356 Result := Alias (Result);
25357 end if;
25359 return Result;
25360 end Get_Base_Subprogram;
25362 -----------------------
25363 -- Get_SPARK_Mode_Type --
25364 -----------------------
25366 function Get_SPARK_Mode_Type (N : Name_Id) return SPARK_Mode_Type is
25367 begin
25368 if N = Name_On then
25369 return On;
25370 elsif N = Name_Off then
25371 return Off;
25373 -- Any other argument is illegal
25375 else
25376 raise Program_Error;
25377 end if;
25378 end Get_SPARK_Mode_Type;
25380 --------------------------------
25381 -- Get_SPARK_Mode_From_Pragma --
25382 --------------------------------
25384 function Get_SPARK_Mode_From_Pragma (N : Node_Id) return SPARK_Mode_Type is
25385 Args : List_Id;
25386 Mode : Node_Id;
25388 begin
25389 pragma Assert (Nkind (N) = N_Pragma);
25390 Args := Pragma_Argument_Associations (N);
25392 -- Extract the mode from the argument list
25394 if Present (Args) then
25395 Mode := First (Pragma_Argument_Associations (N));
25396 return Get_SPARK_Mode_Type (Chars (Get_Pragma_Arg (Mode)));
25398 -- If SPARK_Mode pragma has no argument, default is ON
25400 else
25401 return On;
25402 end if;
25403 end Get_SPARK_Mode_From_Pragma;
25405 ---------------------------
25406 -- Has_Extra_Parentheses --
25407 ---------------------------
25409 function Has_Extra_Parentheses (Clause : Node_Id) return Boolean is
25410 Expr : Node_Id;
25412 begin
25413 -- The aggregate should not have an expression list because a clause
25414 -- is always interpreted as a component association. The only way an
25415 -- expression list can sneak in is by adding extra parentheses around
25416 -- the individual clauses:
25418 -- Depends (Output => Input) -- proper form
25419 -- Depends ((Output => Input)) -- extra parentheses
25421 -- Since the extra parentheses are not allowed by the syntax of the
25422 -- pragma, flag them now to avoid emitting misleading errors down the
25423 -- line.
25425 if Nkind (Clause) = N_Aggregate
25426 and then Present (Expressions (Clause))
25427 then
25428 Expr := First (Expressions (Clause));
25429 while Present (Expr) loop
25431 -- A dependency clause surrounded by extra parentheses appears
25432 -- as an aggregate of component associations with an optional
25433 -- Paren_Count set.
25435 if Nkind (Expr) = N_Aggregate
25436 and then Present (Component_Associations (Expr))
25437 then
25438 SPARK_Msg_N
25439 ("dependency clause contains extra parentheses", Expr);
25441 -- Otherwise the expression is a malformed construct
25443 else
25444 SPARK_Msg_N ("malformed dependency clause", Expr);
25445 end if;
25447 Next (Expr);
25448 end loop;
25450 return True;
25451 end if;
25453 return False;
25454 end Has_Extra_Parentheses;
25456 ----------------
25457 -- Initialize --
25458 ----------------
25460 procedure Initialize is
25461 begin
25462 Externals.Init;
25463 end Initialize;
25465 --------
25466 -- ip --
25467 --------
25469 procedure ip is
25470 begin
25471 Dummy := Dummy + 1;
25472 end ip;
25474 -----------------------------
25475 -- Is_Config_Static_String --
25476 -----------------------------
25478 function Is_Config_Static_String (Arg : Node_Id) return Boolean is
25480 function Add_Config_Static_String (Arg : Node_Id) return Boolean;
25481 -- This is an internal recursive function that is just like the outer
25482 -- function except that it adds the string to the name buffer rather
25483 -- than placing the string in the name buffer.
25485 ------------------------------
25486 -- Add_Config_Static_String --
25487 ------------------------------
25489 function Add_Config_Static_String (Arg : Node_Id) return Boolean is
25490 N : Node_Id;
25491 C : Char_Code;
25493 begin
25494 N := Arg;
25496 if Nkind (N) = N_Op_Concat then
25497 if Add_Config_Static_String (Left_Opnd (N)) then
25498 N := Right_Opnd (N);
25499 else
25500 return False;
25501 end if;
25502 end if;
25504 if Nkind (N) /= N_String_Literal then
25505 Error_Msg_N ("string literal expected for pragma argument", N);
25506 return False;
25508 else
25509 for J in 1 .. String_Length (Strval (N)) loop
25510 C := Get_String_Char (Strval (N), J);
25512 if not In_Character_Range (C) then
25513 Error_Msg
25514 ("string literal contains invalid wide character",
25515 Sloc (N) + 1 + Source_Ptr (J));
25516 return False;
25517 end if;
25519 Add_Char_To_Name_Buffer (Get_Character (C));
25520 end loop;
25521 end if;
25523 return True;
25524 end Add_Config_Static_String;
25526 -- Start of processing for Is_Config_Static_String
25528 begin
25529 Name_Len := 0;
25531 return Add_Config_Static_String (Arg);
25532 end Is_Config_Static_String;
25534 -------------------------------
25535 -- Is_Elaboration_SPARK_Mode --
25536 -------------------------------
25538 function Is_Elaboration_SPARK_Mode (N : Node_Id) return Boolean is
25539 begin
25540 pragma Assert
25541 (Nkind (N) = N_Pragma
25542 and then Pragma_Name (N) = Name_SPARK_Mode
25543 and then Is_List_Member (N));
25545 -- Pragma SPARK_Mode affects the elaboration of a package body when it
25546 -- appears in the statement part of the body.
25548 return
25549 Present (Parent (N))
25550 and then Nkind (Parent (N)) = N_Handled_Sequence_Of_Statements
25551 and then List_Containing (N) = Statements (Parent (N))
25552 and then Present (Parent (Parent (N)))
25553 and then Nkind (Parent (Parent (N))) = N_Package_Body;
25554 end Is_Elaboration_SPARK_Mode;
25556 -----------------------------------------
25557 -- Is_Non_Significant_Pragma_Reference --
25558 -----------------------------------------
25560 -- This function makes use of the following static table which indicates
25561 -- whether appearance of some name in a given pragma is to be considered
25562 -- as a reference for the purposes of warnings about unreferenced objects.
25564 -- -1 indicates that appearence in any argument is significant
25565 -- 0 indicates that appearance in any argument is not significant
25566 -- +n indicates that appearance as argument n is significant, but all
25567 -- other arguments are not significant
25568 -- 9n arguments from n on are significant, before n inisignificant
25570 Sig_Flags : constant array (Pragma_Id) of Int :=
25571 (Pragma_Abort_Defer => -1,
25572 Pragma_Abstract_State => -1,
25573 Pragma_Ada_83 => -1,
25574 Pragma_Ada_95 => -1,
25575 Pragma_Ada_05 => -1,
25576 Pragma_Ada_2005 => -1,
25577 Pragma_Ada_12 => -1,
25578 Pragma_Ada_2012 => -1,
25579 Pragma_All_Calls_Remote => -1,
25580 Pragma_Allow_Integer_Address => -1,
25581 Pragma_Annotate => 93,
25582 Pragma_Assert => -1,
25583 Pragma_Assert_And_Cut => -1,
25584 Pragma_Assertion_Policy => 0,
25585 Pragma_Assume => -1,
25586 Pragma_Assume_No_Invalid_Values => 0,
25587 Pragma_Async_Readers => 0,
25588 Pragma_Async_Writers => 0,
25589 Pragma_Asynchronous => 0,
25590 Pragma_Atomic => 0,
25591 Pragma_Atomic_Components => 0,
25592 Pragma_Attach_Handler => -1,
25593 Pragma_Attribute_Definition => 92,
25594 Pragma_Check => -1,
25595 Pragma_Check_Float_Overflow => 0,
25596 Pragma_Check_Name => 0,
25597 Pragma_Check_Policy => 0,
25598 Pragma_CIL_Constructor => 0,
25599 Pragma_CPP_Class => 0,
25600 Pragma_CPP_Constructor => 0,
25601 Pragma_CPP_Virtual => 0,
25602 Pragma_CPP_Vtable => 0,
25603 Pragma_CPU => -1,
25604 Pragma_C_Pass_By_Copy => 0,
25605 Pragma_Comment => -1,
25606 Pragma_Common_Object => 0,
25607 Pragma_Compile_Time_Error => -1,
25608 Pragma_Compile_Time_Warning => -1,
25609 Pragma_Compiler_Unit => -1,
25610 Pragma_Compiler_Unit_Warning => -1,
25611 Pragma_Complete_Representation => 0,
25612 Pragma_Complex_Representation => 0,
25613 Pragma_Component_Alignment => 0,
25614 Pragma_Contract_Cases => -1,
25615 Pragma_Controlled => 0,
25616 Pragma_Convention => 0,
25617 Pragma_Convention_Identifier => 0,
25618 Pragma_Debug => -1,
25619 Pragma_Debug_Policy => 0,
25620 Pragma_Detect_Blocking => 0,
25621 Pragma_Default_Initial_Condition => -1,
25622 Pragma_Default_Scalar_Storage_Order => 0,
25623 Pragma_Default_Storage_Pool => 0,
25624 Pragma_Depends => -1,
25625 Pragma_Disable_Atomic_Synchronization => 0,
25626 Pragma_Discard_Names => 0,
25627 Pragma_Dispatching_Domain => -1,
25628 Pragma_Effective_Reads => 0,
25629 Pragma_Effective_Writes => 0,
25630 Pragma_Elaborate => 0,
25631 Pragma_Elaborate_All => 0,
25632 Pragma_Elaborate_Body => 0,
25633 Pragma_Elaboration_Checks => 0,
25634 Pragma_Eliminate => 0,
25635 Pragma_Enable_Atomic_Synchronization => 0,
25636 Pragma_Export => -1,
25637 Pragma_Export_Function => -1,
25638 Pragma_Export_Object => -1,
25639 Pragma_Export_Procedure => -1,
25640 Pragma_Export_Value => -1,
25641 Pragma_Export_Valued_Procedure => -1,
25642 Pragma_Extend_System => -1,
25643 Pragma_Extensions_Allowed => 0,
25644 Pragma_Extensions_Visible => 0,
25645 Pragma_External => -1,
25646 Pragma_Favor_Top_Level => 0,
25647 Pragma_External_Name_Casing => 0,
25648 Pragma_Fast_Math => 0,
25649 Pragma_Finalize_Storage_Only => 0,
25650 Pragma_Ghost => 0,
25651 Pragma_Global => -1,
25652 Pragma_Ident => -1,
25653 Pragma_Implementation_Defined => -1,
25654 Pragma_Implemented => -1,
25655 Pragma_Implicit_Packing => 0,
25656 Pragma_Import => 93,
25657 Pragma_Import_Function => 0,
25658 Pragma_Import_Object => 0,
25659 Pragma_Import_Procedure => 0,
25660 Pragma_Import_Valued_Procedure => 0,
25661 Pragma_Independent => 0,
25662 Pragma_Independent_Components => 0,
25663 Pragma_Initial_Condition => -1,
25664 Pragma_Initialize_Scalars => 0,
25665 Pragma_Initializes => -1,
25666 Pragma_Inline => 0,
25667 Pragma_Inline_Always => 0,
25668 Pragma_Inline_Generic => 0,
25669 Pragma_Inspection_Point => -1,
25670 Pragma_Interface => 92,
25671 Pragma_Interface_Name => 0,
25672 Pragma_Interrupt_Handler => -1,
25673 Pragma_Interrupt_Priority => -1,
25674 Pragma_Interrupt_State => -1,
25675 Pragma_Invariant => -1,
25676 Pragma_Java_Constructor => -1,
25677 Pragma_Java_Interface => -1,
25678 Pragma_Keep_Names => 0,
25679 Pragma_License => 0,
25680 Pragma_Link_With => -1,
25681 Pragma_Linker_Alias => -1,
25682 Pragma_Linker_Constructor => -1,
25683 Pragma_Linker_Destructor => -1,
25684 Pragma_Linker_Options => -1,
25685 Pragma_Linker_Section => 0,
25686 Pragma_List => 0,
25687 Pragma_Lock_Free => 0,
25688 Pragma_Locking_Policy => 0,
25689 Pragma_Loop_Invariant => -1,
25690 Pragma_Loop_Optimize => 0,
25691 Pragma_Loop_Variant => -1,
25692 Pragma_Machine_Attribute => -1,
25693 Pragma_Main => -1,
25694 Pragma_Main_Storage => -1,
25695 Pragma_Memory_Size => 0,
25696 Pragma_No_Return => 0,
25697 Pragma_No_Body => 0,
25698 Pragma_No_Elaboration_Code_All => 0,
25699 Pragma_No_Inline => 0,
25700 Pragma_No_Run_Time => -1,
25701 Pragma_No_Strict_Aliasing => -1,
25702 Pragma_No_Tagged_Streams => 0,
25703 Pragma_Normalize_Scalars => 0,
25704 Pragma_Obsolescent => 0,
25705 Pragma_Optimize => 0,
25706 Pragma_Optimize_Alignment => 0,
25707 Pragma_Overflow_Mode => 0,
25708 Pragma_Overriding_Renamings => 0,
25709 Pragma_Ordered => 0,
25710 Pragma_Pack => 0,
25711 Pragma_Page => 0,
25712 Pragma_Part_Of => 0,
25713 Pragma_Partition_Elaboration_Policy => 0,
25714 Pragma_Passive => 0,
25715 Pragma_Persistent_BSS => 0,
25716 Pragma_Polling => 0,
25717 Pragma_Prefix_Exception_Messages => 0,
25718 Pragma_Post => -1,
25719 Pragma_Postcondition => -1,
25720 Pragma_Post_Class => -1,
25721 Pragma_Pre => -1,
25722 Pragma_Precondition => -1,
25723 Pragma_Predicate => -1,
25724 Pragma_Preelaborable_Initialization => -1,
25725 Pragma_Preelaborate => 0,
25726 Pragma_Pre_Class => -1,
25727 Pragma_Priority => -1,
25728 Pragma_Priority_Specific_Dispatching => 0,
25729 Pragma_Profile => 0,
25730 Pragma_Profile_Warnings => 0,
25731 Pragma_Propagate_Exceptions => 0,
25732 Pragma_Provide_Shift_Operators => 0,
25733 Pragma_Psect_Object => 0,
25734 Pragma_Pure => 0,
25735 Pragma_Pure_Function => 0,
25736 Pragma_Queuing_Policy => 0,
25737 Pragma_Rational => 0,
25738 Pragma_Ravenscar => 0,
25739 Pragma_Refined_Depends => -1,
25740 Pragma_Refined_Global => -1,
25741 Pragma_Refined_Post => -1,
25742 Pragma_Refined_State => -1,
25743 Pragma_Relative_Deadline => 0,
25744 Pragma_Remote_Access_Type => -1,
25745 Pragma_Remote_Call_Interface => -1,
25746 Pragma_Remote_Types => -1,
25747 Pragma_Restricted_Run_Time => 0,
25748 Pragma_Restriction_Warnings => 0,
25749 Pragma_Restrictions => 0,
25750 Pragma_Reviewable => -1,
25751 Pragma_Short_Circuit_And_Or => 0,
25752 Pragma_Share_Generic => 0,
25753 Pragma_Shared => 0,
25754 Pragma_Shared_Passive => 0,
25755 Pragma_Short_Descriptors => 0,
25756 Pragma_Simple_Storage_Pool_Type => 0,
25757 Pragma_Source_File_Name => 0,
25758 Pragma_Source_File_Name_Project => 0,
25759 Pragma_Source_Reference => 0,
25760 Pragma_SPARK_Mode => 0,
25761 Pragma_Storage_Size => -1,
25762 Pragma_Storage_Unit => 0,
25763 Pragma_Static_Elaboration_Desired => 0,
25764 Pragma_Stream_Convert => 0,
25765 Pragma_Style_Checks => 0,
25766 Pragma_Subtitle => 0,
25767 Pragma_Suppress => 0,
25768 Pragma_Suppress_Exception_Locations => 0,
25769 Pragma_Suppress_All => 0,
25770 Pragma_Suppress_Debug_Info => 0,
25771 Pragma_Suppress_Initialization => 0,
25772 Pragma_System_Name => 0,
25773 Pragma_Task_Dispatching_Policy => 0,
25774 Pragma_Task_Info => -1,
25775 Pragma_Task_Name => -1,
25776 Pragma_Task_Storage => -1,
25777 Pragma_Test_Case => -1,
25778 Pragma_Thread_Local_Storage => -1,
25779 Pragma_Time_Slice => -1,
25780 Pragma_Title => 0,
25781 Pragma_Type_Invariant => -1,
25782 Pragma_Type_Invariant_Class => -1,
25783 Pragma_Unchecked_Union => 0,
25784 Pragma_Unimplemented_Unit => 0,
25785 Pragma_Universal_Aliasing => 0,
25786 Pragma_Universal_Data => 0,
25787 Pragma_Unmodified => 0,
25788 Pragma_Unreferenced => 0,
25789 Pragma_Unreferenced_Objects => 0,
25790 Pragma_Unreserve_All_Interrupts => 0,
25791 Pragma_Unsuppress => 0,
25792 Pragma_Unevaluated_Use_Of_Old => 0,
25793 Pragma_Use_VADS_Size => 0,
25794 Pragma_Validity_Checks => 0,
25795 Pragma_Volatile => 0,
25796 Pragma_Volatile_Components => 0,
25797 Pragma_Warning_As_Error => 0,
25798 Pragma_Warnings => 0,
25799 Pragma_Weak_External => 0,
25800 Pragma_Wide_Character_Encoding => 0,
25801 Unknown_Pragma => 0);
25803 function Is_Non_Significant_Pragma_Reference (N : Node_Id) return Boolean is
25804 Id : Pragma_Id;
25805 P : Node_Id;
25806 C : Int;
25807 AN : Nat;
25809 function Arg_No return Nat;
25810 -- Returns an integer showing what argument we are in. A value of
25811 -- zero means we are not in any of the arguments.
25813 ------------
25814 -- Arg_No --
25815 ------------
25817 function Arg_No return Nat is
25818 A : Node_Id;
25819 N : Nat;
25821 begin
25822 A := First (Pragma_Argument_Associations (Parent (P)));
25823 N := 1;
25824 loop
25825 if No (A) then
25826 return 0;
25827 elsif A = P then
25828 return N;
25829 end if;
25831 Next (A);
25832 N := N + 1;
25833 end loop;
25834 end Arg_No;
25836 -- Start of processing for Non_Significant_Pragma_Reference
25838 begin
25839 P := Parent (N);
25841 if Nkind (P) /= N_Pragma_Argument_Association then
25842 return False;
25844 else
25845 Id := Get_Pragma_Id (Parent (P));
25846 C := Sig_Flags (Id);
25847 AN := Arg_No;
25849 if AN = 0 then
25850 return False;
25851 end if;
25853 case C is
25854 when -1 =>
25855 return False;
25857 when 0 =>
25858 return True;
25860 when 92 .. 99 =>
25861 return AN < (C - 90);
25863 when others =>
25864 return AN /= C;
25865 end case;
25866 end if;
25867 end Is_Non_Significant_Pragma_Reference;
25869 ------------------------------
25870 -- Is_Pragma_String_Literal --
25871 ------------------------------
25873 -- This function returns true if the corresponding pragma argument is a
25874 -- static string expression. These are the only cases in which string
25875 -- literals can appear as pragma arguments. We also allow a string literal
25876 -- as the first argument to pragma Assert (although it will of course
25877 -- always generate a type error).
25879 function Is_Pragma_String_Literal (Par : Node_Id) return Boolean is
25880 Pragn : constant Node_Id := Parent (Par);
25881 Assoc : constant List_Id := Pragma_Argument_Associations (Pragn);
25882 Pname : constant Name_Id := Pragma_Name (Pragn);
25883 Argn : Natural;
25884 N : Node_Id;
25886 begin
25887 Argn := 1;
25888 N := First (Assoc);
25889 loop
25890 exit when N = Par;
25891 Argn := Argn + 1;
25892 Next (N);
25893 end loop;
25895 if Pname = Name_Assert then
25896 return True;
25898 elsif Pname = Name_Export then
25899 return Argn > 2;
25901 elsif Pname = Name_Ident then
25902 return Argn = 1;
25904 elsif Pname = Name_Import then
25905 return Argn > 2;
25907 elsif Pname = Name_Interface_Name then
25908 return Argn > 1;
25910 elsif Pname = Name_Linker_Alias then
25911 return Argn = 2;
25913 elsif Pname = Name_Linker_Section then
25914 return Argn = 2;
25916 elsif Pname = Name_Machine_Attribute then
25917 return Argn = 2;
25919 elsif Pname = Name_Source_File_Name then
25920 return True;
25922 elsif Pname = Name_Source_Reference then
25923 return Argn = 2;
25925 elsif Pname = Name_Title then
25926 return True;
25928 elsif Pname = Name_Subtitle then
25929 return True;
25931 else
25932 return False;
25933 end if;
25934 end Is_Pragma_String_Literal;
25936 ---------------------------
25937 -- Is_Private_SPARK_Mode --
25938 ---------------------------
25940 function Is_Private_SPARK_Mode (N : Node_Id) return Boolean is
25941 begin
25942 pragma Assert
25943 (Nkind (N) = N_Pragma
25944 and then Pragma_Name (N) = Name_SPARK_Mode
25945 and then Is_List_Member (N));
25947 -- For pragma SPARK_Mode to be private, it has to appear in the private
25948 -- declarations of a package.
25950 return
25951 Present (Parent (N))
25952 and then Nkind (Parent (N)) = N_Package_Specification
25953 and then List_Containing (N) = Private_Declarations (Parent (N));
25954 end Is_Private_SPARK_Mode;
25956 -------------------------------------
25957 -- Is_Unconstrained_Or_Tagged_Item --
25958 -------------------------------------
25960 function Is_Unconstrained_Or_Tagged_Item
25961 (Item : Entity_Id) return Boolean
25963 function Has_Unconstrained_Component (Typ : Entity_Id) return Boolean;
25964 -- Determine whether record type Typ has at least one unconstrained
25965 -- component.
25967 ---------------------------------
25968 -- Has_Unconstrained_Component --
25969 ---------------------------------
25971 function Has_Unconstrained_Component (Typ : Entity_Id) return Boolean is
25972 Comp : Entity_Id;
25974 begin
25975 Comp := First_Component (Typ);
25976 while Present (Comp) loop
25977 if Is_Unconstrained_Or_Tagged_Item (Comp) then
25978 return True;
25979 end if;
25981 Next_Component (Comp);
25982 end loop;
25984 return False;
25985 end Has_Unconstrained_Component;
25987 -- Local variables
25989 Typ : constant Entity_Id := Etype (Item);
25991 -- Start of processing for Is_Unconstrained_Or_Tagged_Item
25993 begin
25994 if Is_Tagged_Type (Typ) then
25995 return True;
25997 elsif Is_Array_Type (Typ) and then not Is_Constrained (Typ) then
25998 return True;
26000 elsif Is_Record_Type (Typ) then
26001 if Has_Discriminants (Typ) and then not Is_Constrained (Typ) then
26002 return True;
26003 else
26004 return Has_Unconstrained_Component (Typ);
26005 end if;
26007 elsif Is_Private_Type (Typ) and then Has_Discriminants (Typ) then
26008 return True;
26010 else
26011 return False;
26012 end if;
26013 end Is_Unconstrained_Or_Tagged_Item;
26015 -----------------------------
26016 -- Is_Valid_Assertion_Kind --
26017 -----------------------------
26019 function Is_Valid_Assertion_Kind (Nam : Name_Id) return Boolean is
26020 begin
26021 case Nam is
26022 when
26023 -- RM defined
26025 Name_Assert |
26026 Name_Static_Predicate |
26027 Name_Dynamic_Predicate |
26028 Name_Pre |
26029 Name_uPre |
26030 Name_Post |
26031 Name_uPost |
26032 Name_Type_Invariant |
26033 Name_uType_Invariant |
26035 -- Impl defined
26037 Name_Assert_And_Cut |
26038 Name_Assume |
26039 Name_Contract_Cases |
26040 Name_Debug |
26041 Name_Default_Initial_Condition |
26042 Name_Ghost |
26043 Name_Initial_Condition |
26044 Name_Invariant |
26045 Name_uInvariant |
26046 Name_Loop_Invariant |
26047 Name_Loop_Variant |
26048 Name_Postcondition |
26049 Name_Precondition |
26050 Name_Predicate |
26051 Name_Refined_Post |
26052 Name_Statement_Assertions => return True;
26054 when others => return False;
26055 end case;
26056 end Is_Valid_Assertion_Kind;
26058 -----------------------------------------
26059 -- Make_Aspect_For_PPC_In_Gen_Sub_Decl --
26060 -----------------------------------------
26062 procedure Make_Aspect_For_PPC_In_Gen_Sub_Decl (Decl : Node_Id) is
26063 Aspects : constant List_Id := New_List;
26064 Loc : constant Source_Ptr := Sloc (Decl);
26065 Or_Decl : constant Node_Id := Original_Node (Decl);
26067 Original_Aspects : List_Id;
26068 -- To capture global references, a copy of the created aspects must be
26069 -- inserted in the original tree.
26071 Prag : Node_Id;
26072 Prag_Arg_Ass : Node_Id;
26073 Prag_Id : Pragma_Id;
26075 begin
26076 -- Check for any PPC pragmas that appear within Decl
26078 Prag := Next (Decl);
26079 while Nkind (Prag) = N_Pragma loop
26080 Prag_Id := Get_Pragma_Id (Chars (Pragma_Identifier (Prag)));
26082 case Prag_Id is
26083 when Pragma_Postcondition | Pragma_Precondition =>
26084 Prag_Arg_Ass := First (Pragma_Argument_Associations (Prag));
26086 -- Make an aspect from any PPC pragma
26088 Append_To (Aspects,
26089 Make_Aspect_Specification (Loc,
26090 Identifier =>
26091 Make_Identifier (Loc, Chars (Pragma_Identifier (Prag))),
26092 Expression =>
26093 Copy_Separate_Tree (Expression (Prag_Arg_Ass))));
26095 -- Generate the analysis information in the pragma expression
26096 -- and then set the pragma node analyzed to avoid any further
26097 -- analysis.
26099 Analyze (Expression (Prag_Arg_Ass));
26100 Set_Analyzed (Prag, True);
26102 when others => null;
26103 end case;
26105 Next (Prag);
26106 end loop;
26108 -- Set all new aspects into the generic declaration node
26110 if Is_Non_Empty_List (Aspects) then
26112 -- Create the list of aspects to be inserted in the original tree
26114 Original_Aspects := Copy_Separate_List (Aspects);
26116 -- Check if Decl already has aspects
26118 -- Attach the new lists of aspects to both the generic copy and the
26119 -- original tree.
26121 if Has_Aspects (Decl) then
26122 Append_List (Aspects, Aspect_Specifications (Decl));
26123 Append_List (Original_Aspects, Aspect_Specifications (Or_Decl));
26125 else
26126 Set_Parent (Aspects, Decl);
26127 Set_Aspect_Specifications (Decl, Aspects);
26128 Set_Parent (Original_Aspects, Or_Decl);
26129 Set_Aspect_Specifications (Or_Decl, Original_Aspects);
26130 end if;
26131 end if;
26132 end Make_Aspect_For_PPC_In_Gen_Sub_Decl;
26134 -------------------------
26135 -- Preanalyze_CTC_Args --
26136 -------------------------
26138 procedure Preanalyze_CTC_Args (N, Arg_Req, Arg_Ens : Node_Id) is
26139 begin
26140 -- Preanalyze the boolean expressions, we treat these as spec
26141 -- expressions (i.e. similar to a default expression).
26143 if Present (Arg_Req) then
26144 Preanalyze_Assert_Expression
26145 (Get_Pragma_Arg (Arg_Req), Standard_Boolean);
26147 -- In ASIS mode, for a pragma generated from a source aspect, also
26148 -- analyze the original aspect expression.
26150 if ASIS_Mode and then Present (Corresponding_Aspect (N)) then
26151 Preanalyze_Assert_Expression
26152 (Original_Node (Get_Pragma_Arg (Arg_Req)), Standard_Boolean);
26153 end if;
26154 end if;
26156 if Present (Arg_Ens) then
26157 Preanalyze_Assert_Expression
26158 (Get_Pragma_Arg (Arg_Ens), Standard_Boolean);
26160 -- In ASIS mode, for a pragma generated from a source aspect, also
26161 -- analyze the original aspect expression.
26163 if ASIS_Mode and then Present (Corresponding_Aspect (N)) then
26164 Preanalyze_Assert_Expression
26165 (Original_Node (Get_Pragma_Arg (Arg_Ens)), Standard_Boolean);
26166 end if;
26167 end if;
26168 end Preanalyze_CTC_Args;
26170 --------------------------------------
26171 -- Process_Compilation_Unit_Pragmas --
26172 --------------------------------------
26174 procedure Process_Compilation_Unit_Pragmas (N : Node_Id) is
26175 begin
26176 -- A special check for pragma Suppress_All, a very strange DEC pragma,
26177 -- strange because it comes at the end of the unit. Rational has the
26178 -- same name for a pragma, but treats it as a program unit pragma, In
26179 -- GNAT we just decide to allow it anywhere at all. If it appeared then
26180 -- the flag Has_Pragma_Suppress_All was set on the compilation unit
26181 -- node, and we insert a pragma Suppress (All_Checks) at the start of
26182 -- the context clause to ensure the correct processing.
26184 if Has_Pragma_Suppress_All (N) then
26185 Prepend_To (Context_Items (N),
26186 Make_Pragma (Sloc (N),
26187 Chars => Name_Suppress,
26188 Pragma_Argument_Associations => New_List (
26189 Make_Pragma_Argument_Association (Sloc (N),
26190 Expression => Make_Identifier (Sloc (N), Name_All_Checks)))));
26191 end if;
26193 -- Nothing else to do at the current time
26195 end Process_Compilation_Unit_Pragmas;
26197 ------------------------------------
26198 -- Record_Possible_Body_Reference --
26199 ------------------------------------
26201 procedure Record_Possible_Body_Reference
26202 (State_Id : Entity_Id;
26203 Ref : Node_Id)
26205 Context : Node_Id;
26206 Spec_Id : Entity_Id;
26208 begin
26209 -- Ensure that we are dealing with a reference to a state
26211 pragma Assert (Ekind (State_Id) = E_Abstract_State);
26213 -- Climb the tree starting from the reference looking for a package body
26214 -- whose spec declares the referenced state. This criteria automatically
26215 -- excludes references in package specs which are legal. Note that it is
26216 -- not wise to emit an error now as the package body may lack pragma
26217 -- Refined_State or the referenced state may not be mentioned in the
26218 -- refinement. This approach avoids the generation of misleading errors.
26220 Context := Ref;
26221 while Present (Context) loop
26222 if Nkind (Context) = N_Package_Body then
26223 Spec_Id := Corresponding_Spec (Context);
26225 if Present (Abstract_States (Spec_Id))
26226 and then Contains (Abstract_States (Spec_Id), State_Id)
26227 then
26228 if No (Body_References (State_Id)) then
26229 Set_Body_References (State_Id, New_Elmt_List);
26230 end if;
26232 Append_Elmt (Ref, To => Body_References (State_Id));
26233 exit;
26234 end if;
26235 end if;
26237 Context := Parent (Context);
26238 end loop;
26239 end Record_Possible_Body_Reference;
26241 ------------------------------
26242 -- Relocate_Pragmas_To_Body --
26243 ------------------------------
26245 procedure Relocate_Pragmas_To_Body
26246 (Subp_Body : Node_Id;
26247 Target_Body : Node_Id := Empty)
26249 procedure Relocate_Pragma (Prag : Node_Id);
26250 -- Remove a single pragma from its current list and add it to the
26251 -- declarations of the proper body (either Subp_Body or Target_Body).
26253 ---------------------
26254 -- Relocate_Pragma --
26255 ---------------------
26257 procedure Relocate_Pragma (Prag : Node_Id) is
26258 Decls : List_Id;
26259 Target : Node_Id;
26261 begin
26262 -- When subprogram stubs or expression functions are involves, the
26263 -- destination declaration list belongs to the proper body.
26265 if Present (Target_Body) then
26266 Target := Target_Body;
26267 else
26268 Target := Subp_Body;
26269 end if;
26271 Decls := Declarations (Target);
26273 if No (Decls) then
26274 Decls := New_List;
26275 Set_Declarations (Target, Decls);
26276 end if;
26278 -- Unhook the pragma from its current list
26280 Remove (Prag);
26281 Prepend (Prag, Decls);
26282 end Relocate_Pragma;
26284 -- Local variables
26286 Body_Id : constant Entity_Id :=
26287 Defining_Unit_Name (Specification (Subp_Body));
26288 Next_Stmt : Node_Id;
26289 Stmt : Node_Id;
26291 -- Start of processing for Relocate_Pragmas_To_Body
26293 begin
26294 -- Do not process a body that comes from a separate unit as no construct
26295 -- can possibly follow it.
26297 if not Is_List_Member (Subp_Body) then
26298 return;
26300 -- Do not relocate pragmas that follow a stub if the stub does not have
26301 -- a proper body.
26303 elsif Nkind (Subp_Body) = N_Subprogram_Body_Stub
26304 and then No (Target_Body)
26305 then
26306 return;
26308 -- Do not process internally generated routine _Postconditions
26310 elsif Ekind (Body_Id) = E_Procedure
26311 and then Chars (Body_Id) = Name_uPostconditions
26312 then
26313 return;
26314 end if;
26316 -- Look at what is following the body. We are interested in certain kind
26317 -- of pragmas (either from source or byproducts of expansion) that can
26318 -- apply to a body [stub].
26320 Stmt := Next (Subp_Body);
26321 while Present (Stmt) loop
26323 -- Preserve the following statement for iteration purposes due to a
26324 -- possible relocation of a pragma.
26326 Next_Stmt := Next (Stmt);
26328 -- Move a candidate pragma following the body to the declarations of
26329 -- the body.
26331 if Nkind (Stmt) = N_Pragma
26332 and then Pragma_On_Body_Or_Stub_OK (Get_Pragma_Id (Stmt))
26333 then
26334 Relocate_Pragma (Stmt);
26336 -- Skip internally generated code
26338 elsif not Comes_From_Source (Stmt) then
26339 null;
26341 -- No candidate pragmas are available for relocation
26343 else
26344 exit;
26345 end if;
26347 Stmt := Next_Stmt;
26348 end loop;
26349 end Relocate_Pragmas_To_Body;
26351 -------------------
26352 -- Resolve_State --
26353 -------------------
26355 procedure Resolve_State (N : Node_Id) is
26356 Func : Entity_Id;
26357 State : Entity_Id;
26359 begin
26360 if Is_Entity_Name (N) and then Present (Entity (N)) then
26361 Func := Entity (N);
26363 -- Handle overloading of state names by functions. Traverse the
26364 -- homonym chain looking for an abstract state.
26366 if Ekind (Func) = E_Function and then Has_Homonym (Func) then
26367 State := Homonym (Func);
26368 while Present (State) loop
26370 -- Resolve the overloading by setting the proper entity of the
26371 -- reference to that of the state.
26373 if Ekind (State) = E_Abstract_State then
26374 Set_Etype (N, Standard_Void_Type);
26375 Set_Entity (N, State);
26376 Set_Associated_Node (N, State);
26377 return;
26378 end if;
26380 State := Homonym (State);
26381 end loop;
26383 -- A function can never act as a state. If the homonym chain does
26384 -- not contain a corresponding state, then something went wrong in
26385 -- the overloading mechanism.
26387 raise Program_Error;
26388 end if;
26389 end if;
26390 end Resolve_State;
26392 ----------------------------
26393 -- Rewrite_Assertion_Kind --
26394 ----------------------------
26396 procedure Rewrite_Assertion_Kind (N : Node_Id) is
26397 Nam : Name_Id;
26399 begin
26400 if Nkind (N) = N_Attribute_Reference
26401 and then Attribute_Name (N) = Name_Class
26402 and then Nkind (Prefix (N)) = N_Identifier
26403 then
26404 case Chars (Prefix (N)) is
26405 when Name_Pre =>
26406 Nam := Name_uPre;
26407 when Name_Post =>
26408 Nam := Name_uPost;
26409 when Name_Type_Invariant =>
26410 Nam := Name_uType_Invariant;
26411 when Name_Invariant =>
26412 Nam := Name_uInvariant;
26413 when others =>
26414 return;
26415 end case;
26417 Rewrite (N, Make_Identifier (Sloc (N), Chars => Nam));
26418 end if;
26419 end Rewrite_Assertion_Kind;
26421 --------
26422 -- rv --
26423 --------
26425 procedure rv is
26426 begin
26427 Dummy := Dummy + 1;
26428 end rv;
26430 --------------------------------
26431 -- Set_Encoded_Interface_Name --
26432 --------------------------------
26434 procedure Set_Encoded_Interface_Name (E : Entity_Id; S : Node_Id) is
26435 Str : constant String_Id := Strval (S);
26436 Len : constant Int := String_Length (Str);
26437 CC : Char_Code;
26438 C : Character;
26439 J : Int;
26441 Hex : constant array (0 .. 15) of Character := "0123456789abcdef";
26443 procedure Encode;
26444 -- Stores encoded value of character code CC. The encoding we use an
26445 -- underscore followed by four lower case hex digits.
26447 ------------
26448 -- Encode --
26449 ------------
26451 procedure Encode is
26452 begin
26453 Store_String_Char (Get_Char_Code ('_'));
26454 Store_String_Char
26455 (Get_Char_Code (Hex (Integer (CC / 2 ** 12))));
26456 Store_String_Char
26457 (Get_Char_Code (Hex (Integer (CC / 2 ** 8 and 16#0F#))));
26458 Store_String_Char
26459 (Get_Char_Code (Hex (Integer (CC / 2 ** 4 and 16#0F#))));
26460 Store_String_Char
26461 (Get_Char_Code (Hex (Integer (CC and 16#0F#))));
26462 end Encode;
26464 -- Start of processing for Set_Encoded_Interface_Name
26466 begin
26467 -- If first character is asterisk, this is a link name, and we leave it
26468 -- completely unmodified. We also ignore null strings (the latter case
26469 -- happens only in error cases) and no encoding should occur for Java or
26470 -- AAMP interface names.
26472 if Len = 0
26473 or else Get_String_Char (Str, 1) = Get_Char_Code ('*')
26474 or else VM_Target /= No_VM
26475 or else AAMP_On_Target
26476 then
26477 Set_Interface_Name (E, S);
26479 else
26480 J := 1;
26481 loop
26482 CC := Get_String_Char (Str, J);
26484 exit when not In_Character_Range (CC);
26486 C := Get_Character (CC);
26488 exit when C /= '_' and then C /= '$'
26489 and then C not in '0' .. '9'
26490 and then C not in 'a' .. 'z'
26491 and then C not in 'A' .. 'Z';
26493 if J = Len then
26494 Set_Interface_Name (E, S);
26495 return;
26497 else
26498 J := J + 1;
26499 end if;
26500 end loop;
26502 -- Here we need to encode. The encoding we use as follows:
26503 -- three underscores + four hex digits (lower case)
26505 Start_String;
26507 for J in 1 .. String_Length (Str) loop
26508 CC := Get_String_Char (Str, J);
26510 if not In_Character_Range (CC) then
26511 Encode;
26512 else
26513 C := Get_Character (CC);
26515 if C = '_' or else C = '$'
26516 or else C in '0' .. '9'
26517 or else C in 'a' .. 'z'
26518 or else C in 'A' .. 'Z'
26519 then
26520 Store_String_Char (CC);
26521 else
26522 Encode;
26523 end if;
26524 end if;
26525 end loop;
26527 Set_Interface_Name (E,
26528 Make_String_Literal (Sloc (S),
26529 Strval => End_String));
26530 end if;
26531 end Set_Encoded_Interface_Name;
26533 -------------------
26534 -- Set_Unit_Name --
26535 -------------------
26537 procedure Set_Unit_Name (N : Node_Id; With_Item : Node_Id) is
26538 Pref : Node_Id;
26539 Scop : Entity_Id;
26541 begin
26542 if Nkind (N) = N_Identifier
26543 and then Nkind (With_Item) = N_Identifier
26544 then
26545 Set_Entity (N, Entity (With_Item));
26547 elsif Nkind (N) = N_Selected_Component then
26548 Change_Selected_Component_To_Expanded_Name (N);
26549 Set_Entity (N, Entity (With_Item));
26550 Set_Entity (Selector_Name (N), Entity (N));
26552 Pref := Prefix (N);
26553 Scop := Scope (Entity (N));
26554 while Nkind (Pref) = N_Selected_Component loop
26555 Change_Selected_Component_To_Expanded_Name (Pref);
26556 Set_Entity (Selector_Name (Pref), Scop);
26557 Set_Entity (Pref, Scop);
26558 Pref := Prefix (Pref);
26559 Scop := Scope (Scop);
26560 end loop;
26562 Set_Entity (Pref, Scop);
26563 end if;
26564 end Set_Unit_Name;
26566 end Sem_Prag;