* libgnarl/a-intnam__rtems.ads: Update copyright date.
[official-gcc.git] / gcc / ada / sem_util.adb
blob6dc3591b9734f47fd4549c87a08e1c74d8631e52
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- S E M _ U T I L --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2017, 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 with Treepr; -- ???For debugging code below
28 with Aspects; use Aspects;
29 with Atree; use Atree;
30 with Casing; use Casing;
31 with Checks; use Checks;
32 with Debug; use Debug;
33 with Elists; use Elists;
34 with Errout; use Errout;
35 with Erroutc; use Erroutc;
36 with Exp_Ch11; use Exp_Ch11;
37 with Exp_Disp; use Exp_Disp;
38 with Exp_Util; use Exp_Util;
39 with Fname; use Fname;
40 with Freeze; use Freeze;
41 with Lib; use Lib;
42 with Lib.Xref; use Lib.Xref;
43 with Namet.Sp; use Namet.Sp;
44 with Nlists; use Nlists;
45 with Nmake; use Nmake;
46 with Output; use Output;
47 with Restrict; use Restrict;
48 with Rident; use Rident;
49 with Rtsfind; use Rtsfind;
50 with Sem; use Sem;
51 with Sem_Aux; use Sem_Aux;
52 with Sem_Attr; use Sem_Attr;
53 with Sem_Ch6; use Sem_Ch6;
54 with Sem_Ch8; use Sem_Ch8;
55 with Sem_Disp; use Sem_Disp;
56 with Sem_Eval; use Sem_Eval;
57 with Sem_Prag; use Sem_Prag;
58 with Sem_Res; use Sem_Res;
59 with Sem_Warn; use Sem_Warn;
60 with Sem_Type; use Sem_Type;
61 with Sinfo; use Sinfo;
62 with Sinput; use Sinput;
63 with Stand; use Stand;
64 with Style;
65 with Stringt; use Stringt;
66 with Targparm; use Targparm;
67 with Tbuild; use Tbuild;
68 with Ttypes; use Ttypes;
69 with Uname; use Uname;
71 with GNAT.HTable; use GNAT.HTable;
73 package body Sem_Util is
75 -----------------------
76 -- Local Subprograms --
77 -----------------------
79 function Build_Component_Subtype
80 (C : List_Id;
81 Loc : Source_Ptr;
82 T : Entity_Id) return Node_Id;
83 -- This function builds the subtype for Build_Actual_Subtype_Of_Component
84 -- and Build_Discriminal_Subtype_Of_Component. C is a list of constraints,
85 -- Loc is the source location, T is the original subtype.
87 function Has_Enabled_Property
88 (Item_Id : Entity_Id;
89 Property : Name_Id) return Boolean;
90 -- Subsidiary to routines Async_xxx_Enabled and Effective_xxx_Enabled.
91 -- Determine whether an abstract state or a variable denoted by entity
92 -- Item_Id has enabled property Property.
94 function Has_Null_Extension (T : Entity_Id) return Boolean;
95 -- T is a derived tagged type. Check whether the type extension is null.
96 -- If the parent type is fully initialized, T can be treated as such.
98 function Is_Fully_Initialized_Variant (Typ : Entity_Id) return Boolean;
99 -- Subsidiary to Is_Fully_Initialized_Type. For an unconstrained type
100 -- with discriminants whose default values are static, examine only the
101 -- components in the selected variant to determine whether all of them
102 -- have a default.
104 type Null_Status_Kind is
105 (Is_Null,
106 -- This value indicates that a subexpression is known to have a null
107 -- value at compile time.
109 Is_Non_Null,
110 -- This value indicates that a subexpression is known to have a non-null
111 -- value at compile time.
113 Unknown);
114 -- This value indicates that it cannot be determined at compile time
115 -- whether a subexpression yields a null or non-null value.
117 function Null_Status (N : Node_Id) return Null_Status_Kind;
118 -- Determine whether subexpression N of an access type yields a null value,
119 -- a non-null value, or the value cannot be determined at compile time. The
120 -- routine does not take simple flow diagnostics into account, it relies on
121 -- static facts such as the presence of null exclusions.
123 function Old_Requires_Transient_Scope (Id : Entity_Id) return Boolean;
124 function New_Requires_Transient_Scope (Id : Entity_Id) return Boolean;
125 -- ???We retain the old and new algorithms for Requires_Transient_Scope for
126 -- the time being. New_Requires_Transient_Scope is used by default; the
127 -- debug switch -gnatdQ can be used to do Old_Requires_Transient_Scope
128 -- instead. The intent is to use this temporarily to measure before/after
129 -- efficiency. Note: when this temporary code is removed, the documentation
130 -- of dQ in debug.adb should be removed.
132 procedure Results_Differ
133 (Id : Entity_Id;
134 Old_Val : Boolean;
135 New_Val : Boolean);
136 -- ???Debugging code. Called when the Old_Val and New_Val differ. This
137 -- routine will be removed eventially when New_Requires_Transient_Scope
138 -- becomes Requires_Transient_Scope and Old_Requires_Transient_Scope is
139 -- eliminated.
141 function Subprogram_Name (N : Node_Id) return String;
142 -- Return the fully qualified name of the enclosing subprogram for the
143 -- given node N.
145 ------------------------------
146 -- Abstract_Interface_List --
147 ------------------------------
149 function Abstract_Interface_List (Typ : Entity_Id) return List_Id is
150 Nod : Node_Id;
152 begin
153 if Is_Concurrent_Type (Typ) then
155 -- If we are dealing with a synchronized subtype, go to the base
156 -- type, whose declaration has the interface list.
158 -- Shouldn't this be Declaration_Node???
160 Nod := Parent (Base_Type (Typ));
162 if Nkind (Nod) = N_Full_Type_Declaration then
163 return Empty_List;
164 end if;
166 elsif Ekind (Typ) = E_Record_Type_With_Private then
167 if Nkind (Parent (Typ)) = N_Full_Type_Declaration then
168 Nod := Type_Definition (Parent (Typ));
170 elsif Nkind (Parent (Typ)) = N_Private_Type_Declaration then
171 if Present (Full_View (Typ))
172 and then
173 Nkind (Parent (Full_View (Typ))) = N_Full_Type_Declaration
174 then
175 Nod := Type_Definition (Parent (Full_View (Typ)));
177 -- If the full-view is not available we cannot do anything else
178 -- here (the source has errors).
180 else
181 return Empty_List;
182 end if;
184 -- Support for generic formals with interfaces is still missing ???
186 elsif Nkind (Parent (Typ)) = N_Formal_Type_Declaration then
187 return Empty_List;
189 else
190 pragma Assert
191 (Nkind (Parent (Typ)) = N_Private_Extension_Declaration);
192 Nod := Parent (Typ);
193 end if;
195 elsif Ekind (Typ) = E_Record_Subtype then
196 Nod := Type_Definition (Parent (Etype (Typ)));
198 elsif Ekind (Typ) = E_Record_Subtype_With_Private then
200 -- Recurse, because parent may still be a private extension. Also
201 -- note that the full view of the subtype or the full view of its
202 -- base type may (both) be unavailable.
204 return Abstract_Interface_List (Etype (Typ));
206 elsif Ekind (Typ) = E_Record_Type then
207 if Nkind (Parent (Typ)) = N_Formal_Type_Declaration then
208 Nod := Formal_Type_Definition (Parent (Typ));
209 else
210 Nod := Type_Definition (Parent (Typ));
211 end if;
213 -- Otherwise the type is of a kind which does not implement interfaces
215 else
216 return Empty_List;
217 end if;
219 return Interface_List (Nod);
220 end Abstract_Interface_List;
222 --------------------------------
223 -- Add_Access_Type_To_Process --
224 --------------------------------
226 procedure Add_Access_Type_To_Process (E : Entity_Id; A : Entity_Id) is
227 L : Elist_Id;
229 begin
230 Ensure_Freeze_Node (E);
231 L := Access_Types_To_Process (Freeze_Node (E));
233 if No (L) then
234 L := New_Elmt_List;
235 Set_Access_Types_To_Process (Freeze_Node (E), L);
236 end if;
238 Append_Elmt (A, L);
239 end Add_Access_Type_To_Process;
241 --------------------------
242 -- Add_Block_Identifier --
243 --------------------------
245 procedure Add_Block_Identifier (N : Node_Id; Id : out Entity_Id) is
246 Loc : constant Source_Ptr := Sloc (N);
248 begin
249 pragma Assert (Nkind (N) = N_Block_Statement);
251 -- The block already has a label, return its entity
253 if Present (Identifier (N)) then
254 Id := Entity (Identifier (N));
256 -- Create a new block label and set its attributes
258 else
259 Id := New_Internal_Entity (E_Block, Current_Scope, Loc, 'B');
260 Set_Etype (Id, Standard_Void_Type);
261 Set_Parent (Id, N);
263 Set_Identifier (N, New_Occurrence_Of (Id, Loc));
264 Set_Block_Node (Id, Identifier (N));
265 end if;
266 end Add_Block_Identifier;
268 ----------------------------
269 -- Add_Global_Declaration --
270 ----------------------------
272 procedure Add_Global_Declaration (N : Node_Id) is
273 Aux_Node : constant Node_Id := Aux_Decls_Node (Cunit (Current_Sem_Unit));
275 begin
276 if No (Declarations (Aux_Node)) then
277 Set_Declarations (Aux_Node, New_List);
278 end if;
280 Append_To (Declarations (Aux_Node), N);
281 Analyze (N);
282 end Add_Global_Declaration;
284 --------------------------------
285 -- Address_Integer_Convert_OK --
286 --------------------------------
288 function Address_Integer_Convert_OK (T1, T2 : Entity_Id) return Boolean is
289 begin
290 if Allow_Integer_Address
291 and then ((Is_Descendant_Of_Address (T1)
292 and then Is_Private_Type (T1)
293 and then Is_Integer_Type (T2))
294 or else
295 (Is_Descendant_Of_Address (T2)
296 and then Is_Private_Type (T2)
297 and then Is_Integer_Type (T1)))
298 then
299 return True;
300 else
301 return False;
302 end if;
303 end Address_Integer_Convert_OK;
305 -------------------
306 -- Address_Value --
307 -------------------
309 function Address_Value (N : Node_Id) return Node_Id is
310 Expr : Node_Id := N;
312 begin
313 loop
314 -- For constant, get constant expression
316 if Is_Entity_Name (Expr)
317 and then Ekind (Entity (Expr)) = E_Constant
318 then
319 Expr := Constant_Value (Entity (Expr));
321 -- For unchecked conversion, get result to convert
323 elsif Nkind (Expr) = N_Unchecked_Type_Conversion then
324 Expr := Expression (Expr);
326 -- For (common case) of To_Address call, get argument
328 elsif Nkind (Expr) = N_Function_Call
329 and then Is_Entity_Name (Name (Expr))
330 and then Is_RTE (Entity (Name (Expr)), RE_To_Address)
331 then
332 Expr := First (Parameter_Associations (Expr));
334 if Nkind (Expr) = N_Parameter_Association then
335 Expr := Explicit_Actual_Parameter (Expr);
336 end if;
338 -- We finally have the real expression
340 else
341 exit;
342 end if;
343 end loop;
345 return Expr;
346 end Address_Value;
348 -----------------
349 -- Addressable --
350 -----------------
352 -- For now, just 8/16/32/64
354 function Addressable (V : Uint) return Boolean is
355 begin
356 return V = Uint_8 or else
357 V = Uint_16 or else
358 V = Uint_32 or else
359 V = Uint_64;
360 end Addressable;
362 function Addressable (V : Int) return Boolean is
363 begin
364 return V = 8 or else
365 V = 16 or else
366 V = 32 or else
367 V = 64;
368 end Addressable;
370 ---------------------------------
371 -- Aggregate_Constraint_Checks --
372 ---------------------------------
374 procedure Aggregate_Constraint_Checks
375 (Exp : Node_Id;
376 Check_Typ : Entity_Id)
378 Exp_Typ : constant Entity_Id := Etype (Exp);
380 begin
381 if Raises_Constraint_Error (Exp) then
382 return;
383 end if;
385 -- Ada 2005 (AI-230): Generate a conversion to an anonymous access
386 -- component's type to force the appropriate accessibility checks.
388 -- Ada 2005 (AI-231): Generate conversion to the null-excluding type to
389 -- force the corresponding run-time check
391 if Is_Access_Type (Check_Typ)
392 and then Is_Local_Anonymous_Access (Check_Typ)
393 then
394 Rewrite (Exp, Convert_To (Check_Typ, Relocate_Node (Exp)));
395 Analyze_And_Resolve (Exp, Check_Typ);
396 Check_Unset_Reference (Exp);
397 end if;
399 -- What follows is really expansion activity, so check that expansion
400 -- is on and is allowed. In GNATprove mode, we also want check flags to
401 -- be added in the tree, so that the formal verification can rely on
402 -- those to be present. In GNATprove mode for formal verification, some
403 -- treatment typically only done during expansion needs to be performed
404 -- on the tree, but it should not be applied inside generics. Otherwise,
405 -- this breaks the name resolution mechanism for generic instances.
407 if not Expander_Active
408 and (Inside_A_Generic or not Full_Analysis or not GNATprove_Mode)
409 then
410 return;
411 end if;
413 if Is_Access_Type (Check_Typ)
414 and then Can_Never_Be_Null (Check_Typ)
415 and then not Can_Never_Be_Null (Exp_Typ)
416 then
417 Install_Null_Excluding_Check (Exp);
418 end if;
420 -- First check if we have to insert discriminant checks
422 if Has_Discriminants (Exp_Typ) then
423 Apply_Discriminant_Check (Exp, Check_Typ);
425 -- Next emit length checks for array aggregates
427 elsif Is_Array_Type (Exp_Typ) then
428 Apply_Length_Check (Exp, Check_Typ);
430 -- Finally emit scalar and string checks. If we are dealing with a
431 -- scalar literal we need to check by hand because the Etype of
432 -- literals is not necessarily correct.
434 elsif Is_Scalar_Type (Exp_Typ)
435 and then Compile_Time_Known_Value (Exp)
436 then
437 if Is_Out_Of_Range (Exp, Base_Type (Check_Typ)) then
438 Apply_Compile_Time_Constraint_Error
439 (Exp, "value not in range of}??", CE_Range_Check_Failed,
440 Ent => Base_Type (Check_Typ),
441 Typ => Base_Type (Check_Typ));
443 elsif Is_Out_Of_Range (Exp, Check_Typ) then
444 Apply_Compile_Time_Constraint_Error
445 (Exp, "value not in range of}??", CE_Range_Check_Failed,
446 Ent => Check_Typ,
447 Typ => Check_Typ);
449 elsif not Range_Checks_Suppressed (Check_Typ) then
450 Apply_Scalar_Range_Check (Exp, Check_Typ);
451 end if;
453 -- Verify that target type is also scalar, to prevent view anomalies
454 -- in instantiations.
456 elsif (Is_Scalar_Type (Exp_Typ)
457 or else Nkind (Exp) = N_String_Literal)
458 and then Is_Scalar_Type (Check_Typ)
459 and then Exp_Typ /= Check_Typ
460 then
461 if Is_Entity_Name (Exp)
462 and then Ekind (Entity (Exp)) = E_Constant
463 then
464 -- If expression is a constant, it is worthwhile checking whether
465 -- it is a bound of the type.
467 if (Is_Entity_Name (Type_Low_Bound (Check_Typ))
468 and then Entity (Exp) = Entity (Type_Low_Bound (Check_Typ)))
469 or else
470 (Is_Entity_Name (Type_High_Bound (Check_Typ))
471 and then Entity (Exp) = Entity (Type_High_Bound (Check_Typ)))
472 then
473 return;
475 else
476 Rewrite (Exp, Convert_To (Check_Typ, Relocate_Node (Exp)));
477 Analyze_And_Resolve (Exp, Check_Typ);
478 Check_Unset_Reference (Exp);
479 end if;
481 -- Could use a comment on this case ???
483 else
484 Rewrite (Exp, Convert_To (Check_Typ, Relocate_Node (Exp)));
485 Analyze_And_Resolve (Exp, Check_Typ);
486 Check_Unset_Reference (Exp);
487 end if;
489 end if;
490 end Aggregate_Constraint_Checks;
492 -----------------------
493 -- Alignment_In_Bits --
494 -----------------------
496 function Alignment_In_Bits (E : Entity_Id) return Uint is
497 begin
498 return Alignment (E) * System_Storage_Unit;
499 end Alignment_In_Bits;
501 --------------------------------------
502 -- All_Composite_Constraints_Static --
503 --------------------------------------
505 function All_Composite_Constraints_Static
506 (Constr : Node_Id) return Boolean
508 begin
509 if No (Constr) or else Error_Posted (Constr) then
510 return True;
511 end if;
513 case Nkind (Constr) is
514 when N_Subexpr =>
515 if Nkind (Constr) in N_Has_Entity
516 and then Present (Entity (Constr))
517 then
518 if Is_Type (Entity (Constr)) then
519 return
520 not Is_Discrete_Type (Entity (Constr))
521 or else Is_OK_Static_Subtype (Entity (Constr));
522 end if;
524 elsif Nkind (Constr) = N_Range then
525 return
526 Is_OK_Static_Expression (Low_Bound (Constr))
527 and then
528 Is_OK_Static_Expression (High_Bound (Constr));
530 elsif Nkind (Constr) = N_Attribute_Reference
531 and then Attribute_Name (Constr) = Name_Range
532 then
533 return
534 Is_OK_Static_Expression
535 (Type_Low_Bound (Etype (Prefix (Constr))))
536 and then
537 Is_OK_Static_Expression
538 (Type_High_Bound (Etype (Prefix (Constr))));
539 end if;
541 return
542 not Present (Etype (Constr)) -- previous error
543 or else not Is_Discrete_Type (Etype (Constr))
544 or else Is_OK_Static_Expression (Constr);
546 when N_Discriminant_Association =>
547 return All_Composite_Constraints_Static (Expression (Constr));
549 when N_Range_Constraint =>
550 return
551 All_Composite_Constraints_Static (Range_Expression (Constr));
553 when N_Index_Or_Discriminant_Constraint =>
554 declare
555 One_Cstr : Entity_Id;
556 begin
557 One_Cstr := First (Constraints (Constr));
558 while Present (One_Cstr) loop
559 if not All_Composite_Constraints_Static (One_Cstr) then
560 return False;
561 end if;
563 Next (One_Cstr);
564 end loop;
565 end;
567 return True;
569 when N_Subtype_Indication =>
570 return
571 All_Composite_Constraints_Static (Subtype_Mark (Constr))
572 and then
573 All_Composite_Constraints_Static (Constraint (Constr));
575 when others =>
576 raise Program_Error;
577 end case;
578 end All_Composite_Constraints_Static;
580 ------------------------
581 -- Append_Entity_Name --
582 ------------------------
584 procedure Append_Entity_Name (Buf : in out Bounded_String; E : Entity_Id) is
585 Temp : Bounded_String;
587 procedure Inner (E : Entity_Id);
588 -- Inner recursive routine, keep outer routine nonrecursive to ease
589 -- debugging when we get strange results from this routine.
591 -----------
592 -- Inner --
593 -----------
595 procedure Inner (E : Entity_Id) is
596 begin
597 -- If entity has an internal name, skip by it, and print its scope.
598 -- Note that we strip a final R from the name before the test; this
599 -- is needed for some cases of instantiations.
601 declare
602 E_Name : Bounded_String;
604 begin
605 Append (E_Name, Chars (E));
607 if E_Name.Chars (E_Name.Length) = 'R' then
608 E_Name.Length := E_Name.Length - 1;
609 end if;
611 if Is_Internal_Name (E_Name) then
612 Inner (Scope (E));
613 return;
614 end if;
615 end;
617 -- Just print entity name if its scope is at the outer level
619 if Scope (E) = Standard_Standard then
620 null;
622 -- If scope comes from source, write scope and entity
624 elsif Comes_From_Source (Scope (E)) then
625 Append_Entity_Name (Temp, Scope (E));
626 Append (Temp, '.');
628 -- If in wrapper package skip past it
630 elsif Is_Wrapper_Package (Scope (E)) then
631 Append_Entity_Name (Temp, Scope (Scope (E)));
632 Append (Temp, '.');
634 -- Otherwise nothing to output (happens in unnamed block statements)
636 else
637 null;
638 end if;
640 -- Output the name
642 declare
643 E_Name : Bounded_String;
645 begin
646 Append_Unqualified_Decoded (E_Name, Chars (E));
648 -- Remove trailing upper-case letters from the name (useful for
649 -- dealing with some cases of internal names generated in the case
650 -- of references from within a generic).
652 while E_Name.Length > 1
653 and then E_Name.Chars (E_Name.Length) in 'A' .. 'Z'
654 loop
655 E_Name.Length := E_Name.Length - 1;
656 end loop;
658 -- Adjust casing appropriately (gets name from source if possible)
660 Adjust_Name_Case (E_Name, Sloc (E));
661 Append (Temp, E_Name);
662 end;
663 end Inner;
665 -- Start of processing for Append_Entity_Name
667 begin
668 Inner (E);
669 Append (Buf, Temp);
670 end Append_Entity_Name;
672 ---------------------------------
673 -- Append_Inherited_Subprogram --
674 ---------------------------------
676 procedure Append_Inherited_Subprogram (S : Entity_Id) is
677 Par : constant Entity_Id := Alias (S);
678 -- The parent subprogram
680 Scop : constant Entity_Id := Scope (Par);
681 -- The scope of definition of the parent subprogram
683 Typ : constant Entity_Id := Defining_Entity (Parent (S));
684 -- The derived type of which S is a primitive operation
686 Decl : Node_Id;
687 Next_E : Entity_Id;
689 begin
690 if Ekind (Current_Scope) = E_Package
691 and then In_Private_Part (Current_Scope)
692 and then Has_Private_Declaration (Typ)
693 and then Is_Tagged_Type (Typ)
694 and then Scop = Current_Scope
695 then
696 -- The inherited operation is available at the earliest place after
697 -- the derived type declaration ( RM 7.3.1 (6/1)). This is only
698 -- relevant for type extensions. If the parent operation appears
699 -- after the type extension, the operation is not visible.
701 Decl := First
702 (Visible_Declarations
703 (Package_Specification (Current_Scope)));
704 while Present (Decl) loop
705 if Nkind (Decl) = N_Private_Extension_Declaration
706 and then Defining_Entity (Decl) = Typ
707 then
708 if Sloc (Decl) > Sloc (Par) then
709 Next_E := Next_Entity (Par);
710 Set_Next_Entity (Par, S);
711 Set_Next_Entity (S, Next_E);
712 return;
714 else
715 exit;
716 end if;
717 end if;
719 Next (Decl);
720 end loop;
721 end if;
723 -- If partial view is not a type extension, or it appears before the
724 -- subprogram declaration, insert normally at end of entity list.
726 Append_Entity (S, Current_Scope);
727 end Append_Inherited_Subprogram;
729 -----------------------------------------
730 -- Apply_Compile_Time_Constraint_Error --
731 -----------------------------------------
733 procedure Apply_Compile_Time_Constraint_Error
734 (N : Node_Id;
735 Msg : String;
736 Reason : RT_Exception_Code;
737 Ent : Entity_Id := Empty;
738 Typ : Entity_Id := Empty;
739 Loc : Source_Ptr := No_Location;
740 Rep : Boolean := True;
741 Warn : Boolean := False)
743 Stat : constant Boolean := Is_Static_Expression (N);
744 R_Stat : constant Node_Id :=
745 Make_Raise_Constraint_Error (Sloc (N), Reason => Reason);
746 Rtyp : Entity_Id;
748 begin
749 if No (Typ) then
750 Rtyp := Etype (N);
751 else
752 Rtyp := Typ;
753 end if;
755 Discard_Node
756 (Compile_Time_Constraint_Error (N, Msg, Ent, Loc, Warn => Warn));
758 -- In GNATprove mode, do not replace the node with an exception raised.
759 -- In such a case, either the call to Compile_Time_Constraint_Error
760 -- issues an error which stops analysis, or it issues a warning in
761 -- a few cases where a suitable check flag is set for GNATprove to
762 -- generate a check message.
764 if not Rep or GNATprove_Mode then
765 return;
766 end if;
768 -- Now we replace the node by an N_Raise_Constraint_Error node
769 -- This does not need reanalyzing, so set it as analyzed now.
771 Rewrite (N, R_Stat);
772 Set_Analyzed (N, True);
774 Set_Etype (N, Rtyp);
775 Set_Raises_Constraint_Error (N);
777 -- Now deal with possible local raise handling
779 Possible_Local_Raise (N, Standard_Constraint_Error);
781 -- If the original expression was marked as static, the result is
782 -- still marked as static, but the Raises_Constraint_Error flag is
783 -- always set so that further static evaluation is not attempted.
785 if Stat then
786 Set_Is_Static_Expression (N);
787 end if;
788 end Apply_Compile_Time_Constraint_Error;
790 ---------------------------
791 -- Async_Readers_Enabled --
792 ---------------------------
794 function Async_Readers_Enabled (Id : Entity_Id) return Boolean is
795 begin
796 return Has_Enabled_Property (Id, Name_Async_Readers);
797 end Async_Readers_Enabled;
799 ---------------------------
800 -- Async_Writers_Enabled --
801 ---------------------------
803 function Async_Writers_Enabled (Id : Entity_Id) return Boolean is
804 begin
805 return Has_Enabled_Property (Id, Name_Async_Writers);
806 end Async_Writers_Enabled;
808 --------------------------------------
809 -- Available_Full_View_Of_Component --
810 --------------------------------------
812 function Available_Full_View_Of_Component (T : Entity_Id) return Boolean is
813 ST : constant Entity_Id := Scope (T);
814 SCT : constant Entity_Id := Scope (Component_Type (T));
815 begin
816 return In_Open_Scopes (ST)
817 and then In_Open_Scopes (SCT)
818 and then Scope_Depth (ST) >= Scope_Depth (SCT);
819 end Available_Full_View_Of_Component;
821 -------------------
822 -- Bad_Attribute --
823 -------------------
825 procedure Bad_Attribute
826 (N : Node_Id;
827 Nam : Name_Id;
828 Warn : Boolean := False)
830 begin
831 Error_Msg_Warn := Warn;
832 Error_Msg_N ("unrecognized attribute&<<", N);
834 -- Check for possible misspelling
836 Error_Msg_Name_1 := First_Attribute_Name;
837 while Error_Msg_Name_1 <= Last_Attribute_Name loop
838 if Is_Bad_Spelling_Of (Nam, Error_Msg_Name_1) then
839 Error_Msg_N -- CODEFIX
840 ("\possible misspelling of %<<", N);
841 exit;
842 end if;
844 Error_Msg_Name_1 := Error_Msg_Name_1 + 1;
845 end loop;
846 end Bad_Attribute;
848 --------------------------------
849 -- Bad_Predicated_Subtype_Use --
850 --------------------------------
852 procedure Bad_Predicated_Subtype_Use
853 (Msg : String;
854 N : Node_Id;
855 Typ : Entity_Id;
856 Suggest_Static : Boolean := False)
858 Gen : Entity_Id;
860 begin
861 -- Avoid cascaded errors
863 if Error_Posted (N) then
864 return;
865 end if;
867 if Inside_A_Generic then
868 Gen := Current_Scope;
869 while Present (Gen) and then Ekind (Gen) /= E_Generic_Package loop
870 Gen := Scope (Gen);
871 end loop;
873 if No (Gen) then
874 return;
875 end if;
877 if Is_Generic_Formal (Typ) and then Is_Discrete_Type (Typ) then
878 Set_No_Predicate_On_Actual (Typ);
879 end if;
881 elsif Has_Predicates (Typ) then
882 if Is_Generic_Actual_Type (Typ) then
884 -- The restriction on loop parameters is only that the type
885 -- should have no dynamic predicates.
887 if Nkind (Parent (N)) = N_Loop_Parameter_Specification
888 and then not Has_Dynamic_Predicate_Aspect (Typ)
889 and then Is_OK_Static_Subtype (Typ)
890 then
891 return;
892 end if;
894 Gen := Current_Scope;
895 while not Is_Generic_Instance (Gen) loop
896 Gen := Scope (Gen);
897 end loop;
899 pragma Assert (Present (Gen));
901 if Ekind (Gen) = E_Package and then In_Package_Body (Gen) then
902 Error_Msg_Warn := SPARK_Mode /= On;
903 Error_Msg_FE (Msg & "<<", N, Typ);
904 Error_Msg_F ("\Program_Error [<<", N);
906 Insert_Action (N,
907 Make_Raise_Program_Error (Sloc (N),
908 Reason => PE_Bad_Predicated_Generic_Type));
910 else
911 Error_Msg_FE (Msg & "<<", N, Typ);
912 end if;
914 else
915 Error_Msg_FE (Msg, N, Typ);
916 end if;
918 -- Emit an optional suggestion on how to remedy the error if the
919 -- context warrants it.
921 if Suggest_Static and then Has_Static_Predicate (Typ) then
922 Error_Msg_FE ("\predicate of & should be marked static", N, Typ);
923 end if;
924 end if;
925 end Bad_Predicated_Subtype_Use;
927 -----------------------------------------
928 -- Bad_Unordered_Enumeration_Reference --
929 -----------------------------------------
931 function Bad_Unordered_Enumeration_Reference
932 (N : Node_Id;
933 T : Entity_Id) return Boolean
935 begin
936 return Is_Enumeration_Type (T)
937 and then Warn_On_Unordered_Enumeration_Type
938 and then not Is_Generic_Type (T)
939 and then Comes_From_Source (N)
940 and then not Has_Pragma_Ordered (T)
941 and then not In_Same_Extended_Unit (N, T);
942 end Bad_Unordered_Enumeration_Reference;
944 --------------------------
945 -- Build_Actual_Subtype --
946 --------------------------
948 function Build_Actual_Subtype
949 (T : Entity_Id;
950 N : Node_Or_Entity_Id) return Node_Id
952 Loc : Source_Ptr;
953 -- Normally Sloc (N), but may point to corresponding body in some cases
955 Constraints : List_Id;
956 Decl : Node_Id;
957 Discr : Entity_Id;
958 Hi : Node_Id;
959 Lo : Node_Id;
960 Subt : Entity_Id;
961 Disc_Type : Entity_Id;
962 Obj : Node_Id;
964 begin
965 Loc := Sloc (N);
967 if Nkind (N) = N_Defining_Identifier then
968 Obj := New_Occurrence_Of (N, Loc);
970 -- If this is a formal parameter of a subprogram declaration, and
971 -- we are compiling the body, we want the declaration for the
972 -- actual subtype to carry the source position of the body, to
973 -- prevent anomalies in gdb when stepping through the code.
975 if Is_Formal (N) then
976 declare
977 Decl : constant Node_Id := Unit_Declaration_Node (Scope (N));
978 begin
979 if Nkind (Decl) = N_Subprogram_Declaration
980 and then Present (Corresponding_Body (Decl))
981 then
982 Loc := Sloc (Corresponding_Body (Decl));
983 end if;
984 end;
985 end if;
987 else
988 Obj := N;
989 end if;
991 if Is_Array_Type (T) then
992 Constraints := New_List;
993 for J in 1 .. Number_Dimensions (T) loop
995 -- Build an array subtype declaration with the nominal subtype and
996 -- the bounds of the actual. Add the declaration in front of the
997 -- local declarations for the subprogram, for analysis before any
998 -- reference to the formal in the body.
1000 Lo :=
1001 Make_Attribute_Reference (Loc,
1002 Prefix =>
1003 Duplicate_Subexpr_No_Checks (Obj, Name_Req => True),
1004 Attribute_Name => Name_First,
1005 Expressions => New_List (
1006 Make_Integer_Literal (Loc, J)));
1008 Hi :=
1009 Make_Attribute_Reference (Loc,
1010 Prefix =>
1011 Duplicate_Subexpr_No_Checks (Obj, Name_Req => True),
1012 Attribute_Name => Name_Last,
1013 Expressions => New_List (
1014 Make_Integer_Literal (Loc, J)));
1016 Append (Make_Range (Loc, Lo, Hi), Constraints);
1017 end loop;
1019 -- If the type has unknown discriminants there is no constrained
1020 -- subtype to build. This is never called for a formal or for a
1021 -- lhs, so returning the type is ok ???
1023 elsif Has_Unknown_Discriminants (T) then
1024 return T;
1026 else
1027 Constraints := New_List;
1029 -- Type T is a generic derived type, inherit the discriminants from
1030 -- the parent type.
1032 if Is_Private_Type (T)
1033 and then No (Full_View (T))
1035 -- T was flagged as an error if it was declared as a formal
1036 -- derived type with known discriminants. In this case there
1037 -- is no need to look at the parent type since T already carries
1038 -- its own discriminants.
1040 and then not Error_Posted (T)
1041 then
1042 Disc_Type := Etype (Base_Type (T));
1043 else
1044 Disc_Type := T;
1045 end if;
1047 Discr := First_Discriminant (Disc_Type);
1048 while Present (Discr) loop
1049 Append_To (Constraints,
1050 Make_Selected_Component (Loc,
1051 Prefix =>
1052 Duplicate_Subexpr_No_Checks (Obj),
1053 Selector_Name => New_Occurrence_Of (Discr, Loc)));
1054 Next_Discriminant (Discr);
1055 end loop;
1056 end if;
1058 Subt := Make_Temporary (Loc, 'S', Related_Node => N);
1059 Set_Is_Internal (Subt);
1061 Decl :=
1062 Make_Subtype_Declaration (Loc,
1063 Defining_Identifier => Subt,
1064 Subtype_Indication =>
1065 Make_Subtype_Indication (Loc,
1066 Subtype_Mark => New_Occurrence_Of (T, Loc),
1067 Constraint =>
1068 Make_Index_Or_Discriminant_Constraint (Loc,
1069 Constraints => Constraints)));
1071 Mark_Rewrite_Insertion (Decl);
1072 return Decl;
1073 end Build_Actual_Subtype;
1075 ---------------------------------------
1076 -- Build_Actual_Subtype_Of_Component --
1077 ---------------------------------------
1079 function Build_Actual_Subtype_Of_Component
1080 (T : Entity_Id;
1081 N : Node_Id) return Node_Id
1083 Loc : constant Source_Ptr := Sloc (N);
1084 P : constant Node_Id := Prefix (N);
1085 D : Elmt_Id;
1086 Id : Node_Id;
1087 Index_Typ : Entity_Id;
1089 Desig_Typ : Entity_Id;
1090 -- This is either a copy of T, or if T is an access type, then it is
1091 -- the directly designated type of this access type.
1093 function Build_Actual_Array_Constraint return List_Id;
1094 -- If one or more of the bounds of the component depends on
1095 -- discriminants, build actual constraint using the discriminants
1096 -- of the prefix.
1098 function Build_Actual_Record_Constraint return List_Id;
1099 -- Similar to previous one, for discriminated components constrained
1100 -- by the discriminant of the enclosing object.
1102 -----------------------------------
1103 -- Build_Actual_Array_Constraint --
1104 -----------------------------------
1106 function Build_Actual_Array_Constraint return List_Id is
1107 Constraints : constant List_Id := New_List;
1108 Indx : Node_Id;
1109 Hi : Node_Id;
1110 Lo : Node_Id;
1111 Old_Hi : Node_Id;
1112 Old_Lo : Node_Id;
1114 begin
1115 Indx := First_Index (Desig_Typ);
1116 while Present (Indx) loop
1117 Old_Lo := Type_Low_Bound (Etype (Indx));
1118 Old_Hi := Type_High_Bound (Etype (Indx));
1120 if Denotes_Discriminant (Old_Lo) then
1121 Lo :=
1122 Make_Selected_Component (Loc,
1123 Prefix => New_Copy_Tree (P),
1124 Selector_Name => New_Occurrence_Of (Entity (Old_Lo), Loc));
1126 else
1127 Lo := New_Copy_Tree (Old_Lo);
1129 -- The new bound will be reanalyzed in the enclosing
1130 -- declaration. For literal bounds that come from a type
1131 -- declaration, the type of the context must be imposed, so
1132 -- insure that analysis will take place. For non-universal
1133 -- types this is not strictly necessary.
1135 Set_Analyzed (Lo, False);
1136 end if;
1138 if Denotes_Discriminant (Old_Hi) then
1139 Hi :=
1140 Make_Selected_Component (Loc,
1141 Prefix => New_Copy_Tree (P),
1142 Selector_Name => New_Occurrence_Of (Entity (Old_Hi), Loc));
1144 else
1145 Hi := New_Copy_Tree (Old_Hi);
1146 Set_Analyzed (Hi, False);
1147 end if;
1149 Append (Make_Range (Loc, Lo, Hi), Constraints);
1150 Next_Index (Indx);
1151 end loop;
1153 return Constraints;
1154 end Build_Actual_Array_Constraint;
1156 ------------------------------------
1157 -- Build_Actual_Record_Constraint --
1158 ------------------------------------
1160 function Build_Actual_Record_Constraint return List_Id is
1161 Constraints : constant List_Id := New_List;
1162 D : Elmt_Id;
1163 D_Val : Node_Id;
1165 begin
1166 D := First_Elmt (Discriminant_Constraint (Desig_Typ));
1167 while Present (D) loop
1168 if Denotes_Discriminant (Node (D)) then
1169 D_Val := Make_Selected_Component (Loc,
1170 Prefix => New_Copy_Tree (P),
1171 Selector_Name => New_Occurrence_Of (Entity (Node (D)), Loc));
1173 else
1174 D_Val := New_Copy_Tree (Node (D));
1175 end if;
1177 Append (D_Val, Constraints);
1178 Next_Elmt (D);
1179 end loop;
1181 return Constraints;
1182 end Build_Actual_Record_Constraint;
1184 -- Start of processing for Build_Actual_Subtype_Of_Component
1186 begin
1187 -- Why the test for Spec_Expression mode here???
1189 if In_Spec_Expression then
1190 return Empty;
1192 -- More comments for the rest of this body would be good ???
1194 elsif Nkind (N) = N_Explicit_Dereference then
1195 if Is_Composite_Type (T)
1196 and then not Is_Constrained (T)
1197 and then not (Is_Class_Wide_Type (T)
1198 and then Is_Constrained (Root_Type (T)))
1199 and then not Has_Unknown_Discriminants (T)
1200 then
1201 -- If the type of the dereference is already constrained, it is an
1202 -- actual subtype.
1204 if Is_Array_Type (Etype (N))
1205 and then Is_Constrained (Etype (N))
1206 then
1207 return Empty;
1208 else
1209 Remove_Side_Effects (P);
1210 return Build_Actual_Subtype (T, N);
1211 end if;
1212 else
1213 return Empty;
1214 end if;
1215 end if;
1217 if Ekind (T) = E_Access_Subtype then
1218 Desig_Typ := Designated_Type (T);
1219 else
1220 Desig_Typ := T;
1221 end if;
1223 if Ekind (Desig_Typ) = E_Array_Subtype then
1224 Id := First_Index (Desig_Typ);
1225 while Present (Id) loop
1226 Index_Typ := Underlying_Type (Etype (Id));
1228 if Denotes_Discriminant (Type_Low_Bound (Index_Typ))
1229 or else
1230 Denotes_Discriminant (Type_High_Bound (Index_Typ))
1231 then
1232 Remove_Side_Effects (P);
1233 return
1234 Build_Component_Subtype
1235 (Build_Actual_Array_Constraint, Loc, Base_Type (T));
1236 end if;
1238 Next_Index (Id);
1239 end loop;
1241 elsif Is_Composite_Type (Desig_Typ)
1242 and then Has_Discriminants (Desig_Typ)
1243 and then not Has_Unknown_Discriminants (Desig_Typ)
1244 then
1245 if Is_Private_Type (Desig_Typ)
1246 and then No (Discriminant_Constraint (Desig_Typ))
1247 then
1248 Desig_Typ := Full_View (Desig_Typ);
1249 end if;
1251 D := First_Elmt (Discriminant_Constraint (Desig_Typ));
1252 while Present (D) loop
1253 if Denotes_Discriminant (Node (D)) then
1254 Remove_Side_Effects (P);
1255 return
1256 Build_Component_Subtype (
1257 Build_Actual_Record_Constraint, Loc, Base_Type (T));
1258 end if;
1260 Next_Elmt (D);
1261 end loop;
1262 end if;
1264 -- If none of the above, the actual and nominal subtypes are the same
1266 return Empty;
1267 end Build_Actual_Subtype_Of_Component;
1269 ---------------------------------
1270 -- Build_Class_Wide_Clone_Body --
1271 ---------------------------------
1273 procedure Build_Class_Wide_Clone_Body
1274 (Spec_Id : Entity_Id;
1275 Bod : Node_Id)
1277 Loc : constant Source_Ptr := Sloc (Bod);
1278 Clone_Id : constant Entity_Id := Class_Wide_Clone (Spec_Id);
1279 Clone_Body : Node_Id;
1281 begin
1282 -- The declaration of the class-wide clone was created when the
1283 -- corresponding class-wide condition was analyzed.
1285 Clone_Body :=
1286 Make_Subprogram_Body (Loc,
1287 Specification =>
1288 Copy_Subprogram_Spec (Parent (Clone_Id)),
1289 Declarations => Declarations (Bod),
1290 Handled_Statement_Sequence => Handled_Statement_Sequence (Bod));
1292 -- The new operation is internal and overriding indicators do not apply
1293 -- (the original primitive may have carried one).
1295 Set_Must_Override (Specification (Clone_Body), False);
1296 Insert_Before (Bod, Clone_Body);
1297 Analyze (Clone_Body);
1298 end Build_Class_Wide_Clone_Body;
1300 ---------------------------------
1301 -- Build_Class_Wide_Clone_Call --
1302 ---------------------------------
1304 function Build_Class_Wide_Clone_Call
1305 (Loc : Source_Ptr;
1306 Decls : List_Id;
1307 Spec_Id : Entity_Id;
1308 Spec : Node_Id) return Node_Id
1310 Clone_Id : constant Entity_Id := Class_Wide_Clone (Spec_Id);
1311 Par_Type : constant Entity_Id := Find_Dispatching_Type (Spec_Id);
1313 Actuals : List_Id;
1314 Call : Node_Id;
1315 Formal : Entity_Id;
1316 New_Body : Node_Id;
1317 New_F_Spec : Entity_Id;
1318 New_Formal : Entity_Id;
1320 begin
1321 Actuals := Empty_List;
1322 Formal := First_Formal (Spec_Id);
1323 New_F_Spec := First (Parameter_Specifications (Spec));
1325 -- Build parameter association for call to class-wide clone.
1327 while Present (Formal) loop
1328 New_Formal := Defining_Identifier (New_F_Spec);
1330 -- If controlling argument and operation is inherited, add conversion
1331 -- to parent type for the call.
1333 if Etype (Formal) = Par_Type
1334 and then not Is_Empty_List (Decls)
1335 then
1336 Append_To (Actuals,
1337 Make_Type_Conversion (Loc,
1338 New_Occurrence_Of (Par_Type, Loc),
1339 New_Occurrence_Of (New_Formal, Loc)));
1341 else
1342 Append_To (Actuals, New_Occurrence_Of (New_Formal, Loc));
1343 end if;
1345 Next_Formal (Formal);
1346 Next (New_F_Spec);
1347 end loop;
1349 if Ekind (Spec_Id) = E_Procedure then
1350 Call :=
1351 Make_Procedure_Call_Statement (Loc,
1352 Name => New_Occurrence_Of (Clone_Id, Loc),
1353 Parameter_Associations => Actuals);
1354 else
1355 Call :=
1356 Make_Simple_Return_Statement (Loc,
1357 Expression =>
1358 Make_Function_Call (Loc,
1359 Name => New_Occurrence_Of (Clone_Id, Loc),
1360 Parameter_Associations => Actuals));
1361 end if;
1363 New_Body :=
1364 Make_Subprogram_Body (Loc,
1365 Specification =>
1366 Copy_Subprogram_Spec (Spec),
1367 Declarations => Decls,
1368 Handled_Statement_Sequence =>
1369 Make_Handled_Sequence_Of_Statements (Loc,
1370 Statements => New_List (Call),
1371 End_Label => Make_Identifier (Loc, Chars (Spec_Id))));
1373 return New_Body;
1374 end Build_Class_Wide_Clone_Call;
1376 ---------------------------------
1377 -- Build_Class_Wide_Clone_Decl --
1378 ---------------------------------
1380 procedure Build_Class_Wide_Clone_Decl (Spec_Id : Entity_Id) is
1381 Loc : constant Source_Ptr := Sloc (Spec_Id);
1382 Clone_Id : constant Entity_Id :=
1383 Make_Defining_Identifier (Loc,
1384 New_External_Name (Chars (Spec_Id), Suffix => "CL"));
1386 Decl : Node_Id;
1387 Spec : Node_Id;
1389 begin
1390 Spec := Copy_Subprogram_Spec (Parent (Spec_Id));
1391 Set_Must_Override (Spec, False);
1392 Set_Must_Not_Override (Spec, False);
1393 Set_Defining_Unit_Name (Spec, Clone_Id);
1395 Decl := Make_Subprogram_Declaration (Loc, Spec);
1396 Append (Decl, List_Containing (Unit_Declaration_Node (Spec_Id)));
1398 -- Link clone to original subprogram, for use when building body and
1399 -- wrapper call to inherited operation.
1401 Set_Class_Wide_Clone (Spec_Id, Clone_Id);
1402 end Build_Class_Wide_Clone_Decl;
1404 -----------------------------
1405 -- Build_Component_Subtype --
1406 -----------------------------
1408 function Build_Component_Subtype
1409 (C : List_Id;
1410 Loc : Source_Ptr;
1411 T : Entity_Id) return Node_Id
1413 Subt : Entity_Id;
1414 Decl : Node_Id;
1416 begin
1417 -- Unchecked_Union components do not require component subtypes
1419 if Is_Unchecked_Union (T) then
1420 return Empty;
1421 end if;
1423 Subt := Make_Temporary (Loc, 'S');
1424 Set_Is_Internal (Subt);
1426 Decl :=
1427 Make_Subtype_Declaration (Loc,
1428 Defining_Identifier => Subt,
1429 Subtype_Indication =>
1430 Make_Subtype_Indication (Loc,
1431 Subtype_Mark => New_Occurrence_Of (Base_Type (T), Loc),
1432 Constraint =>
1433 Make_Index_Or_Discriminant_Constraint (Loc,
1434 Constraints => C)));
1436 Mark_Rewrite_Insertion (Decl);
1437 return Decl;
1438 end Build_Component_Subtype;
1440 ---------------------------
1441 -- Build_Default_Subtype --
1442 ---------------------------
1444 function Build_Default_Subtype
1445 (T : Entity_Id;
1446 N : Node_Id) return Entity_Id
1448 Loc : constant Source_Ptr := Sloc (N);
1449 Disc : Entity_Id;
1451 Bas : Entity_Id;
1452 -- The base type that is to be constrained by the defaults
1454 begin
1455 if not Has_Discriminants (T) or else Is_Constrained (T) then
1456 return T;
1457 end if;
1459 Bas := Base_Type (T);
1461 -- If T is non-private but its base type is private, this is the
1462 -- completion of a subtype declaration whose parent type is private
1463 -- (see Complete_Private_Subtype in Sem_Ch3). The proper discriminants
1464 -- are to be found in the full view of the base. Check that the private
1465 -- status of T and its base differ.
1467 if Is_Private_Type (Bas)
1468 and then not Is_Private_Type (T)
1469 and then Present (Full_View (Bas))
1470 then
1471 Bas := Full_View (Bas);
1472 end if;
1474 Disc := First_Discriminant (T);
1476 if No (Discriminant_Default_Value (Disc)) then
1477 return T;
1478 end if;
1480 declare
1481 Act : constant Entity_Id := Make_Temporary (Loc, 'S');
1482 Constraints : constant List_Id := New_List;
1483 Decl : Node_Id;
1485 begin
1486 while Present (Disc) loop
1487 Append_To (Constraints,
1488 New_Copy_Tree (Discriminant_Default_Value (Disc)));
1489 Next_Discriminant (Disc);
1490 end loop;
1492 Decl :=
1493 Make_Subtype_Declaration (Loc,
1494 Defining_Identifier => Act,
1495 Subtype_Indication =>
1496 Make_Subtype_Indication (Loc,
1497 Subtype_Mark => New_Occurrence_Of (Bas, Loc),
1498 Constraint =>
1499 Make_Index_Or_Discriminant_Constraint (Loc,
1500 Constraints => Constraints)));
1502 Insert_Action (N, Decl);
1504 -- If the context is a component declaration the subtype declaration
1505 -- will be analyzed when the enclosing type is frozen, otherwise do
1506 -- it now.
1508 if Ekind (Current_Scope) /= E_Record_Type then
1509 Analyze (Decl);
1510 end if;
1512 return Act;
1513 end;
1514 end Build_Default_Subtype;
1516 --------------------------------------------
1517 -- Build_Discriminal_Subtype_Of_Component --
1518 --------------------------------------------
1520 function Build_Discriminal_Subtype_Of_Component
1521 (T : Entity_Id) return Node_Id
1523 Loc : constant Source_Ptr := Sloc (T);
1524 D : Elmt_Id;
1525 Id : Node_Id;
1527 function Build_Discriminal_Array_Constraint return List_Id;
1528 -- If one or more of the bounds of the component depends on
1529 -- discriminants, build actual constraint using the discriminants
1530 -- of the prefix.
1532 function Build_Discriminal_Record_Constraint return List_Id;
1533 -- Similar to previous one, for discriminated components constrained by
1534 -- the discriminant of the enclosing object.
1536 ----------------------------------------
1537 -- Build_Discriminal_Array_Constraint --
1538 ----------------------------------------
1540 function Build_Discriminal_Array_Constraint return List_Id is
1541 Constraints : constant List_Id := New_List;
1542 Indx : Node_Id;
1543 Hi : Node_Id;
1544 Lo : Node_Id;
1545 Old_Hi : Node_Id;
1546 Old_Lo : Node_Id;
1548 begin
1549 Indx := First_Index (T);
1550 while Present (Indx) loop
1551 Old_Lo := Type_Low_Bound (Etype (Indx));
1552 Old_Hi := Type_High_Bound (Etype (Indx));
1554 if Denotes_Discriminant (Old_Lo) then
1555 Lo := New_Occurrence_Of (Discriminal (Entity (Old_Lo)), Loc);
1557 else
1558 Lo := New_Copy_Tree (Old_Lo);
1559 end if;
1561 if Denotes_Discriminant (Old_Hi) then
1562 Hi := New_Occurrence_Of (Discriminal (Entity (Old_Hi)), Loc);
1564 else
1565 Hi := New_Copy_Tree (Old_Hi);
1566 end if;
1568 Append (Make_Range (Loc, Lo, Hi), Constraints);
1569 Next_Index (Indx);
1570 end loop;
1572 return Constraints;
1573 end Build_Discriminal_Array_Constraint;
1575 -----------------------------------------
1576 -- Build_Discriminal_Record_Constraint --
1577 -----------------------------------------
1579 function Build_Discriminal_Record_Constraint return List_Id is
1580 Constraints : constant List_Id := New_List;
1581 D : Elmt_Id;
1582 D_Val : Node_Id;
1584 begin
1585 D := First_Elmt (Discriminant_Constraint (T));
1586 while Present (D) loop
1587 if Denotes_Discriminant (Node (D)) then
1588 D_Val :=
1589 New_Occurrence_Of (Discriminal (Entity (Node (D))), Loc);
1590 else
1591 D_Val := New_Copy_Tree (Node (D));
1592 end if;
1594 Append (D_Val, Constraints);
1595 Next_Elmt (D);
1596 end loop;
1598 return Constraints;
1599 end Build_Discriminal_Record_Constraint;
1601 -- Start of processing for Build_Discriminal_Subtype_Of_Component
1603 begin
1604 if Ekind (T) = E_Array_Subtype then
1605 Id := First_Index (T);
1606 while Present (Id) loop
1607 if Denotes_Discriminant (Type_Low_Bound (Etype (Id)))
1608 or else
1609 Denotes_Discriminant (Type_High_Bound (Etype (Id)))
1610 then
1611 return Build_Component_Subtype
1612 (Build_Discriminal_Array_Constraint, Loc, T);
1613 end if;
1615 Next_Index (Id);
1616 end loop;
1618 elsif Ekind (T) = E_Record_Subtype
1619 and then Has_Discriminants (T)
1620 and then not Has_Unknown_Discriminants (T)
1621 then
1622 D := First_Elmt (Discriminant_Constraint (T));
1623 while Present (D) loop
1624 if Denotes_Discriminant (Node (D)) then
1625 return Build_Component_Subtype
1626 (Build_Discriminal_Record_Constraint, Loc, T);
1627 end if;
1629 Next_Elmt (D);
1630 end loop;
1631 end if;
1633 -- If none of the above, the actual and nominal subtypes are the same
1635 return Empty;
1636 end Build_Discriminal_Subtype_Of_Component;
1638 ------------------------------
1639 -- Build_Elaboration_Entity --
1640 ------------------------------
1642 procedure Build_Elaboration_Entity (N : Node_Id; Spec_Id : Entity_Id) is
1643 Loc : constant Source_Ptr := Sloc (N);
1644 Decl : Node_Id;
1645 Elab_Ent : Entity_Id;
1647 procedure Set_Package_Name (Ent : Entity_Id);
1648 -- Given an entity, sets the fully qualified name of the entity in
1649 -- Name_Buffer, with components separated by double underscores. This
1650 -- is a recursive routine that climbs the scope chain to Standard.
1652 ----------------------
1653 -- Set_Package_Name --
1654 ----------------------
1656 procedure Set_Package_Name (Ent : Entity_Id) is
1657 begin
1658 if Scope (Ent) /= Standard_Standard then
1659 Set_Package_Name (Scope (Ent));
1661 declare
1662 Nam : constant String := Get_Name_String (Chars (Ent));
1663 begin
1664 Name_Buffer (Name_Len + 1) := '_';
1665 Name_Buffer (Name_Len + 2) := '_';
1666 Name_Buffer (Name_Len + 3 .. Name_Len + Nam'Length + 2) := Nam;
1667 Name_Len := Name_Len + Nam'Length + 2;
1668 end;
1670 else
1671 Get_Name_String (Chars (Ent));
1672 end if;
1673 end Set_Package_Name;
1675 -- Start of processing for Build_Elaboration_Entity
1677 begin
1678 -- Ignore call if already constructed
1680 if Present (Elaboration_Entity (Spec_Id)) then
1681 return;
1683 -- Ignore in ASIS mode, elaboration entity is not in source and plays
1684 -- no role in analysis.
1686 elsif ASIS_Mode then
1687 return;
1689 -- Do not generate an elaboration entity in GNATprove move because the
1690 -- elaboration counter is a form of expansion.
1692 elsif GNATprove_Mode then
1693 return;
1695 -- See if we need elaboration entity
1697 -- We always need an elaboration entity when preserving control flow, as
1698 -- we want to remain explicit about the unit's elaboration order.
1700 elsif Opt.Suppress_Control_Flow_Optimizations then
1701 null;
1703 -- We always need an elaboration entity for the dynamic elaboration
1704 -- model, since it is needed to properly generate the PE exception for
1705 -- access before elaboration.
1707 elsif Dynamic_Elaboration_Checks then
1708 null;
1710 -- For the static model, we don't need the elaboration counter if this
1711 -- unit is sure to have no elaboration code, since that means there
1712 -- is no elaboration unit to be called. Note that we can't just decide
1713 -- after the fact by looking to see whether there was elaboration code,
1714 -- because that's too late to make this decision.
1716 elsif Restriction_Active (No_Elaboration_Code) then
1717 return;
1719 -- Similarly, for the static model, we can skip the elaboration counter
1720 -- if we have the No_Multiple_Elaboration restriction, since for the
1721 -- static model, that's the only purpose of the counter (to avoid
1722 -- multiple elaboration).
1724 elsif Restriction_Active (No_Multiple_Elaboration) then
1725 return;
1726 end if;
1728 -- Here we need the elaboration entity
1730 -- Construct name of elaboration entity as xxx_E, where xxx is the unit
1731 -- name with dots replaced by double underscore. We have to manually
1732 -- construct this name, since it will be elaborated in the outer scope,
1733 -- and thus will not have the unit name automatically prepended.
1735 Set_Package_Name (Spec_Id);
1736 Add_Str_To_Name_Buffer ("_E");
1738 -- Create elaboration counter
1740 Elab_Ent := Make_Defining_Identifier (Loc, Chars => Name_Find);
1741 Set_Elaboration_Entity (Spec_Id, Elab_Ent);
1743 Decl :=
1744 Make_Object_Declaration (Loc,
1745 Defining_Identifier => Elab_Ent,
1746 Object_Definition =>
1747 New_Occurrence_Of (Standard_Short_Integer, Loc),
1748 Expression => Make_Integer_Literal (Loc, Uint_0));
1750 Push_Scope (Standard_Standard);
1751 Add_Global_Declaration (Decl);
1752 Pop_Scope;
1754 -- Reset True_Constant indication, since we will indeed assign a value
1755 -- to the variable in the binder main. We also kill the Current_Value
1756 -- and Last_Assignment fields for the same reason.
1758 Set_Is_True_Constant (Elab_Ent, False);
1759 Set_Current_Value (Elab_Ent, Empty);
1760 Set_Last_Assignment (Elab_Ent, Empty);
1762 -- We do not want any further qualification of the name (if we did not
1763 -- do this, we would pick up the name of the generic package in the case
1764 -- of a library level generic instantiation).
1766 Set_Has_Qualified_Name (Elab_Ent);
1767 Set_Has_Fully_Qualified_Name (Elab_Ent);
1768 end Build_Elaboration_Entity;
1770 --------------------------------
1771 -- Build_Explicit_Dereference --
1772 --------------------------------
1774 procedure Build_Explicit_Dereference
1775 (Expr : Node_Id;
1776 Disc : Entity_Id)
1778 Loc : constant Source_Ptr := Sloc (Expr);
1779 I : Interp_Index;
1780 It : Interp;
1782 begin
1783 -- An entity of a type with a reference aspect is overloaded with
1784 -- both interpretations: with and without the dereference. Now that
1785 -- the dereference is made explicit, set the type of the node properly,
1786 -- to prevent anomalies in the backend. Same if the expression is an
1787 -- overloaded function call whose return type has a reference aspect.
1789 if Is_Entity_Name (Expr) then
1790 Set_Etype (Expr, Etype (Entity (Expr)));
1792 -- The designated entity will not be examined again when resolving
1793 -- the dereference, so generate a reference to it now.
1795 Generate_Reference (Entity (Expr), Expr);
1797 elsif Nkind (Expr) = N_Function_Call then
1799 -- If the name of the indexing function is overloaded, locate the one
1800 -- whose return type has an implicit dereference on the desired
1801 -- discriminant, and set entity and type of function call.
1803 if Is_Overloaded (Name (Expr)) then
1804 Get_First_Interp (Name (Expr), I, It);
1806 while Present (It.Nam) loop
1807 if Ekind ((It.Typ)) = E_Record_Type
1808 and then First_Entity ((It.Typ)) = Disc
1809 then
1810 Set_Entity (Name (Expr), It.Nam);
1811 Set_Etype (Name (Expr), Etype (It.Nam));
1812 exit;
1813 end if;
1815 Get_Next_Interp (I, It);
1816 end loop;
1817 end if;
1819 -- Set type of call from resolved function name.
1821 Set_Etype (Expr, Etype (Name (Expr)));
1822 end if;
1824 Set_Is_Overloaded (Expr, False);
1826 -- The expression will often be a generalized indexing that yields a
1827 -- container element that is then dereferenced, in which case the
1828 -- generalized indexing call is also non-overloaded.
1830 if Nkind (Expr) = N_Indexed_Component
1831 and then Present (Generalized_Indexing (Expr))
1832 then
1833 Set_Is_Overloaded (Generalized_Indexing (Expr), False);
1834 end if;
1836 Rewrite (Expr,
1837 Make_Explicit_Dereference (Loc,
1838 Prefix =>
1839 Make_Selected_Component (Loc,
1840 Prefix => Relocate_Node (Expr),
1841 Selector_Name => New_Occurrence_Of (Disc, Loc))));
1842 Set_Etype (Prefix (Expr), Etype (Disc));
1843 Set_Etype (Expr, Designated_Type (Etype (Disc)));
1844 end Build_Explicit_Dereference;
1846 ---------------------------
1847 -- Build_Overriding_Spec --
1848 ---------------------------
1850 function Build_Overriding_Spec
1851 (Op : Entity_Id;
1852 Typ : Entity_Id) return Node_Id
1854 Loc : constant Source_Ptr := Sloc (Typ);
1855 Par_Typ : constant Entity_Id := Find_Dispatching_Type (Op);
1856 Spec : constant Node_Id := Specification (Unit_Declaration_Node (Op));
1858 Formal_Spec : Node_Id;
1859 Formal_Type : Node_Id;
1860 New_Spec : Node_Id;
1862 begin
1863 New_Spec := Copy_Subprogram_Spec (Spec);
1865 Formal_Spec := First (Parameter_Specifications (New_Spec));
1866 while Present (Formal_Spec) loop
1867 Formal_Type := Parameter_Type (Formal_Spec);
1869 if Is_Entity_Name (Formal_Type)
1870 and then Entity (Formal_Type) = Par_Typ
1871 then
1872 Rewrite (Formal_Type, New_Occurrence_Of (Typ, Loc));
1873 end if;
1875 -- Nothing needs to be done for access parameters
1877 Next (Formal_Spec);
1878 end loop;
1880 return New_Spec;
1881 end Build_Overriding_Spec;
1883 -----------------------------------
1884 -- Cannot_Raise_Constraint_Error --
1885 -----------------------------------
1887 function Cannot_Raise_Constraint_Error (Expr : Node_Id) return Boolean is
1888 begin
1889 if Compile_Time_Known_Value (Expr) then
1890 return True;
1892 elsif Do_Range_Check (Expr) then
1893 return False;
1895 elsif Raises_Constraint_Error (Expr) then
1896 return False;
1898 else
1899 case Nkind (Expr) is
1900 when N_Identifier =>
1901 return True;
1903 when N_Expanded_Name =>
1904 return True;
1906 when N_Selected_Component =>
1907 return not Do_Discriminant_Check (Expr);
1909 when N_Attribute_Reference =>
1910 if Do_Overflow_Check (Expr) then
1911 return False;
1913 elsif No (Expressions (Expr)) then
1914 return True;
1916 else
1917 declare
1918 N : Node_Id;
1920 begin
1921 N := First (Expressions (Expr));
1922 while Present (N) loop
1923 if Cannot_Raise_Constraint_Error (N) then
1924 Next (N);
1925 else
1926 return False;
1927 end if;
1928 end loop;
1930 return True;
1931 end;
1932 end if;
1934 when N_Type_Conversion =>
1935 if Do_Overflow_Check (Expr)
1936 or else Do_Length_Check (Expr)
1937 or else Do_Tag_Check (Expr)
1938 then
1939 return False;
1940 else
1941 return Cannot_Raise_Constraint_Error (Expression (Expr));
1942 end if;
1944 when N_Unchecked_Type_Conversion =>
1945 return Cannot_Raise_Constraint_Error (Expression (Expr));
1947 when N_Unary_Op =>
1948 if Do_Overflow_Check (Expr) then
1949 return False;
1950 else
1951 return Cannot_Raise_Constraint_Error (Right_Opnd (Expr));
1952 end if;
1954 when N_Op_Divide
1955 | N_Op_Mod
1956 | N_Op_Rem
1958 if Do_Division_Check (Expr)
1959 or else
1960 Do_Overflow_Check (Expr)
1961 then
1962 return False;
1963 else
1964 return
1965 Cannot_Raise_Constraint_Error (Left_Opnd (Expr))
1966 and then
1967 Cannot_Raise_Constraint_Error (Right_Opnd (Expr));
1968 end if;
1970 when N_Op_Add
1971 | N_Op_And
1972 | N_Op_Concat
1973 | N_Op_Eq
1974 | N_Op_Expon
1975 | N_Op_Ge
1976 | N_Op_Gt
1977 | N_Op_Le
1978 | N_Op_Lt
1979 | N_Op_Multiply
1980 | N_Op_Ne
1981 | N_Op_Or
1982 | N_Op_Rotate_Left
1983 | N_Op_Rotate_Right
1984 | N_Op_Shift_Left
1985 | N_Op_Shift_Right
1986 | N_Op_Shift_Right_Arithmetic
1987 | N_Op_Subtract
1988 | N_Op_Xor
1990 if Do_Overflow_Check (Expr) then
1991 return False;
1992 else
1993 return
1994 Cannot_Raise_Constraint_Error (Left_Opnd (Expr))
1995 and then
1996 Cannot_Raise_Constraint_Error (Right_Opnd (Expr));
1997 end if;
1999 when others =>
2000 return False;
2001 end case;
2002 end if;
2003 end Cannot_Raise_Constraint_Error;
2005 -----------------------------------------
2006 -- Check_Dynamically_Tagged_Expression --
2007 -----------------------------------------
2009 procedure Check_Dynamically_Tagged_Expression
2010 (Expr : Node_Id;
2011 Typ : Entity_Id;
2012 Related_Nod : Node_Id)
2014 begin
2015 pragma Assert (Is_Tagged_Type (Typ));
2017 -- In order to avoid spurious errors when analyzing the expanded code,
2018 -- this check is done only for nodes that come from source and for
2019 -- actuals of generic instantiations.
2021 if (Comes_From_Source (Related_Nod)
2022 or else In_Generic_Actual (Expr))
2023 and then (Is_Class_Wide_Type (Etype (Expr))
2024 or else Is_Dynamically_Tagged (Expr))
2025 and then not Is_Class_Wide_Type (Typ)
2026 then
2027 Error_Msg_N ("dynamically tagged expression not allowed!", Expr);
2028 end if;
2029 end Check_Dynamically_Tagged_Expression;
2031 --------------------------
2032 -- Check_Fully_Declared --
2033 --------------------------
2035 procedure Check_Fully_Declared (T : Entity_Id; N : Node_Id) is
2036 begin
2037 if Ekind (T) = E_Incomplete_Type then
2039 -- Ada 2005 (AI-50217): If the type is available through a limited
2040 -- with_clause, verify that its full view has been analyzed.
2042 if From_Limited_With (T)
2043 and then Present (Non_Limited_View (T))
2044 and then Ekind (Non_Limited_View (T)) /= E_Incomplete_Type
2045 then
2046 -- The non-limited view is fully declared
2048 null;
2050 else
2051 Error_Msg_NE
2052 ("premature usage of incomplete}", N, First_Subtype (T));
2053 end if;
2055 -- Need comments for these tests ???
2057 elsif Has_Private_Component (T)
2058 and then not Is_Generic_Type (Root_Type (T))
2059 and then not In_Spec_Expression
2060 then
2061 -- Special case: if T is the anonymous type created for a single
2062 -- task or protected object, use the name of the source object.
2064 if Is_Concurrent_Type (T)
2065 and then not Comes_From_Source (T)
2066 and then Nkind (N) = N_Object_Declaration
2067 then
2068 Error_Msg_NE
2069 ("type of& has incomplete component",
2070 N, Defining_Identifier (N));
2071 else
2072 Error_Msg_NE
2073 ("premature usage of incomplete}",
2074 N, First_Subtype (T));
2075 end if;
2076 end if;
2077 end Check_Fully_Declared;
2079 -------------------------------------------
2080 -- Check_Function_With_Address_Parameter --
2081 -------------------------------------------
2083 procedure Check_Function_With_Address_Parameter (Subp_Id : Entity_Id) is
2084 F : Entity_Id;
2085 T : Entity_Id;
2087 begin
2088 F := First_Formal (Subp_Id);
2089 while Present (F) loop
2090 T := Etype (F);
2092 if Is_Private_Type (T) and then Present (Full_View (T)) then
2093 T := Full_View (T);
2094 end if;
2096 if Is_Descendant_Of_Address (T) or else Is_Limited_Type (T) then
2097 Set_Is_Pure (Subp_Id, False);
2098 exit;
2099 end if;
2101 Next_Formal (F);
2102 end loop;
2103 end Check_Function_With_Address_Parameter;
2105 -------------------------------------
2106 -- Check_Function_Writable_Actuals --
2107 -------------------------------------
2109 procedure Check_Function_Writable_Actuals (N : Node_Id) is
2110 Writable_Actuals_List : Elist_Id := No_Elist;
2111 Identifiers_List : Elist_Id := No_Elist;
2112 Aggr_Error_Node : Node_Id := Empty;
2113 Error_Node : Node_Id := Empty;
2115 procedure Collect_Identifiers (N : Node_Id);
2116 -- In a single traversal of subtree N collect in Writable_Actuals_List
2117 -- all the actuals of functions with writable actuals, and in the list
2118 -- Identifiers_List collect all the identifiers that are not actuals of
2119 -- functions with writable actuals. If a writable actual is referenced
2120 -- twice as writable actual then Error_Node is set to reference its
2121 -- second occurrence, the error is reported, and the tree traversal
2122 -- is abandoned.
2124 procedure Preanalyze_Without_Errors (N : Node_Id);
2125 -- Preanalyze N without reporting errors. Very dubious, you can't just
2126 -- go analyzing things more than once???
2128 -------------------------
2129 -- Collect_Identifiers --
2130 -------------------------
2132 procedure Collect_Identifiers (N : Node_Id) is
2134 function Check_Node (N : Node_Id) return Traverse_Result;
2135 -- Process a single node during the tree traversal to collect the
2136 -- writable actuals of functions and all the identifiers which are
2137 -- not writable actuals of functions.
2139 function Contains (List : Elist_Id; N : Node_Id) return Boolean;
2140 -- Returns True if List has a node whose Entity is Entity (N)
2142 ----------------
2143 -- Check_Node --
2144 ----------------
2146 function Check_Node (N : Node_Id) return Traverse_Result is
2147 Is_Writable_Actual : Boolean := False;
2148 Id : Entity_Id;
2150 begin
2151 if Nkind (N) = N_Identifier then
2153 -- No analysis possible if the entity is not decorated
2155 if No (Entity (N)) then
2156 return Skip;
2158 -- Don't collect identifiers of packages, called functions, etc
2160 elsif Ekind_In (Entity (N), E_Package,
2161 E_Function,
2162 E_Procedure,
2163 E_Entry)
2164 then
2165 return Skip;
2167 -- For rewritten nodes, continue the traversal in the original
2168 -- subtree. Needed to handle aggregates in original expressions
2169 -- extracted from the tree by Remove_Side_Effects.
2171 elsif Is_Rewrite_Substitution (N) then
2172 Collect_Identifiers (Original_Node (N));
2173 return Skip;
2175 -- For now we skip aggregate discriminants, since they require
2176 -- performing the analysis in two phases to identify conflicts:
2177 -- first one analyzing discriminants and second one analyzing
2178 -- the rest of components (since at run time, discriminants are
2179 -- evaluated prior to components): too much computation cost
2180 -- to identify a corner case???
2182 elsif Nkind (Parent (N)) = N_Component_Association
2183 and then Nkind_In (Parent (Parent (N)),
2184 N_Aggregate,
2185 N_Extension_Aggregate)
2186 then
2187 declare
2188 Choice : constant Node_Id := First (Choices (Parent (N)));
2190 begin
2191 if Ekind (Entity (N)) = E_Discriminant then
2192 return Skip;
2194 elsif Expression (Parent (N)) = N
2195 and then Nkind (Choice) = N_Identifier
2196 and then Ekind (Entity (Choice)) = E_Discriminant
2197 then
2198 return Skip;
2199 end if;
2200 end;
2202 -- Analyze if N is a writable actual of a function
2204 elsif Nkind (Parent (N)) = N_Function_Call then
2205 declare
2206 Call : constant Node_Id := Parent (N);
2207 Actual : Node_Id;
2208 Formal : Node_Id;
2210 begin
2211 Id := Get_Called_Entity (Call);
2213 -- In case of previous error, no check is possible
2215 if No (Id) then
2216 return Abandon;
2217 end if;
2219 if Ekind_In (Id, E_Function, E_Generic_Function)
2220 and then Has_Out_Or_In_Out_Parameter (Id)
2221 then
2222 Formal := First_Formal (Id);
2223 Actual := First_Actual (Call);
2224 while Present (Actual) and then Present (Formal) loop
2225 if Actual = N then
2226 if Ekind_In (Formal, E_Out_Parameter,
2227 E_In_Out_Parameter)
2228 then
2229 Is_Writable_Actual := True;
2230 end if;
2232 exit;
2233 end if;
2235 Next_Formal (Formal);
2236 Next_Actual (Actual);
2237 end loop;
2238 end if;
2239 end;
2240 end if;
2242 if Is_Writable_Actual then
2244 -- Skip checking the error in non-elementary types since
2245 -- RM 6.4.1(6.15/3) is restricted to elementary types, but
2246 -- store this actual in Writable_Actuals_List since it is
2247 -- needed to perform checks on other constructs that have
2248 -- arbitrary order of evaluation (for example, aggregates).
2250 if not Is_Elementary_Type (Etype (N)) then
2251 if not Contains (Writable_Actuals_List, N) then
2252 Append_New_Elmt (N, To => Writable_Actuals_List);
2253 end if;
2255 -- Second occurrence of an elementary type writable actual
2257 elsif Contains (Writable_Actuals_List, N) then
2259 -- Report the error on the second occurrence of the
2260 -- identifier. We cannot assume that N is the second
2261 -- occurrence (according to their location in the
2262 -- sources), since Traverse_Func walks through Field2
2263 -- last (see comment in the body of Traverse_Func).
2265 declare
2266 Elmt : Elmt_Id;
2268 begin
2269 Elmt := First_Elmt (Writable_Actuals_List);
2270 while Present (Elmt)
2271 and then Entity (Node (Elmt)) /= Entity (N)
2272 loop
2273 Next_Elmt (Elmt);
2274 end loop;
2276 if Sloc (N) > Sloc (Node (Elmt)) then
2277 Error_Node := N;
2278 else
2279 Error_Node := Node (Elmt);
2280 end if;
2282 Error_Msg_NE
2283 ("value may be affected by call to & "
2284 & "because order of evaluation is arbitrary",
2285 Error_Node, Id);
2286 return Abandon;
2287 end;
2289 -- First occurrence of a elementary type writable actual
2291 else
2292 Append_New_Elmt (N, To => Writable_Actuals_List);
2293 end if;
2295 else
2296 if Identifiers_List = No_Elist then
2297 Identifiers_List := New_Elmt_List;
2298 end if;
2300 Append_Unique_Elmt (N, Identifiers_List);
2301 end if;
2302 end if;
2304 return OK;
2305 end Check_Node;
2307 --------------
2308 -- Contains --
2309 --------------
2311 function Contains
2312 (List : Elist_Id;
2313 N : Node_Id) return Boolean
2315 pragma Assert (Nkind (N) in N_Has_Entity);
2317 Elmt : Elmt_Id;
2319 begin
2320 if List = No_Elist then
2321 return False;
2322 end if;
2324 Elmt := First_Elmt (List);
2325 while Present (Elmt) loop
2326 if Entity (Node (Elmt)) = Entity (N) then
2327 return True;
2328 else
2329 Next_Elmt (Elmt);
2330 end if;
2331 end loop;
2333 return False;
2334 end Contains;
2336 ------------------
2337 -- Do_Traversal --
2338 ------------------
2340 procedure Do_Traversal is new Traverse_Proc (Check_Node);
2341 -- The traversal procedure
2343 -- Start of processing for Collect_Identifiers
2345 begin
2346 if Present (Error_Node) then
2347 return;
2348 end if;
2350 if Nkind (N) in N_Subexpr and then Is_OK_Static_Expression (N) then
2351 return;
2352 end if;
2354 Do_Traversal (N);
2355 end Collect_Identifiers;
2357 -------------------------------
2358 -- Preanalyze_Without_Errors --
2359 -------------------------------
2361 procedure Preanalyze_Without_Errors (N : Node_Id) is
2362 Status : constant Boolean := Get_Ignore_Errors;
2363 begin
2364 Set_Ignore_Errors (True);
2365 Preanalyze (N);
2366 Set_Ignore_Errors (Status);
2367 end Preanalyze_Without_Errors;
2369 -- Start of processing for Check_Function_Writable_Actuals
2371 begin
2372 -- The check only applies to Ada 2012 code on which Check_Actuals has
2373 -- been set, and only to constructs that have multiple constituents
2374 -- whose order of evaluation is not specified by the language.
2376 if Ada_Version < Ada_2012
2377 or else not Check_Actuals (N)
2378 or else (not (Nkind (N) in N_Op)
2379 and then not (Nkind (N) in N_Membership_Test)
2380 and then not Nkind_In (N, N_Range,
2381 N_Aggregate,
2382 N_Extension_Aggregate,
2383 N_Full_Type_Declaration,
2384 N_Function_Call,
2385 N_Procedure_Call_Statement,
2386 N_Entry_Call_Statement))
2387 or else (Nkind (N) = N_Full_Type_Declaration
2388 and then not Is_Record_Type (Defining_Identifier (N)))
2390 -- In addition, this check only applies to source code, not to code
2391 -- generated by constraint checks.
2393 or else not Comes_From_Source (N)
2394 then
2395 return;
2396 end if;
2398 -- If a construct C has two or more direct constituents that are names
2399 -- or expressions whose evaluation may occur in an arbitrary order, at
2400 -- least one of which contains a function call with an in out or out
2401 -- parameter, then the construct is legal only if: for each name N that
2402 -- is passed as a parameter of mode in out or out to some inner function
2403 -- call C2 (not including the construct C itself), there is no other
2404 -- name anywhere within a direct constituent of the construct C other
2405 -- than the one containing C2, that is known to refer to the same
2406 -- object (RM 6.4.1(6.17/3)).
2408 case Nkind (N) is
2409 when N_Range =>
2410 Collect_Identifiers (Low_Bound (N));
2411 Collect_Identifiers (High_Bound (N));
2413 when N_Membership_Test
2414 | N_Op
2416 declare
2417 Expr : Node_Id;
2419 begin
2420 Collect_Identifiers (Left_Opnd (N));
2422 if Present (Right_Opnd (N)) then
2423 Collect_Identifiers (Right_Opnd (N));
2424 end if;
2426 if Nkind_In (N, N_In, N_Not_In)
2427 and then Present (Alternatives (N))
2428 then
2429 Expr := First (Alternatives (N));
2430 while Present (Expr) loop
2431 Collect_Identifiers (Expr);
2433 Next (Expr);
2434 end loop;
2435 end if;
2436 end;
2438 when N_Full_Type_Declaration =>
2439 declare
2440 function Get_Record_Part (N : Node_Id) return Node_Id;
2441 -- Return the record part of this record type definition
2443 function Get_Record_Part (N : Node_Id) return Node_Id is
2444 Type_Def : constant Node_Id := Type_Definition (N);
2445 begin
2446 if Nkind (Type_Def) = N_Derived_Type_Definition then
2447 return Record_Extension_Part (Type_Def);
2448 else
2449 return Type_Def;
2450 end if;
2451 end Get_Record_Part;
2453 Comp : Node_Id;
2454 Def_Id : Entity_Id := Defining_Identifier (N);
2455 Rec : Node_Id := Get_Record_Part (N);
2457 begin
2458 -- No need to perform any analysis if the record has no
2459 -- components
2461 if No (Rec) or else No (Component_List (Rec)) then
2462 return;
2463 end if;
2465 -- Collect the identifiers starting from the deepest
2466 -- derivation. Done to report the error in the deepest
2467 -- derivation.
2469 loop
2470 if Present (Component_List (Rec)) then
2471 Comp := First (Component_Items (Component_List (Rec)));
2472 while Present (Comp) loop
2473 if Nkind (Comp) = N_Component_Declaration
2474 and then Present (Expression (Comp))
2475 then
2476 Collect_Identifiers (Expression (Comp));
2477 end if;
2479 Next (Comp);
2480 end loop;
2481 end if;
2483 exit when No (Underlying_Type (Etype (Def_Id)))
2484 or else Base_Type (Underlying_Type (Etype (Def_Id)))
2485 = Def_Id;
2487 Def_Id := Base_Type (Underlying_Type (Etype (Def_Id)));
2488 Rec := Get_Record_Part (Parent (Def_Id));
2489 end loop;
2490 end;
2492 when N_Entry_Call_Statement
2493 | N_Subprogram_Call
2495 declare
2496 Id : constant Entity_Id := Get_Called_Entity (N);
2497 Formal : Node_Id;
2498 Actual : Node_Id;
2500 begin
2501 Formal := First_Formal (Id);
2502 Actual := First_Actual (N);
2503 while Present (Actual) and then Present (Formal) loop
2504 if Ekind_In (Formal, E_Out_Parameter,
2505 E_In_Out_Parameter)
2506 then
2507 Collect_Identifiers (Actual);
2508 end if;
2510 Next_Formal (Formal);
2511 Next_Actual (Actual);
2512 end loop;
2513 end;
2515 when N_Aggregate
2516 | N_Extension_Aggregate
2518 declare
2519 Assoc : Node_Id;
2520 Choice : Node_Id;
2521 Comp_Expr : Node_Id;
2523 begin
2524 -- Handle the N_Others_Choice of array aggregates with static
2525 -- bounds. There is no need to perform this analysis in
2526 -- aggregates without static bounds since we cannot evaluate
2527 -- if the N_Others_Choice covers several elements. There is
2528 -- no need to handle the N_Others choice of record aggregates
2529 -- since at this stage it has been already expanded by
2530 -- Resolve_Record_Aggregate.
2532 if Is_Array_Type (Etype (N))
2533 and then Nkind (N) = N_Aggregate
2534 and then Present (Aggregate_Bounds (N))
2535 and then Compile_Time_Known_Bounds (Etype (N))
2536 and then Expr_Value (High_Bound (Aggregate_Bounds (N)))
2538 Expr_Value (Low_Bound (Aggregate_Bounds (N)))
2539 then
2540 declare
2541 Count_Components : Uint := Uint_0;
2542 Num_Components : Uint;
2543 Others_Assoc : Node_Id;
2544 Others_Choice : Node_Id := Empty;
2545 Others_Box_Present : Boolean := False;
2547 begin
2548 -- Count positional associations
2550 if Present (Expressions (N)) then
2551 Comp_Expr := First (Expressions (N));
2552 while Present (Comp_Expr) loop
2553 Count_Components := Count_Components + 1;
2554 Next (Comp_Expr);
2555 end loop;
2556 end if;
2558 -- Count the rest of elements and locate the N_Others
2559 -- choice (if any)
2561 Assoc := First (Component_Associations (N));
2562 while Present (Assoc) loop
2563 Choice := First (Choices (Assoc));
2564 while Present (Choice) loop
2565 if Nkind (Choice) = N_Others_Choice then
2566 Others_Assoc := Assoc;
2567 Others_Choice := Choice;
2568 Others_Box_Present := Box_Present (Assoc);
2570 -- Count several components
2572 elsif Nkind_In (Choice, N_Range,
2573 N_Subtype_Indication)
2574 or else (Is_Entity_Name (Choice)
2575 and then Is_Type (Entity (Choice)))
2576 then
2577 declare
2578 L, H : Node_Id;
2579 begin
2580 Get_Index_Bounds (Choice, L, H);
2581 pragma Assert
2582 (Compile_Time_Known_Value (L)
2583 and then Compile_Time_Known_Value (H));
2584 Count_Components :=
2585 Count_Components
2586 + Expr_Value (H) - Expr_Value (L) + 1;
2587 end;
2589 -- Count single component. No other case available
2590 -- since we are handling an aggregate with static
2591 -- bounds.
2593 else
2594 pragma Assert (Is_OK_Static_Expression (Choice)
2595 or else Nkind (Choice) = N_Identifier
2596 or else Nkind (Choice) = N_Integer_Literal);
2598 Count_Components := Count_Components + 1;
2599 end if;
2601 Next (Choice);
2602 end loop;
2604 Next (Assoc);
2605 end loop;
2607 Num_Components :=
2608 Expr_Value (High_Bound (Aggregate_Bounds (N))) -
2609 Expr_Value (Low_Bound (Aggregate_Bounds (N))) + 1;
2611 pragma Assert (Count_Components <= Num_Components);
2613 -- Handle the N_Others choice if it covers several
2614 -- components
2616 if Present (Others_Choice)
2617 and then (Num_Components - Count_Components) > 1
2618 then
2619 if not Others_Box_Present then
2621 -- At this stage, if expansion is active, the
2622 -- expression of the others choice has not been
2623 -- analyzed. Hence we generate a duplicate and
2624 -- we analyze it silently to have available the
2625 -- minimum decoration required to collect the
2626 -- identifiers.
2628 if not Expander_Active then
2629 Comp_Expr := Expression (Others_Assoc);
2630 else
2631 Comp_Expr :=
2632 New_Copy_Tree (Expression (Others_Assoc));
2633 Preanalyze_Without_Errors (Comp_Expr);
2634 end if;
2636 Collect_Identifiers (Comp_Expr);
2638 if Writable_Actuals_List /= No_Elist then
2640 -- As suggested by Robert, at current stage we
2641 -- report occurrences of this case as warnings.
2643 Error_Msg_N
2644 ("writable function parameter may affect "
2645 & "value in other component because order "
2646 & "of evaluation is unspecified??",
2647 Node (First_Elmt (Writable_Actuals_List)));
2648 end if;
2649 end if;
2650 end if;
2651 end;
2653 -- For an array aggregate, a discrete_choice_list that has
2654 -- a nonstatic range is considered as two or more separate
2655 -- occurrences of the expression (RM 6.4.1(20/3)).
2657 elsif Is_Array_Type (Etype (N))
2658 and then Nkind (N) = N_Aggregate
2659 and then Present (Aggregate_Bounds (N))
2660 and then not Compile_Time_Known_Bounds (Etype (N))
2661 then
2662 -- Collect identifiers found in the dynamic bounds
2664 declare
2665 Count_Components : Natural := 0;
2666 Low, High : Node_Id;
2668 begin
2669 Assoc := First (Component_Associations (N));
2670 while Present (Assoc) loop
2671 Choice := First (Choices (Assoc));
2672 while Present (Choice) loop
2673 if Nkind_In (Choice, N_Range,
2674 N_Subtype_Indication)
2675 or else (Is_Entity_Name (Choice)
2676 and then Is_Type (Entity (Choice)))
2677 then
2678 Get_Index_Bounds (Choice, Low, High);
2680 if not Compile_Time_Known_Value (Low) then
2681 Collect_Identifiers (Low);
2683 if No (Aggr_Error_Node) then
2684 Aggr_Error_Node := Low;
2685 end if;
2686 end if;
2688 if not Compile_Time_Known_Value (High) then
2689 Collect_Identifiers (High);
2691 if No (Aggr_Error_Node) then
2692 Aggr_Error_Node := High;
2693 end if;
2694 end if;
2696 -- The RM rule is violated if there is more than
2697 -- a single choice in a component association.
2699 else
2700 Count_Components := Count_Components + 1;
2702 if No (Aggr_Error_Node)
2703 and then Count_Components > 1
2704 then
2705 Aggr_Error_Node := Choice;
2706 end if;
2708 if not Compile_Time_Known_Value (Choice) then
2709 Collect_Identifiers (Choice);
2710 end if;
2711 end if;
2713 Next (Choice);
2714 end loop;
2716 Next (Assoc);
2717 end loop;
2718 end;
2719 end if;
2721 -- Handle ancestor part of extension aggregates
2723 if Nkind (N) = N_Extension_Aggregate then
2724 Collect_Identifiers (Ancestor_Part (N));
2725 end if;
2727 -- Handle positional associations
2729 if Present (Expressions (N)) then
2730 Comp_Expr := First (Expressions (N));
2731 while Present (Comp_Expr) loop
2732 if not Is_OK_Static_Expression (Comp_Expr) then
2733 Collect_Identifiers (Comp_Expr);
2734 end if;
2736 Next (Comp_Expr);
2737 end loop;
2738 end if;
2740 -- Handle discrete associations
2742 if Present (Component_Associations (N)) then
2743 Assoc := First (Component_Associations (N));
2744 while Present (Assoc) loop
2746 if not Box_Present (Assoc) then
2747 Choice := First (Choices (Assoc));
2748 while Present (Choice) loop
2750 -- For now we skip discriminants since it requires
2751 -- performing the analysis in two phases: first one
2752 -- analyzing discriminants and second one analyzing
2753 -- the rest of components since discriminants are
2754 -- evaluated prior to components: too much extra
2755 -- work to detect a corner case???
2757 if Nkind (Choice) in N_Has_Entity
2758 and then Present (Entity (Choice))
2759 and then Ekind (Entity (Choice)) = E_Discriminant
2760 then
2761 null;
2763 elsif Box_Present (Assoc) then
2764 null;
2766 else
2767 if not Analyzed (Expression (Assoc)) then
2768 Comp_Expr :=
2769 New_Copy_Tree (Expression (Assoc));
2770 Set_Parent (Comp_Expr, Parent (N));
2771 Preanalyze_Without_Errors (Comp_Expr);
2772 else
2773 Comp_Expr := Expression (Assoc);
2774 end if;
2776 Collect_Identifiers (Comp_Expr);
2777 end if;
2779 Next (Choice);
2780 end loop;
2781 end if;
2783 Next (Assoc);
2784 end loop;
2785 end if;
2786 end;
2788 when others =>
2789 return;
2790 end case;
2792 -- No further action needed if we already reported an error
2794 if Present (Error_Node) then
2795 return;
2796 end if;
2798 -- Check violation of RM 6.20/3 in aggregates
2800 if Present (Aggr_Error_Node)
2801 and then Writable_Actuals_List /= No_Elist
2802 then
2803 Error_Msg_N
2804 ("value may be affected by call in other component because they "
2805 & "are evaluated in unspecified order",
2806 Node (First_Elmt (Writable_Actuals_List)));
2807 return;
2808 end if;
2810 -- Check if some writable argument of a function is referenced
2812 if Writable_Actuals_List /= No_Elist
2813 and then Identifiers_List /= No_Elist
2814 then
2815 declare
2816 Elmt_1 : Elmt_Id;
2817 Elmt_2 : Elmt_Id;
2819 begin
2820 Elmt_1 := First_Elmt (Writable_Actuals_List);
2821 while Present (Elmt_1) loop
2822 Elmt_2 := First_Elmt (Identifiers_List);
2823 while Present (Elmt_2) loop
2824 if Entity (Node (Elmt_1)) = Entity (Node (Elmt_2)) then
2825 case Nkind (Parent (Node (Elmt_2))) is
2826 when N_Aggregate
2827 | N_Component_Association
2828 | N_Component_Declaration
2830 Error_Msg_N
2831 ("value may be affected by call in other "
2832 & "component because they are evaluated "
2833 & "in unspecified order",
2834 Node (Elmt_2));
2836 when N_In
2837 | N_Not_In
2839 Error_Msg_N
2840 ("value may be affected by call in other "
2841 & "alternative because they are evaluated "
2842 & "in unspecified order",
2843 Node (Elmt_2));
2845 when others =>
2846 Error_Msg_N
2847 ("value of actual may be affected by call in "
2848 & "other actual because they are evaluated "
2849 & "in unspecified order",
2850 Node (Elmt_2));
2851 end case;
2852 end if;
2854 Next_Elmt (Elmt_2);
2855 end loop;
2857 Next_Elmt (Elmt_1);
2858 end loop;
2859 end;
2860 end if;
2861 end Check_Function_Writable_Actuals;
2863 --------------------------------
2864 -- Check_Implicit_Dereference --
2865 --------------------------------
2867 procedure Check_Implicit_Dereference (N : Node_Id; Typ : Entity_Id) is
2868 Disc : Entity_Id;
2869 Desig : Entity_Id;
2870 Nam : Node_Id;
2872 begin
2873 if Nkind (N) = N_Indexed_Component
2874 and then Present (Generalized_Indexing (N))
2875 then
2876 Nam := Generalized_Indexing (N);
2877 else
2878 Nam := N;
2879 end if;
2881 if Ada_Version < Ada_2012
2882 or else not Has_Implicit_Dereference (Base_Type (Typ))
2883 then
2884 return;
2886 elsif not Comes_From_Source (N)
2887 and then Nkind (N) /= N_Indexed_Component
2888 then
2889 return;
2891 elsif Is_Entity_Name (Nam) and then Is_Type (Entity (Nam)) then
2892 null;
2894 else
2895 Disc := First_Discriminant (Typ);
2896 while Present (Disc) loop
2897 if Has_Implicit_Dereference (Disc) then
2898 Desig := Designated_Type (Etype (Disc));
2899 Add_One_Interp (Nam, Disc, Desig);
2901 -- If the node is a generalized indexing, add interpretation
2902 -- to that node as well, for subsequent resolution.
2904 if Nkind (N) = N_Indexed_Component then
2905 Add_One_Interp (N, Disc, Desig);
2906 end if;
2908 -- If the operation comes from a generic unit and the context
2909 -- is a selected component, the selector name may be global
2910 -- and set in the instance already. Remove the entity to
2911 -- force resolution of the selected component, and the
2912 -- generation of an explicit dereference if needed.
2914 if In_Instance
2915 and then Nkind (Parent (Nam)) = N_Selected_Component
2916 then
2917 Set_Entity (Selector_Name (Parent (Nam)), Empty);
2918 end if;
2920 exit;
2921 end if;
2923 Next_Discriminant (Disc);
2924 end loop;
2925 end if;
2926 end Check_Implicit_Dereference;
2928 ----------------------------------
2929 -- Check_Internal_Protected_Use --
2930 ----------------------------------
2932 procedure Check_Internal_Protected_Use (N : Node_Id; Nam : Entity_Id) is
2933 S : Entity_Id;
2934 Prot : Entity_Id;
2936 begin
2937 Prot := Empty;
2939 S := Current_Scope;
2940 while Present (S) loop
2941 if S = Standard_Standard then
2942 exit;
2944 elsif Ekind (S) = E_Function
2945 and then Ekind (Scope (S)) = E_Protected_Type
2946 then
2947 Prot := Scope (S);
2948 exit;
2949 end if;
2951 S := Scope (S);
2952 end loop;
2954 if Present (Prot)
2955 and then Scope (Nam) = Prot
2956 and then Ekind (Nam) /= E_Function
2957 then
2958 -- An indirect function call (e.g. a callback within a protected
2959 -- function body) is not statically illegal. If the access type is
2960 -- anonymous and is the type of an access parameter, the scope of Nam
2961 -- will be the protected type, but it is not a protected operation.
2963 if Ekind (Nam) = E_Subprogram_Type
2964 and then Nkind (Associated_Node_For_Itype (Nam)) =
2965 N_Function_Specification
2966 then
2967 null;
2969 elsif Nkind (N) = N_Subprogram_Renaming_Declaration then
2970 Error_Msg_N
2971 ("within protected function cannot use protected procedure in "
2972 & "renaming or as generic actual", N);
2974 elsif Nkind (N) = N_Attribute_Reference then
2975 Error_Msg_N
2976 ("within protected function cannot take access of protected "
2977 & "procedure", N);
2979 else
2980 Error_Msg_N
2981 ("within protected function, protected object is constant", N);
2982 Error_Msg_N
2983 ("\cannot call operation that may modify it", N);
2984 end if;
2985 end if;
2987 -- Verify that an internal call does not appear within a precondition
2988 -- of a protected operation. This implements AI12-0166.
2989 -- The precondition aspect has been rewritten as a pragma Precondition
2990 -- and we check whether the scope of the called subprogram is the same
2991 -- as that of the entity to which the aspect applies.
2993 if Convention (Nam) = Convention_Protected then
2994 declare
2995 P : Node_Id;
2997 begin
2998 P := Parent (N);
2999 while Present (P) loop
3000 if Nkind (P) = N_Pragma
3001 and then Chars (Pragma_Identifier (P)) = Name_Precondition
3002 and then From_Aspect_Specification (P)
3003 and then
3004 Scope (Entity (Corresponding_Aspect (P))) = Scope (Nam)
3005 then
3006 Error_Msg_N
3007 ("internal call cannot appear in precondition of "
3008 & "protected operation", N);
3009 return;
3011 elsif Nkind (P) = N_Pragma
3012 and then Chars (Pragma_Identifier (P)) = Name_Contract_Cases
3013 then
3014 -- Check whether call is in a case guard. It is legal in a
3015 -- consequence.
3017 P := N;
3018 while Present (P) loop
3019 if Nkind (Parent (P)) = N_Component_Association
3020 and then P /= Expression (Parent (P))
3021 then
3022 Error_Msg_N
3023 ("internal call cannot appear in case guard in a "
3024 & "contract case", N);
3025 end if;
3027 P := Parent (P);
3028 end loop;
3030 return;
3032 elsif Nkind (P) = N_Parameter_Specification
3033 and then Scope (Current_Scope) = Scope (Nam)
3034 and then Nkind_In (Parent (P), N_Entry_Declaration,
3035 N_Subprogram_Declaration)
3036 then
3037 Error_Msg_N
3038 ("internal call cannot appear in default for formal of "
3039 & "protected operation", N);
3040 return;
3041 end if;
3043 P := Parent (P);
3044 end loop;
3045 end;
3046 end if;
3047 end Check_Internal_Protected_Use;
3049 ---------------------------------------
3050 -- Check_Later_Vs_Basic_Declarations --
3051 ---------------------------------------
3053 procedure Check_Later_Vs_Basic_Declarations
3054 (Decls : List_Id;
3055 During_Parsing : Boolean)
3057 Body_Sloc : Source_Ptr;
3058 Decl : Node_Id;
3060 function Is_Later_Declarative_Item (Decl : Node_Id) return Boolean;
3061 -- Return whether Decl is considered as a declarative item.
3062 -- When During_Parsing is True, the semantics of Ada 83 is followed.
3063 -- When During_Parsing is False, the semantics of SPARK is followed.
3065 -------------------------------
3066 -- Is_Later_Declarative_Item --
3067 -------------------------------
3069 function Is_Later_Declarative_Item (Decl : Node_Id) return Boolean is
3070 begin
3071 if Nkind (Decl) in N_Later_Decl_Item then
3072 return True;
3074 elsif Nkind (Decl) = N_Pragma then
3075 return True;
3077 elsif During_Parsing then
3078 return False;
3080 -- In SPARK, a package declaration is not considered as a later
3081 -- declarative item.
3083 elsif Nkind (Decl) = N_Package_Declaration then
3084 return False;
3086 -- In SPARK, a renaming is considered as a later declarative item
3088 elsif Nkind (Decl) in N_Renaming_Declaration then
3089 return True;
3091 else
3092 return False;
3093 end if;
3094 end Is_Later_Declarative_Item;
3096 -- Start of processing for Check_Later_Vs_Basic_Declarations
3098 begin
3099 Decl := First (Decls);
3101 -- Loop through sequence of basic declarative items
3103 Outer : while Present (Decl) loop
3104 if not Nkind_In (Decl, N_Subprogram_Body, N_Package_Body, N_Task_Body)
3105 and then Nkind (Decl) not in N_Body_Stub
3106 then
3107 Next (Decl);
3109 -- Once a body is encountered, we only allow later declarative
3110 -- items. The inner loop checks the rest of the list.
3112 else
3113 Body_Sloc := Sloc (Decl);
3115 Inner : while Present (Decl) loop
3116 if not Is_Later_Declarative_Item (Decl) then
3117 if During_Parsing then
3118 if Ada_Version = Ada_83 then
3119 Error_Msg_Sloc := Body_Sloc;
3120 Error_Msg_N
3121 ("(Ada 83) decl cannot appear after body#", Decl);
3122 end if;
3123 else
3124 Error_Msg_Sloc := Body_Sloc;
3125 Check_SPARK_05_Restriction
3126 ("decl cannot appear after body#", Decl);
3127 end if;
3128 end if;
3130 Next (Decl);
3131 end loop Inner;
3132 end if;
3133 end loop Outer;
3134 end Check_Later_Vs_Basic_Declarations;
3136 ---------------------------
3137 -- Check_No_Hidden_State --
3138 ---------------------------
3140 procedure Check_No_Hidden_State (Id : Entity_Id) is
3141 function Has_Null_Abstract_State (Pkg : Entity_Id) return Boolean;
3142 -- Determine whether the entity of a package denoted by Pkg has a null
3143 -- abstract state.
3145 -----------------------------
3146 -- Has_Null_Abstract_State --
3147 -----------------------------
3149 function Has_Null_Abstract_State (Pkg : Entity_Id) return Boolean is
3150 States : constant Elist_Id := Abstract_States (Pkg);
3152 begin
3153 -- Check first available state of related package. A null abstract
3154 -- state always appears as the sole element of the state list.
3156 return
3157 Present (States)
3158 and then Is_Null_State (Node (First_Elmt (States)));
3159 end Has_Null_Abstract_State;
3161 -- Local variables
3163 Context : Entity_Id := Empty;
3164 Not_Visible : Boolean := False;
3165 Scop : Entity_Id;
3167 -- Start of processing for Check_No_Hidden_State
3169 begin
3170 pragma Assert (Ekind_In (Id, E_Abstract_State, E_Variable));
3172 -- Find the proper context where the object or state appears
3174 Scop := Scope (Id);
3175 while Present (Scop) loop
3176 Context := Scop;
3178 -- Keep track of the context's visibility
3180 Not_Visible := Not_Visible or else In_Private_Part (Context);
3182 -- Prevent the search from going too far
3184 if Context = Standard_Standard then
3185 return;
3187 -- Objects and states that appear immediately within a subprogram or
3188 -- inside a construct nested within a subprogram do not introduce a
3189 -- hidden state. They behave as local variable declarations.
3191 elsif Is_Subprogram (Context) then
3192 return;
3194 -- When examining a package body, use the entity of the spec as it
3195 -- carries the abstract state declarations.
3197 elsif Ekind (Context) = E_Package_Body then
3198 Context := Spec_Entity (Context);
3199 end if;
3201 -- Stop the traversal when a package subject to a null abstract state
3202 -- has been found.
3204 if Ekind_In (Context, E_Generic_Package, E_Package)
3205 and then Has_Null_Abstract_State (Context)
3206 then
3207 exit;
3208 end if;
3210 Scop := Scope (Scop);
3211 end loop;
3213 -- At this point we know that there is at least one package with a null
3214 -- abstract state in visibility. Emit an error message unconditionally
3215 -- if the entity being processed is a state because the placement of the
3216 -- related package is irrelevant. This is not the case for objects as
3217 -- the intermediate context matters.
3219 if Present (Context)
3220 and then (Ekind (Id) = E_Abstract_State or else Not_Visible)
3221 then
3222 Error_Msg_N ("cannot introduce hidden state &", Id);
3223 Error_Msg_NE ("\package & has null abstract state", Id, Context);
3224 end if;
3225 end Check_No_Hidden_State;
3227 ----------------------------------------
3228 -- Check_Nonvolatile_Function_Profile --
3229 ----------------------------------------
3231 procedure Check_Nonvolatile_Function_Profile (Func_Id : Entity_Id) is
3232 Formal : Entity_Id;
3234 begin
3235 -- Inspect all formal parameters
3237 Formal := First_Formal (Func_Id);
3238 while Present (Formal) loop
3239 if Is_Effectively_Volatile (Etype (Formal)) then
3240 Error_Msg_NE
3241 ("nonvolatile function & cannot have a volatile parameter",
3242 Formal, Func_Id);
3243 end if;
3245 Next_Formal (Formal);
3246 end loop;
3248 -- Inspect the return type
3250 if Is_Effectively_Volatile (Etype (Func_Id)) then
3251 Error_Msg_NE
3252 ("nonvolatile function & cannot have a volatile return type",
3253 Result_Definition (Parent (Func_Id)), Func_Id);
3254 end if;
3255 end Check_Nonvolatile_Function_Profile;
3257 -----------------------------
3258 -- Check_Part_Of_Reference --
3259 -----------------------------
3261 procedure Check_Part_Of_Reference (Var_Id : Entity_Id; Ref : Node_Id) is
3262 Conc_Obj : constant Entity_Id := Encapsulating_State (Var_Id);
3263 Decl : Node_Id;
3264 OK_Use : Boolean := False;
3265 Par : Node_Id;
3266 Prag_Nam : Name_Id;
3267 Spec_Id : Entity_Id;
3269 begin
3270 -- Traverse the parent chain looking for a suitable context for the
3271 -- reference to the concurrent constituent.
3273 Par := Parent (Ref);
3274 while Present (Par) loop
3275 if Nkind (Par) = N_Pragma then
3276 Prag_Nam := Pragma_Name (Par);
3278 -- A concurrent constituent is allowed to appear in pragmas
3279 -- Initial_Condition and Initializes as this is part of the
3280 -- elaboration checks for the constituent (SPARK RM 9.3).
3282 if Nam_In (Prag_Nam, Name_Initial_Condition, Name_Initializes) then
3283 OK_Use := True;
3284 exit;
3286 -- When the reference appears within pragma Depends or Global,
3287 -- check whether the pragma applies to a single task type. Note
3288 -- that the pragma is not encapsulated by the type definition,
3289 -- but this is still a valid context.
3291 elsif Nam_In (Prag_Nam, Name_Depends, Name_Global) then
3292 Decl := Find_Related_Declaration_Or_Body (Par);
3294 if Nkind (Decl) = N_Object_Declaration
3295 and then Defining_Entity (Decl) = Conc_Obj
3296 then
3297 OK_Use := True;
3298 exit;
3299 end if;
3300 end if;
3302 -- The reference appears somewhere in the definition of the single
3303 -- protected/task type (SPARK RM 9.3).
3305 elsif Nkind_In (Par, N_Single_Protected_Declaration,
3306 N_Single_Task_Declaration)
3307 and then Defining_Entity (Par) = Conc_Obj
3308 then
3309 OK_Use := True;
3310 exit;
3312 -- The reference appears within the expanded declaration or the body
3313 -- of the single protected/task type (SPARK RM 9.3).
3315 elsif Nkind_In (Par, N_Protected_Body,
3316 N_Protected_Type_Declaration,
3317 N_Task_Body,
3318 N_Task_Type_Declaration)
3319 then
3320 Spec_Id := Unique_Defining_Entity (Par);
3322 if Present (Anonymous_Object (Spec_Id))
3323 and then Anonymous_Object (Spec_Id) = Conc_Obj
3324 then
3325 OK_Use := True;
3326 exit;
3327 end if;
3329 -- The reference has been relocated within an internally generated
3330 -- package or subprogram. Assume that the reference is legal as the
3331 -- real check was already performed in the original context of the
3332 -- reference.
3334 elsif Nkind_In (Par, N_Package_Body,
3335 N_Package_Declaration,
3336 N_Subprogram_Body,
3337 N_Subprogram_Declaration)
3338 and then not Comes_From_Source (Par)
3339 then
3340 -- Continue to examine the context if the reference appears in a
3341 -- subprogram body which was previously an expression function.
3343 if Nkind (Par) = N_Subprogram_Body
3344 and then Was_Expression_Function (Par)
3345 then
3346 null;
3348 -- Otherwise the reference is legal
3350 else
3351 OK_Use := True;
3352 exit;
3353 end if;
3355 -- The reference has been relocated to an inlined body for GNATprove.
3356 -- Assume that the reference is legal as the real check was already
3357 -- performed in the original context of the reference.
3359 elsif GNATprove_Mode
3360 and then Nkind (Par) = N_Subprogram_Body
3361 and then Chars (Defining_Entity (Par)) = Name_uParent
3362 then
3363 OK_Use := True;
3364 exit;
3365 end if;
3367 Par := Parent (Par);
3368 end loop;
3370 -- The reference is illegal as it appears outside the definition or
3371 -- body of the single protected/task type.
3373 if not OK_Use then
3374 Error_Msg_NE
3375 ("reference to variable & cannot appear in this context",
3376 Ref, Var_Id);
3377 Error_Msg_Name_1 := Chars (Var_Id);
3379 if Is_Single_Protected_Object (Conc_Obj) then
3380 Error_Msg_NE
3381 ("\% is constituent of single protected type &", Ref, Conc_Obj);
3383 else
3384 Error_Msg_NE
3385 ("\% is constituent of single task type &", Ref, Conc_Obj);
3386 end if;
3387 end if;
3388 end Check_Part_Of_Reference;
3390 ------------------------------------------
3391 -- Check_Potentially_Blocking_Operation --
3392 ------------------------------------------
3394 procedure Check_Potentially_Blocking_Operation (N : Node_Id) is
3395 S : Entity_Id;
3397 begin
3398 -- N is one of the potentially blocking operations listed in 9.5.1(8).
3399 -- When pragma Detect_Blocking is active, the run time will raise
3400 -- Program_Error. Here we only issue a warning, since we generally
3401 -- support the use of potentially blocking operations in the absence
3402 -- of the pragma.
3404 -- Indirect blocking through a subprogram call cannot be diagnosed
3405 -- statically without interprocedural analysis, so we do not attempt
3406 -- to do it here.
3408 S := Scope (Current_Scope);
3409 while Present (S) and then S /= Standard_Standard loop
3410 if Is_Protected_Type (S) then
3411 Error_Msg_N
3412 ("potentially blocking operation in protected operation??", N);
3413 return;
3414 end if;
3416 S := Scope (S);
3417 end loop;
3418 end Check_Potentially_Blocking_Operation;
3420 ------------------------------------
3421 -- Check_Previous_Null_Procedure --
3422 ------------------------------------
3424 procedure Check_Previous_Null_Procedure
3425 (Decl : Node_Id;
3426 Prev : Entity_Id)
3428 begin
3429 if Ekind (Prev) = E_Procedure
3430 and then Nkind (Parent (Prev)) = N_Procedure_Specification
3431 and then Null_Present (Parent (Prev))
3432 then
3433 Error_Msg_Sloc := Sloc (Prev);
3434 Error_Msg_N
3435 ("declaration cannot complete previous null procedure#", Decl);
3436 end if;
3437 end Check_Previous_Null_Procedure;
3439 ---------------------------------
3440 -- Check_Result_And_Post_State --
3441 ---------------------------------
3443 procedure Check_Result_And_Post_State (Subp_Id : Entity_Id) is
3444 procedure Check_Result_And_Post_State_In_Pragma
3445 (Prag : Node_Id;
3446 Result_Seen : in out Boolean);
3447 -- Determine whether pragma Prag mentions attribute 'Result and whether
3448 -- the pragma contains an expression that evaluates differently in pre-
3449 -- and post-state. Prag is a [refined] postcondition or a contract-cases
3450 -- pragma. Result_Seen is set when the pragma mentions attribute 'Result
3452 function Has_In_Out_Parameter (Subp_Id : Entity_Id) return Boolean;
3453 -- Determine whether subprogram Subp_Id contains at least one IN OUT
3454 -- formal parameter.
3456 -------------------------------------------
3457 -- Check_Result_And_Post_State_In_Pragma --
3458 -------------------------------------------
3460 procedure Check_Result_And_Post_State_In_Pragma
3461 (Prag : Node_Id;
3462 Result_Seen : in out Boolean)
3464 procedure Check_Conjunct (Expr : Node_Id);
3465 -- Check an individual conjunct in a conjunction of Boolean
3466 -- expressions, connected by "and" or "and then" operators.
3468 procedure Check_Conjuncts (Expr : Node_Id);
3469 -- Apply the post-state check to every conjunct in an expression, in
3470 -- case this is a conjunction of Boolean expressions. Otherwise apply
3471 -- it to the expression as a whole.
3473 procedure Check_Expression (Expr : Node_Id);
3474 -- Perform the 'Result and post-state checks on a given expression
3476 function Is_Function_Result (N : Node_Id) return Traverse_Result;
3477 -- Attempt to find attribute 'Result in a subtree denoted by N
3479 function Is_Trivial_Boolean (N : Node_Id) return Boolean;
3480 -- Determine whether source node N denotes "True" or "False"
3482 function Mentions_Post_State (N : Node_Id) return Boolean;
3483 -- Determine whether a subtree denoted by N mentions any construct
3484 -- that denotes a post-state.
3486 procedure Check_Function_Result is
3487 new Traverse_Proc (Is_Function_Result);
3489 --------------------
3490 -- Check_Conjunct --
3491 --------------------
3493 procedure Check_Conjunct (Expr : Node_Id) is
3494 function Adjust_Message (Msg : String) return String;
3495 -- Prepend a prefix to the input message Msg denoting that the
3496 -- message applies to a conjunct in the expression, when this
3497 -- is the case.
3499 function Applied_On_Conjunct return Boolean;
3500 -- Returns True if the message applies to a conjunct in the
3501 -- expression, instead of the whole expression.
3503 function Has_Global_Output (Subp : Entity_Id) return Boolean;
3504 -- Returns True if Subp has an output in its Global contract
3506 function Has_No_Output (Subp : Entity_Id) return Boolean;
3507 -- Returns True if Subp has no declared output: no function
3508 -- result, no output parameter, and no output in its Global
3509 -- contract.
3511 --------------------
3512 -- Adjust_Message --
3513 --------------------
3515 function Adjust_Message (Msg : String) return String is
3516 begin
3517 if Applied_On_Conjunct then
3518 return "conjunct in " & Msg;
3519 else
3520 return Msg;
3521 end if;
3522 end Adjust_Message;
3524 -------------------------
3525 -- Applied_On_Conjunct --
3526 -------------------------
3528 function Applied_On_Conjunct return Boolean is
3529 begin
3530 -- Expr is the conjunct of an enclosing "and" expression
3532 return Nkind (Parent (Expr)) in N_Subexpr
3534 -- or Expr is a conjunct of an enclosing "and then"
3535 -- expression in a postcondition aspect that was split into
3536 -- multiple pragmas. The first conjunct has the "and then"
3537 -- expression as Original_Node, and other conjuncts have
3538 -- Split_PCC set to True.
3540 or else Nkind (Original_Node (Expr)) = N_And_Then
3541 or else Split_PPC (Prag);
3542 end Applied_On_Conjunct;
3544 -----------------------
3545 -- Has_Global_Output --
3546 -----------------------
3548 function Has_Global_Output (Subp : Entity_Id) return Boolean is
3549 Global : constant Node_Id := Get_Pragma (Subp, Pragma_Global);
3550 List : Node_Id;
3551 Assoc : Node_Id;
3553 begin
3554 if No (Global) then
3555 return False;
3556 end if;
3558 List := Expression (Get_Argument (Global, Subp));
3560 -- Empty list (no global items) or single global item
3561 -- declaration (only input items).
3563 if Nkind_In (List, N_Null,
3564 N_Expanded_Name,
3565 N_Identifier,
3566 N_Selected_Component)
3567 then
3568 return False;
3570 -- Simple global list (only input items) or moded global list
3571 -- declaration.
3573 elsif Nkind (List) = N_Aggregate then
3574 if Present (Expressions (List)) then
3575 return False;
3577 else
3578 Assoc := First (Component_Associations (List));
3579 while Present (Assoc) loop
3580 if Chars (First (Choices (Assoc))) /= Name_Input then
3581 return True;
3582 end if;
3584 Next (Assoc);
3585 end loop;
3587 return False;
3588 end if;
3590 -- To accommodate partial decoration of disabled SPARK
3591 -- features, this routine may be called with illegal input.
3592 -- If this is the case, do not raise Program_Error.
3594 else
3595 return False;
3596 end if;
3597 end Has_Global_Output;
3599 -------------------
3600 -- Has_No_Output --
3601 -------------------
3603 function Has_No_Output (Subp : Entity_Id) return Boolean is
3604 Param : Node_Id;
3606 begin
3607 -- A function has its result as output
3609 if Ekind (Subp) = E_Function then
3610 return False;
3611 end if;
3613 -- An OUT or IN OUT parameter is an output
3615 Param := First_Formal (Subp);
3616 while Present (Param) loop
3617 if Ekind_In (Param, E_Out_Parameter, E_In_Out_Parameter) then
3618 return False;
3619 end if;
3621 Next_Formal (Param);
3622 end loop;
3624 -- An item of mode Output or In_Out in the Global contract is
3625 -- an output.
3627 if Has_Global_Output (Subp) then
3628 return False;
3629 end if;
3631 return True;
3632 end Has_No_Output;
3634 -- Local variables
3636 Err_Node : Node_Id;
3637 -- Error node when reporting a warning on a (refined)
3638 -- postcondition.
3640 -- Start of processing for Check_Conjunct
3642 begin
3643 if Applied_On_Conjunct then
3644 Err_Node := Expr;
3645 else
3646 Err_Node := Prag;
3647 end if;
3649 -- Do not report missing reference to outcome in postcondition if
3650 -- either the postcondition is trivially True or False, or if the
3651 -- subprogram is ghost and has no declared output.
3653 if not Is_Trivial_Boolean (Expr)
3654 and then not Mentions_Post_State (Expr)
3655 and then not (Is_Ghost_Entity (Subp_Id)
3656 and then Has_No_Output (Subp_Id))
3657 then
3658 if Pragma_Name (Prag) = Name_Contract_Cases then
3659 Error_Msg_NE (Adjust_Message
3660 ("contract case does not check the outcome of calling "
3661 & "&?T?"), Expr, Subp_Id);
3663 elsif Pragma_Name (Prag) = Name_Refined_Post then
3664 Error_Msg_NE (Adjust_Message
3665 ("refined postcondition does not check the outcome of "
3666 & "calling &?T?"), Err_Node, Subp_Id);
3668 else
3669 Error_Msg_NE (Adjust_Message
3670 ("postcondition does not check the outcome of calling "
3671 & "&?T?"), Err_Node, Subp_Id);
3672 end if;
3673 end if;
3674 end Check_Conjunct;
3676 ---------------------
3677 -- Check_Conjuncts --
3678 ---------------------
3680 procedure Check_Conjuncts (Expr : Node_Id) is
3681 begin
3682 if Nkind_In (Expr, N_Op_And, N_And_Then) then
3683 Check_Conjuncts (Left_Opnd (Expr));
3684 Check_Conjuncts (Right_Opnd (Expr));
3685 else
3686 Check_Conjunct (Expr);
3687 end if;
3688 end Check_Conjuncts;
3690 ----------------------
3691 -- Check_Expression --
3692 ----------------------
3694 procedure Check_Expression (Expr : Node_Id) is
3695 begin
3696 if not Is_Trivial_Boolean (Expr) then
3697 Check_Function_Result (Expr);
3698 Check_Conjuncts (Expr);
3699 end if;
3700 end Check_Expression;
3702 ------------------------
3703 -- Is_Function_Result --
3704 ------------------------
3706 function Is_Function_Result (N : Node_Id) return Traverse_Result is
3707 begin
3708 if Is_Attribute_Result (N) then
3709 Result_Seen := True;
3710 return Abandon;
3712 -- Continue the traversal
3714 else
3715 return OK;
3716 end if;
3717 end Is_Function_Result;
3719 ------------------------
3720 -- Is_Trivial_Boolean --
3721 ------------------------
3723 function Is_Trivial_Boolean (N : Node_Id) return Boolean is
3724 begin
3725 return
3726 Comes_From_Source (N)
3727 and then Is_Entity_Name (N)
3728 and then (Entity (N) = Standard_True
3729 or else
3730 Entity (N) = Standard_False);
3731 end Is_Trivial_Boolean;
3733 -------------------------
3734 -- Mentions_Post_State --
3735 -------------------------
3737 function Mentions_Post_State (N : Node_Id) return Boolean is
3738 Post_State_Seen : Boolean := False;
3740 function Is_Post_State (N : Node_Id) return Traverse_Result;
3741 -- Attempt to find a construct that denotes a post-state. If this
3742 -- is the case, set flag Post_State_Seen.
3744 -------------------
3745 -- Is_Post_State --
3746 -------------------
3748 function Is_Post_State (N : Node_Id) return Traverse_Result is
3749 Ent : Entity_Id;
3751 begin
3752 if Nkind_In (N, N_Explicit_Dereference, N_Function_Call) then
3753 Post_State_Seen := True;
3754 return Abandon;
3756 elsif Nkind_In (N, N_Expanded_Name, N_Identifier) then
3757 Ent := Entity (N);
3759 -- Treat an undecorated reference as OK
3761 if No (Ent)
3763 -- A reference to an assignable entity is considered a
3764 -- change in the post-state of a subprogram.
3766 or else Ekind_In (Ent, E_Generic_In_Out_Parameter,
3767 E_In_Out_Parameter,
3768 E_Out_Parameter,
3769 E_Variable)
3771 -- The reference may be modified through a dereference
3773 or else (Is_Access_Type (Etype (Ent))
3774 and then Nkind (Parent (N)) =
3775 N_Selected_Component)
3776 then
3777 Post_State_Seen := True;
3778 return Abandon;
3779 end if;
3781 elsif Nkind (N) = N_Attribute_Reference then
3782 if Attribute_Name (N) = Name_Old then
3783 return Skip;
3785 elsif Attribute_Name (N) = Name_Result then
3786 Post_State_Seen := True;
3787 return Abandon;
3788 end if;
3789 end if;
3791 return OK;
3792 end Is_Post_State;
3794 procedure Find_Post_State is new Traverse_Proc (Is_Post_State);
3796 -- Start of processing for Mentions_Post_State
3798 begin
3799 Find_Post_State (N);
3801 return Post_State_Seen;
3802 end Mentions_Post_State;
3804 -- Local variables
3806 Expr : constant Node_Id :=
3807 Get_Pragma_Arg
3808 (First (Pragma_Argument_Associations (Prag)));
3809 Nam : constant Name_Id := Pragma_Name (Prag);
3810 CCase : Node_Id;
3812 -- Start of processing for Check_Result_And_Post_State_In_Pragma
3814 begin
3815 -- Examine all consequences
3817 if Nam = Name_Contract_Cases then
3818 CCase := First (Component_Associations (Expr));
3819 while Present (CCase) loop
3820 Check_Expression (Expression (CCase));
3822 Next (CCase);
3823 end loop;
3825 -- Examine the expression of a postcondition
3827 else pragma Assert (Nam_In (Nam, Name_Postcondition,
3828 Name_Refined_Post));
3829 Check_Expression (Expr);
3830 end if;
3831 end Check_Result_And_Post_State_In_Pragma;
3833 --------------------------
3834 -- Has_In_Out_Parameter --
3835 --------------------------
3837 function Has_In_Out_Parameter (Subp_Id : Entity_Id) return Boolean is
3838 Formal : Entity_Id;
3840 begin
3841 -- Traverse the formals looking for an IN OUT parameter
3843 Formal := First_Formal (Subp_Id);
3844 while Present (Formal) loop
3845 if Ekind (Formal) = E_In_Out_Parameter then
3846 return True;
3847 end if;
3849 Next_Formal (Formal);
3850 end loop;
3852 return False;
3853 end Has_In_Out_Parameter;
3855 -- Local variables
3857 Items : constant Node_Id := Contract (Subp_Id);
3858 Subp_Decl : constant Node_Id := Unit_Declaration_Node (Subp_Id);
3859 Case_Prag : Node_Id := Empty;
3860 Post_Prag : Node_Id := Empty;
3861 Prag : Node_Id;
3862 Seen_In_Case : Boolean := False;
3863 Seen_In_Post : Boolean := False;
3864 Spec_Id : Entity_Id;
3866 -- Start of processing for Check_Result_And_Post_State
3868 begin
3869 -- The lack of attribute 'Result or a post-state is classified as a
3870 -- suspicious contract. Do not perform the check if the corresponding
3871 -- swich is not set.
3873 if not Warn_On_Suspicious_Contract then
3874 return;
3876 -- Nothing to do if there is no contract
3878 elsif No (Items) then
3879 return;
3880 end if;
3882 -- Retrieve the entity of the subprogram spec (if any)
3884 if Nkind (Subp_Decl) = N_Subprogram_Body
3885 and then Present (Corresponding_Spec (Subp_Decl))
3886 then
3887 Spec_Id := Corresponding_Spec (Subp_Decl);
3889 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
3890 and then Present (Corresponding_Spec_Of_Stub (Subp_Decl))
3891 then
3892 Spec_Id := Corresponding_Spec_Of_Stub (Subp_Decl);
3894 else
3895 Spec_Id := Subp_Id;
3896 end if;
3898 -- Examine all postconditions for attribute 'Result and a post-state
3900 Prag := Pre_Post_Conditions (Items);
3901 while Present (Prag) loop
3902 if Nam_In (Pragma_Name_Unmapped (Prag),
3903 Name_Postcondition, Name_Refined_Post)
3904 and then not Error_Posted (Prag)
3905 then
3906 Post_Prag := Prag;
3907 Check_Result_And_Post_State_In_Pragma (Prag, Seen_In_Post);
3908 end if;
3910 Prag := Next_Pragma (Prag);
3911 end loop;
3913 -- Examine the contract cases of the subprogram for attribute 'Result
3914 -- and a post-state.
3916 Prag := Contract_Test_Cases (Items);
3917 while Present (Prag) loop
3918 if Pragma_Name (Prag) = Name_Contract_Cases
3919 and then not Error_Posted (Prag)
3920 then
3921 Case_Prag := Prag;
3922 Check_Result_And_Post_State_In_Pragma (Prag, Seen_In_Case);
3923 end if;
3925 Prag := Next_Pragma (Prag);
3926 end loop;
3928 -- Do not emit any errors if the subprogram is not a function
3930 if not Ekind_In (Spec_Id, E_Function, E_Generic_Function) then
3931 null;
3933 -- Regardless of whether the function has postconditions or contract
3934 -- cases, or whether they mention attribute 'Result, an IN OUT formal
3935 -- parameter is always treated as a result.
3937 elsif Has_In_Out_Parameter (Spec_Id) then
3938 null;
3940 -- The function has both a postcondition and contract cases and they do
3941 -- not mention attribute 'Result.
3943 elsif Present (Case_Prag)
3944 and then not Seen_In_Case
3945 and then Present (Post_Prag)
3946 and then not Seen_In_Post
3947 then
3948 Error_Msg_N
3949 ("neither postcondition nor contract cases mention function "
3950 & "result?T?", Post_Prag);
3952 -- The function has contract cases only and they do not mention
3953 -- attribute 'Result.
3955 elsif Present (Case_Prag) and then not Seen_In_Case then
3956 Error_Msg_N ("contract cases do not mention result?T?", Case_Prag);
3958 -- The function has postconditions only and they do not mention
3959 -- attribute 'Result.
3961 elsif Present (Post_Prag) and then not Seen_In_Post then
3962 Error_Msg_N
3963 ("postcondition does not mention function result?T?", Post_Prag);
3964 end if;
3965 end Check_Result_And_Post_State;
3967 -----------------------------
3968 -- Check_State_Refinements --
3969 -----------------------------
3971 procedure Check_State_Refinements
3972 (Context : Node_Id;
3973 Is_Main_Unit : Boolean := False)
3975 procedure Check_Package (Pack : Node_Id);
3976 -- Verify that all abstract states of a [generic] package denoted by its
3977 -- declarative node Pack have proper refinement. Recursively verify the
3978 -- visible and private declarations of the [generic] package for other
3979 -- nested packages.
3981 procedure Check_Packages_In (Decls : List_Id);
3982 -- Seek out [generic] package declarations within declarative list Decls
3983 -- and verify the status of their abstract state refinement.
3985 function SPARK_Mode_Is_Off (N : Node_Id) return Boolean;
3986 -- Determine whether construct N is subject to pragma SPARK_Mode Off
3988 -------------------
3989 -- Check_Package --
3990 -------------------
3992 procedure Check_Package (Pack : Node_Id) is
3993 Body_Id : constant Entity_Id := Corresponding_Body (Pack);
3994 Spec : constant Node_Id := Specification (Pack);
3995 States : constant Elist_Id :=
3996 Abstract_States (Defining_Entity (Pack));
3998 State_Elmt : Elmt_Id;
3999 State_Id : Entity_Id;
4001 begin
4002 -- Do not verify proper state refinement when the package is subject
4003 -- to pragma SPARK_Mode Off because this disables the requirement for
4004 -- state refinement.
4006 if SPARK_Mode_Is_Off (Pack) then
4007 null;
4009 -- State refinement can only occur in a completing packge body. Do
4010 -- not verify proper state refinement when the body is subject to
4011 -- pragma SPARK_Mode Off because this disables the requirement for
4012 -- state refinement.
4014 elsif Present (Body_Id)
4015 and then SPARK_Mode_Is_Off (Unit_Declaration_Node (Body_Id))
4016 then
4017 null;
4019 -- Do not verify proper state refinement when the package is an
4020 -- instance as this check was already performed in the generic.
4022 elsif Present (Generic_Parent (Spec)) then
4023 null;
4025 -- Otherwise examine the contents of the package
4027 else
4028 if Present (States) then
4029 State_Elmt := First_Elmt (States);
4030 while Present (State_Elmt) loop
4031 State_Id := Node (State_Elmt);
4033 -- Emit an error when a non-null state lacks any form of
4034 -- refinement.
4036 if not Is_Null_State (State_Id)
4037 and then not Has_Null_Refinement (State_Id)
4038 and then not Has_Non_Null_Refinement (State_Id)
4039 then
4040 Error_Msg_N ("state & requires refinement", State_Id);
4041 end if;
4043 Next_Elmt (State_Elmt);
4044 end loop;
4045 end if;
4047 Check_Packages_In (Visible_Declarations (Spec));
4048 Check_Packages_In (Private_Declarations (Spec));
4049 end if;
4050 end Check_Package;
4052 -----------------------
4053 -- Check_Packages_In --
4054 -----------------------
4056 procedure Check_Packages_In (Decls : List_Id) is
4057 Decl : Node_Id;
4059 begin
4060 if Present (Decls) then
4061 Decl := First (Decls);
4062 while Present (Decl) loop
4063 if Nkind_In (Decl, N_Generic_Package_Declaration,
4064 N_Package_Declaration)
4065 then
4066 Check_Package (Decl);
4067 end if;
4069 Next (Decl);
4070 end loop;
4071 end if;
4072 end Check_Packages_In;
4074 -----------------------
4075 -- SPARK_Mode_Is_Off --
4076 -----------------------
4078 function SPARK_Mode_Is_Off (N : Node_Id) return Boolean is
4079 Id : constant Entity_Id := Defining_Entity (N);
4080 Prag : constant Node_Id := SPARK_Pragma (Id);
4082 begin
4083 -- Default the mode to "off" when the context is an instance and all
4084 -- SPARK_Mode pragmas found within are to be ignored.
4086 if Ignore_SPARK_Mode_Pragmas (Id) then
4087 return True;
4089 else
4090 return
4091 Present (Prag)
4092 and then Get_SPARK_Mode_From_Annotation (Prag) = Off;
4093 end if;
4094 end SPARK_Mode_Is_Off;
4096 -- Start of processing for Check_State_Refinements
4098 begin
4099 -- A block may declare a nested package
4101 if Nkind (Context) = N_Block_Statement then
4102 Check_Packages_In (Declarations (Context));
4104 -- An entry, protected, subprogram, or task body may declare a nested
4105 -- package.
4107 elsif Nkind_In (Context, N_Entry_Body,
4108 N_Protected_Body,
4109 N_Subprogram_Body,
4110 N_Task_Body)
4111 then
4112 -- Do not verify proper state refinement when the body is subject to
4113 -- pragma SPARK_Mode Off because this disables the requirement for
4114 -- state refinement.
4116 if not SPARK_Mode_Is_Off (Context) then
4117 Check_Packages_In (Declarations (Context));
4118 end if;
4120 -- A package body may declare a nested package
4122 elsif Nkind (Context) = N_Package_Body then
4123 Check_Package (Unit_Declaration_Node (Corresponding_Spec (Context)));
4125 -- Do not verify proper state refinement when the body is subject to
4126 -- pragma SPARK_Mode Off because this disables the requirement for
4127 -- state refinement.
4129 if not SPARK_Mode_Is_Off (Context) then
4130 Check_Packages_In (Declarations (Context));
4131 end if;
4133 -- A library level [generic] package may declare a nested package
4135 elsif Nkind_In (Context, N_Generic_Package_Declaration,
4136 N_Package_Declaration)
4137 and then Is_Main_Unit
4138 then
4139 Check_Package (Context);
4140 end if;
4141 end Check_State_Refinements;
4143 ------------------------------
4144 -- Check_Unprotected_Access --
4145 ------------------------------
4147 procedure Check_Unprotected_Access
4148 (Context : Node_Id;
4149 Expr : Node_Id)
4151 Cont_Encl_Typ : Entity_Id;
4152 Pref_Encl_Typ : Entity_Id;
4154 function Enclosing_Protected_Type (Obj : Node_Id) return Entity_Id;
4155 -- Check whether Obj is a private component of a protected object.
4156 -- Return the protected type where the component resides, Empty
4157 -- otherwise.
4159 function Is_Public_Operation return Boolean;
4160 -- Verify that the enclosing operation is callable from outside the
4161 -- protected object, to minimize false positives.
4163 ------------------------------
4164 -- Enclosing_Protected_Type --
4165 ------------------------------
4167 function Enclosing_Protected_Type (Obj : Node_Id) return Entity_Id is
4168 begin
4169 if Is_Entity_Name (Obj) then
4170 declare
4171 Ent : Entity_Id := Entity (Obj);
4173 begin
4174 -- The object can be a renaming of a private component, use
4175 -- the original record component.
4177 if Is_Prival (Ent) then
4178 Ent := Prival_Link (Ent);
4179 end if;
4181 if Is_Protected_Type (Scope (Ent)) then
4182 return Scope (Ent);
4183 end if;
4184 end;
4185 end if;
4187 -- For indexed and selected components, recursively check the prefix
4189 if Nkind_In (Obj, N_Indexed_Component, N_Selected_Component) then
4190 return Enclosing_Protected_Type (Prefix (Obj));
4192 -- The object does not denote a protected component
4194 else
4195 return Empty;
4196 end if;
4197 end Enclosing_Protected_Type;
4199 -------------------------
4200 -- Is_Public_Operation --
4201 -------------------------
4203 function Is_Public_Operation return Boolean is
4204 S : Entity_Id;
4205 E : Entity_Id;
4207 begin
4208 S := Current_Scope;
4209 while Present (S) and then S /= Pref_Encl_Typ loop
4210 if Scope (S) = Pref_Encl_Typ then
4211 E := First_Entity (Pref_Encl_Typ);
4212 while Present (E)
4213 and then E /= First_Private_Entity (Pref_Encl_Typ)
4214 loop
4215 if E = S then
4216 return True;
4217 end if;
4219 Next_Entity (E);
4220 end loop;
4221 end if;
4223 S := Scope (S);
4224 end loop;
4226 return False;
4227 end Is_Public_Operation;
4229 -- Start of processing for Check_Unprotected_Access
4231 begin
4232 if Nkind (Expr) = N_Attribute_Reference
4233 and then Attribute_Name (Expr) = Name_Unchecked_Access
4234 then
4235 Cont_Encl_Typ := Enclosing_Protected_Type (Context);
4236 Pref_Encl_Typ := Enclosing_Protected_Type (Prefix (Expr));
4238 -- Check whether we are trying to export a protected component to a
4239 -- context with an equal or lower access level.
4241 if Present (Pref_Encl_Typ)
4242 and then No (Cont_Encl_Typ)
4243 and then Is_Public_Operation
4244 and then Scope_Depth (Pref_Encl_Typ) >=
4245 Object_Access_Level (Context)
4246 then
4247 Error_Msg_N
4248 ("??possible unprotected access to protected data", Expr);
4249 end if;
4250 end if;
4251 end Check_Unprotected_Access;
4253 ------------------------------
4254 -- Check_Unused_Body_States --
4255 ------------------------------
4257 procedure Check_Unused_Body_States (Body_Id : Entity_Id) is
4258 procedure Process_Refinement_Clause
4259 (Clause : Node_Id;
4260 States : Elist_Id);
4261 -- Inspect all constituents of refinement clause Clause and remove any
4262 -- matches from body state list States.
4264 procedure Report_Unused_Body_States (States : Elist_Id);
4265 -- Emit errors for each abstract state or object found in list States
4267 -------------------------------
4268 -- Process_Refinement_Clause --
4269 -------------------------------
4271 procedure Process_Refinement_Clause
4272 (Clause : Node_Id;
4273 States : Elist_Id)
4275 procedure Process_Constituent (Constit : Node_Id);
4276 -- Remove constituent Constit from body state list States
4278 -------------------------
4279 -- Process_Constituent --
4280 -------------------------
4282 procedure Process_Constituent (Constit : Node_Id) is
4283 Constit_Id : Entity_Id;
4285 begin
4286 -- Guard against illegal constituents. Only abstract states and
4287 -- objects can appear on the right hand side of a refinement.
4289 if Is_Entity_Name (Constit) then
4290 Constit_Id := Entity_Of (Constit);
4292 if Present (Constit_Id)
4293 and then Ekind_In (Constit_Id, E_Abstract_State,
4294 E_Constant,
4295 E_Variable)
4296 then
4297 Remove (States, Constit_Id);
4298 end if;
4299 end if;
4300 end Process_Constituent;
4302 -- Local variables
4304 Constit : Node_Id;
4306 -- Start of processing for Process_Refinement_Clause
4308 begin
4309 if Nkind (Clause) = N_Component_Association then
4310 Constit := Expression (Clause);
4312 -- Multiple constituents appear as an aggregate
4314 if Nkind (Constit) = N_Aggregate then
4315 Constit := First (Expressions (Constit));
4316 while Present (Constit) loop
4317 Process_Constituent (Constit);
4318 Next (Constit);
4319 end loop;
4321 -- Various forms of a single constituent
4323 else
4324 Process_Constituent (Constit);
4325 end if;
4326 end if;
4327 end Process_Refinement_Clause;
4329 -------------------------------
4330 -- Report_Unused_Body_States --
4331 -------------------------------
4333 procedure Report_Unused_Body_States (States : Elist_Id) is
4334 Posted : Boolean := False;
4335 State_Elmt : Elmt_Id;
4336 State_Id : Entity_Id;
4338 begin
4339 if Present (States) then
4340 State_Elmt := First_Elmt (States);
4341 while Present (State_Elmt) loop
4342 State_Id := Node (State_Elmt);
4344 -- Constants are part of the hidden state of a package, but the
4345 -- compiler cannot determine whether they have variable input
4346 -- (SPARK RM 7.1.1(2)) and cannot classify them properly as a
4347 -- hidden state. Do not emit an error when a constant does not
4348 -- participate in a state refinement, even though it acts as a
4349 -- hidden state.
4351 if Ekind (State_Id) = E_Constant then
4352 null;
4354 -- Generate an error message of the form:
4356 -- body of package ... has unused hidden states
4357 -- abstract state ... defined at ...
4358 -- variable ... defined at ...
4360 else
4361 if not Posted then
4362 Posted := True;
4363 SPARK_Msg_N
4364 ("body of package & has unused hidden states", Body_Id);
4365 end if;
4367 Error_Msg_Sloc := Sloc (State_Id);
4369 if Ekind (State_Id) = E_Abstract_State then
4370 SPARK_Msg_NE
4371 ("\abstract state & defined #", Body_Id, State_Id);
4373 else
4374 SPARK_Msg_NE ("\variable & defined #", Body_Id, State_Id);
4375 end if;
4376 end if;
4378 Next_Elmt (State_Elmt);
4379 end loop;
4380 end if;
4381 end Report_Unused_Body_States;
4383 -- Local variables
4385 Prag : constant Node_Id := Get_Pragma (Body_Id, Pragma_Refined_State);
4386 Spec_Id : constant Entity_Id := Spec_Entity (Body_Id);
4387 Clause : Node_Id;
4388 States : Elist_Id;
4390 -- Start of processing for Check_Unused_Body_States
4392 begin
4393 -- Inspect the clauses of pragma Refined_State and determine whether all
4394 -- visible states declared within the package body participate in the
4395 -- refinement.
4397 if Present (Prag) then
4398 Clause := Expression (Get_Argument (Prag, Spec_Id));
4399 States := Collect_Body_States (Body_Id);
4401 -- Multiple non-null state refinements appear as an aggregate
4403 if Nkind (Clause) = N_Aggregate then
4404 Clause := First (Component_Associations (Clause));
4405 while Present (Clause) loop
4406 Process_Refinement_Clause (Clause, States);
4407 Next (Clause);
4408 end loop;
4410 -- Various forms of a single state refinement
4412 else
4413 Process_Refinement_Clause (Clause, States);
4414 end if;
4416 -- Ensure that all abstract states and objects declared in the
4417 -- package body state space are utilized as constituents.
4419 Report_Unused_Body_States (States);
4420 end if;
4421 end Check_Unused_Body_States;
4423 -----------------
4424 -- Choice_List --
4425 -----------------
4427 function Choice_List (N : Node_Id) return List_Id is
4428 begin
4429 if Nkind (N) = N_Iterated_Component_Association then
4430 return Discrete_Choices (N);
4431 else
4432 return Choices (N);
4433 end if;
4434 end Choice_List;
4436 -------------------------
4437 -- Collect_Body_States --
4438 -------------------------
4440 function Collect_Body_States (Body_Id : Entity_Id) return Elist_Id is
4441 function Is_Visible_Object (Obj_Id : Entity_Id) return Boolean;
4442 -- Determine whether object Obj_Id is a suitable visible state of a
4443 -- package body.
4445 procedure Collect_Visible_States
4446 (Pack_Id : Entity_Id;
4447 States : in out Elist_Id);
4448 -- Gather the entities of all abstract states and objects declared in
4449 -- the visible state space of package Pack_Id.
4451 ----------------------------
4452 -- Collect_Visible_States --
4453 ----------------------------
4455 procedure Collect_Visible_States
4456 (Pack_Id : Entity_Id;
4457 States : in out Elist_Id)
4459 Item_Id : Entity_Id;
4461 begin
4462 -- Traverse the entity chain of the package and inspect all visible
4463 -- items.
4465 Item_Id := First_Entity (Pack_Id);
4466 while Present (Item_Id) and then not In_Private_Part (Item_Id) loop
4468 -- Do not consider internally generated items as those cannot be
4469 -- named and participate in refinement.
4471 if not Comes_From_Source (Item_Id) then
4472 null;
4474 elsif Ekind (Item_Id) = E_Abstract_State then
4475 Append_New_Elmt (Item_Id, States);
4477 elsif Ekind_In (Item_Id, E_Constant, E_Variable)
4478 and then Is_Visible_Object (Item_Id)
4479 then
4480 Append_New_Elmt (Item_Id, States);
4482 -- Recursively gather the visible states of a nested package
4484 elsif Ekind (Item_Id) = E_Package then
4485 Collect_Visible_States (Item_Id, States);
4486 end if;
4488 Next_Entity (Item_Id);
4489 end loop;
4490 end Collect_Visible_States;
4492 -----------------------
4493 -- Is_Visible_Object --
4494 -----------------------
4496 function Is_Visible_Object (Obj_Id : Entity_Id) return Boolean is
4497 begin
4498 -- Objects that map generic formals to their actuals are not visible
4499 -- from outside the generic instantiation.
4501 if Present (Corresponding_Generic_Association
4502 (Declaration_Node (Obj_Id)))
4503 then
4504 return False;
4506 -- Constituents of a single protected/task type act as components of
4507 -- the type and are not visible from outside the type.
4509 elsif Ekind (Obj_Id) = E_Variable
4510 and then Present (Encapsulating_State (Obj_Id))
4511 and then Is_Single_Concurrent_Object (Encapsulating_State (Obj_Id))
4512 then
4513 return False;
4515 else
4516 return True;
4517 end if;
4518 end Is_Visible_Object;
4520 -- Local variables
4522 Body_Decl : constant Node_Id := Unit_Declaration_Node (Body_Id);
4523 Decl : Node_Id;
4524 Item_Id : Entity_Id;
4525 States : Elist_Id := No_Elist;
4527 -- Start of processing for Collect_Body_States
4529 begin
4530 -- Inspect the declarations of the body looking for source objects,
4531 -- packages and package instantiations. Note that even though this
4532 -- processing is very similar to Collect_Visible_States, a package
4533 -- body does not have a First/Next_Entity list.
4535 Decl := First (Declarations (Body_Decl));
4536 while Present (Decl) loop
4538 -- Capture source objects as internally generated temporaries cannot
4539 -- be named and participate in refinement.
4541 if Nkind (Decl) = N_Object_Declaration then
4542 Item_Id := Defining_Entity (Decl);
4544 if Comes_From_Source (Item_Id)
4545 and then Is_Visible_Object (Item_Id)
4546 then
4547 Append_New_Elmt (Item_Id, States);
4548 end if;
4550 -- Capture the visible abstract states and objects of a source
4551 -- package [instantiation].
4553 elsif Nkind (Decl) = N_Package_Declaration then
4554 Item_Id := Defining_Entity (Decl);
4556 if Comes_From_Source (Item_Id) then
4557 Collect_Visible_States (Item_Id, States);
4558 end if;
4559 end if;
4561 Next (Decl);
4562 end loop;
4564 return States;
4565 end Collect_Body_States;
4567 ------------------------
4568 -- Collect_Interfaces --
4569 ------------------------
4571 procedure Collect_Interfaces
4572 (T : Entity_Id;
4573 Ifaces_List : out Elist_Id;
4574 Exclude_Parents : Boolean := False;
4575 Use_Full_View : Boolean := True)
4577 procedure Collect (Typ : Entity_Id);
4578 -- Subsidiary subprogram used to traverse the whole list
4579 -- of directly and indirectly implemented interfaces
4581 -------------
4582 -- Collect --
4583 -------------
4585 procedure Collect (Typ : Entity_Id) is
4586 Ancestor : Entity_Id;
4587 Full_T : Entity_Id;
4588 Id : Node_Id;
4589 Iface : Entity_Id;
4591 begin
4592 Full_T := Typ;
4594 -- Handle private types and subtypes
4596 if Use_Full_View
4597 and then Is_Private_Type (Typ)
4598 and then Present (Full_View (Typ))
4599 then
4600 Full_T := Full_View (Typ);
4602 if Ekind (Full_T) = E_Record_Subtype then
4603 Full_T := Etype (Typ);
4605 if Present (Full_View (Full_T)) then
4606 Full_T := Full_View (Full_T);
4607 end if;
4608 end if;
4609 end if;
4611 -- Include the ancestor if we are generating the whole list of
4612 -- abstract interfaces.
4614 if Etype (Full_T) /= Typ
4616 -- Protect the frontend against wrong sources. For example:
4618 -- package P is
4619 -- type A is tagged null record;
4620 -- type B is new A with private;
4621 -- type C is new A with private;
4622 -- private
4623 -- type B is new C with null record;
4624 -- type C is new B with null record;
4625 -- end P;
4627 and then Etype (Full_T) /= T
4628 then
4629 Ancestor := Etype (Full_T);
4630 Collect (Ancestor);
4632 if Is_Interface (Ancestor) and then not Exclude_Parents then
4633 Append_Unique_Elmt (Ancestor, Ifaces_List);
4634 end if;
4635 end if;
4637 -- Traverse the graph of ancestor interfaces
4639 if Is_Non_Empty_List (Abstract_Interface_List (Full_T)) then
4640 Id := First (Abstract_Interface_List (Full_T));
4641 while Present (Id) loop
4642 Iface := Etype (Id);
4644 -- Protect against wrong uses. For example:
4645 -- type I is interface;
4646 -- type O is tagged null record;
4647 -- type Wrong is new I and O with null record; -- ERROR
4649 if Is_Interface (Iface) then
4650 if Exclude_Parents
4651 and then Etype (T) /= T
4652 and then Interface_Present_In_Ancestor (Etype (T), Iface)
4653 then
4654 null;
4655 else
4656 Collect (Iface);
4657 Append_Unique_Elmt (Iface, Ifaces_List);
4658 end if;
4659 end if;
4661 Next (Id);
4662 end loop;
4663 end if;
4664 end Collect;
4666 -- Start of processing for Collect_Interfaces
4668 begin
4669 pragma Assert (Is_Tagged_Type (T) or else Is_Concurrent_Type (T));
4670 Ifaces_List := New_Elmt_List;
4671 Collect (T);
4672 end Collect_Interfaces;
4674 ----------------------------------
4675 -- Collect_Interface_Components --
4676 ----------------------------------
4678 procedure Collect_Interface_Components
4679 (Tagged_Type : Entity_Id;
4680 Components_List : out Elist_Id)
4682 procedure Collect (Typ : Entity_Id);
4683 -- Subsidiary subprogram used to climb to the parents
4685 -------------
4686 -- Collect --
4687 -------------
4689 procedure Collect (Typ : Entity_Id) is
4690 Tag_Comp : Entity_Id;
4691 Parent_Typ : Entity_Id;
4693 begin
4694 -- Handle private types
4696 if Present (Full_View (Etype (Typ))) then
4697 Parent_Typ := Full_View (Etype (Typ));
4698 else
4699 Parent_Typ := Etype (Typ);
4700 end if;
4702 if Parent_Typ /= Typ
4704 -- Protect the frontend against wrong sources. For example:
4706 -- package P is
4707 -- type A is tagged null record;
4708 -- type B is new A with private;
4709 -- type C is new A with private;
4710 -- private
4711 -- type B is new C with null record;
4712 -- type C is new B with null record;
4713 -- end P;
4715 and then Parent_Typ /= Tagged_Type
4716 then
4717 Collect (Parent_Typ);
4718 end if;
4720 -- Collect the components containing tags of secondary dispatch
4721 -- tables.
4723 Tag_Comp := Next_Tag_Component (First_Tag_Component (Typ));
4724 while Present (Tag_Comp) loop
4725 pragma Assert (Present (Related_Type (Tag_Comp)));
4726 Append_Elmt (Tag_Comp, Components_List);
4728 Tag_Comp := Next_Tag_Component (Tag_Comp);
4729 end loop;
4730 end Collect;
4732 -- Start of processing for Collect_Interface_Components
4734 begin
4735 pragma Assert (Ekind (Tagged_Type) = E_Record_Type
4736 and then Is_Tagged_Type (Tagged_Type));
4738 Components_List := New_Elmt_List;
4739 Collect (Tagged_Type);
4740 end Collect_Interface_Components;
4742 -----------------------------
4743 -- Collect_Interfaces_Info --
4744 -----------------------------
4746 procedure Collect_Interfaces_Info
4747 (T : Entity_Id;
4748 Ifaces_List : out Elist_Id;
4749 Components_List : out Elist_Id;
4750 Tags_List : out Elist_Id)
4752 Comps_List : Elist_Id;
4753 Comp_Elmt : Elmt_Id;
4754 Comp_Iface : Entity_Id;
4755 Iface_Elmt : Elmt_Id;
4756 Iface : Entity_Id;
4758 function Search_Tag (Iface : Entity_Id) return Entity_Id;
4759 -- Search for the secondary tag associated with the interface type
4760 -- Iface that is implemented by T.
4762 ----------------
4763 -- Search_Tag --
4764 ----------------
4766 function Search_Tag (Iface : Entity_Id) return Entity_Id is
4767 ADT : Elmt_Id;
4768 begin
4769 if not Is_CPP_Class (T) then
4770 ADT := Next_Elmt (Next_Elmt (First_Elmt (Access_Disp_Table (T))));
4771 else
4772 ADT := Next_Elmt (First_Elmt (Access_Disp_Table (T)));
4773 end if;
4775 while Present (ADT)
4776 and then Is_Tag (Node (ADT))
4777 and then Related_Type (Node (ADT)) /= Iface
4778 loop
4779 -- Skip secondary dispatch table referencing thunks to user
4780 -- defined primitives covered by this interface.
4782 pragma Assert (Has_Suffix (Node (ADT), 'P'));
4783 Next_Elmt (ADT);
4785 -- Skip secondary dispatch tables of Ada types
4787 if not Is_CPP_Class (T) then
4789 -- Skip secondary dispatch table referencing thunks to
4790 -- predefined primitives.
4792 pragma Assert (Has_Suffix (Node (ADT), 'Y'));
4793 Next_Elmt (ADT);
4795 -- Skip secondary dispatch table referencing user-defined
4796 -- primitives covered by this interface.
4798 pragma Assert (Has_Suffix (Node (ADT), 'D'));
4799 Next_Elmt (ADT);
4801 -- Skip secondary dispatch table referencing predefined
4802 -- primitives.
4804 pragma Assert (Has_Suffix (Node (ADT), 'Z'));
4805 Next_Elmt (ADT);
4806 end if;
4807 end loop;
4809 pragma Assert (Is_Tag (Node (ADT)));
4810 return Node (ADT);
4811 end Search_Tag;
4813 -- Start of processing for Collect_Interfaces_Info
4815 begin
4816 Collect_Interfaces (T, Ifaces_List);
4817 Collect_Interface_Components (T, Comps_List);
4819 -- Search for the record component and tag associated with each
4820 -- interface type of T.
4822 Components_List := New_Elmt_List;
4823 Tags_List := New_Elmt_List;
4825 Iface_Elmt := First_Elmt (Ifaces_List);
4826 while Present (Iface_Elmt) loop
4827 Iface := Node (Iface_Elmt);
4829 -- Associate the primary tag component and the primary dispatch table
4830 -- with all the interfaces that are parents of T
4832 if Is_Ancestor (Iface, T, Use_Full_View => True) then
4833 Append_Elmt (First_Tag_Component (T), Components_List);
4834 Append_Elmt (Node (First_Elmt (Access_Disp_Table (T))), Tags_List);
4836 -- Otherwise search for the tag component and secondary dispatch
4837 -- table of Iface
4839 else
4840 Comp_Elmt := First_Elmt (Comps_List);
4841 while Present (Comp_Elmt) loop
4842 Comp_Iface := Related_Type (Node (Comp_Elmt));
4844 if Comp_Iface = Iface
4845 or else Is_Ancestor (Iface, Comp_Iface, Use_Full_View => True)
4846 then
4847 Append_Elmt (Node (Comp_Elmt), Components_List);
4848 Append_Elmt (Search_Tag (Comp_Iface), Tags_List);
4849 exit;
4850 end if;
4852 Next_Elmt (Comp_Elmt);
4853 end loop;
4854 pragma Assert (Present (Comp_Elmt));
4855 end if;
4857 Next_Elmt (Iface_Elmt);
4858 end loop;
4859 end Collect_Interfaces_Info;
4861 ---------------------
4862 -- Collect_Parents --
4863 ---------------------
4865 procedure Collect_Parents
4866 (T : Entity_Id;
4867 List : out Elist_Id;
4868 Use_Full_View : Boolean := True)
4870 Current_Typ : Entity_Id := T;
4871 Parent_Typ : Entity_Id;
4873 begin
4874 List := New_Elmt_List;
4876 -- No action if the if the type has no parents
4878 if T = Etype (T) then
4879 return;
4880 end if;
4882 loop
4883 Parent_Typ := Etype (Current_Typ);
4885 if Is_Private_Type (Parent_Typ)
4886 and then Present (Full_View (Parent_Typ))
4887 and then Use_Full_View
4888 then
4889 Parent_Typ := Full_View (Base_Type (Parent_Typ));
4890 end if;
4892 Append_Elmt (Parent_Typ, List);
4894 exit when Parent_Typ = Current_Typ;
4895 Current_Typ := Parent_Typ;
4896 end loop;
4897 end Collect_Parents;
4899 ----------------------------------
4900 -- Collect_Primitive_Operations --
4901 ----------------------------------
4903 function Collect_Primitive_Operations (T : Entity_Id) return Elist_Id is
4904 B_Type : constant Entity_Id := Base_Type (T);
4905 B_Decl : constant Node_Id := Original_Node (Parent (B_Type));
4906 B_Scope : Entity_Id := Scope (B_Type);
4907 Op_List : Elist_Id;
4908 Formal : Entity_Id;
4909 Is_Prim : Boolean;
4910 Is_Type_In_Pkg : Boolean;
4911 Formal_Derived : Boolean := False;
4912 Id : Entity_Id;
4914 function Match (E : Entity_Id) return Boolean;
4915 -- True if E's base type is B_Type, or E is of an anonymous access type
4916 -- and the base type of its designated type is B_Type.
4918 -----------
4919 -- Match --
4920 -----------
4922 function Match (E : Entity_Id) return Boolean is
4923 Etyp : Entity_Id := Etype (E);
4925 begin
4926 if Ekind (Etyp) = E_Anonymous_Access_Type then
4927 Etyp := Designated_Type (Etyp);
4928 end if;
4930 -- In Ada 2012 a primitive operation may have a formal of an
4931 -- incomplete view of the parent type.
4933 return Base_Type (Etyp) = B_Type
4934 or else
4935 (Ada_Version >= Ada_2012
4936 and then Ekind (Etyp) = E_Incomplete_Type
4937 and then Full_View (Etyp) = B_Type);
4938 end Match;
4940 -- Start of processing for Collect_Primitive_Operations
4942 begin
4943 -- For tagged types, the primitive operations are collected as they
4944 -- are declared, and held in an explicit list which is simply returned.
4946 if Is_Tagged_Type (B_Type) then
4947 return Primitive_Operations (B_Type);
4949 -- An untagged generic type that is a derived type inherits the
4950 -- primitive operations of its parent type. Other formal types only
4951 -- have predefined operators, which are not explicitly represented.
4953 elsif Is_Generic_Type (B_Type) then
4954 if Nkind (B_Decl) = N_Formal_Type_Declaration
4955 and then Nkind (Formal_Type_Definition (B_Decl)) =
4956 N_Formal_Derived_Type_Definition
4957 then
4958 Formal_Derived := True;
4959 else
4960 return New_Elmt_List;
4961 end if;
4962 end if;
4964 Op_List := New_Elmt_List;
4966 if B_Scope = Standard_Standard then
4967 if B_Type = Standard_String then
4968 Append_Elmt (Standard_Op_Concat, Op_List);
4970 elsif B_Type = Standard_Wide_String then
4971 Append_Elmt (Standard_Op_Concatw, Op_List);
4973 else
4974 null;
4975 end if;
4977 -- Locate the primitive subprograms of the type
4979 else
4980 -- The primitive operations appear after the base type, except
4981 -- if the derivation happens within the private part of B_Scope
4982 -- and the type is a private type, in which case both the type
4983 -- and some primitive operations may appear before the base
4984 -- type, and the list of candidates starts after the type.
4986 if In_Open_Scopes (B_Scope)
4987 and then Scope (T) = B_Scope
4988 and then In_Private_Part (B_Scope)
4989 then
4990 Id := Next_Entity (T);
4992 -- In Ada 2012, If the type has an incomplete partial view, there
4993 -- may be primitive operations declared before the full view, so
4994 -- we need to start scanning from the incomplete view, which is
4995 -- earlier on the entity chain.
4997 elsif Nkind (Parent (B_Type)) = N_Full_Type_Declaration
4998 and then Present (Incomplete_View (Parent (B_Type)))
4999 then
5000 Id := Defining_Entity (Incomplete_View (Parent (B_Type)));
5002 -- If T is a derived from a type with an incomplete view declared
5003 -- elsewhere, that incomplete view is irrelevant, we want the
5004 -- operations in the scope of T.
5006 if Scope (Id) /= Scope (B_Type) then
5007 Id := Next_Entity (B_Type);
5008 end if;
5010 else
5011 Id := Next_Entity (B_Type);
5012 end if;
5014 -- Set flag if this is a type in a package spec
5016 Is_Type_In_Pkg :=
5017 Is_Package_Or_Generic_Package (B_Scope)
5018 and then
5019 Nkind (Parent (Declaration_Node (First_Subtype (T)))) /=
5020 N_Package_Body;
5022 while Present (Id) loop
5024 -- Test whether the result type or any of the parameter types of
5025 -- each subprogram following the type match that type when the
5026 -- type is declared in a package spec, is a derived type, or the
5027 -- subprogram is marked as primitive. (The Is_Primitive test is
5028 -- needed to find primitives of nonderived types in declarative
5029 -- parts that happen to override the predefined "=" operator.)
5031 -- Note that generic formal subprograms are not considered to be
5032 -- primitive operations and thus are never inherited.
5034 if Is_Overloadable (Id)
5035 and then (Is_Type_In_Pkg
5036 or else Is_Derived_Type (B_Type)
5037 or else Is_Primitive (Id))
5038 and then Nkind (Parent (Parent (Id)))
5039 not in N_Formal_Subprogram_Declaration
5040 then
5041 Is_Prim := False;
5043 if Match (Id) then
5044 Is_Prim := True;
5046 else
5047 Formal := First_Formal (Id);
5048 while Present (Formal) loop
5049 if Match (Formal) then
5050 Is_Prim := True;
5051 exit;
5052 end if;
5054 Next_Formal (Formal);
5055 end loop;
5056 end if;
5058 -- For a formal derived type, the only primitives are the ones
5059 -- inherited from the parent type. Operations appearing in the
5060 -- package declaration are not primitive for it.
5062 if Is_Prim
5063 and then (not Formal_Derived or else Present (Alias (Id)))
5064 then
5065 -- In the special case of an equality operator aliased to
5066 -- an overriding dispatching equality belonging to the same
5067 -- type, we don't include it in the list of primitives.
5068 -- This avoids inheriting multiple equality operators when
5069 -- deriving from untagged private types whose full type is
5070 -- tagged, which can otherwise cause ambiguities. Note that
5071 -- this should only happen for this kind of untagged parent
5072 -- type, since normally dispatching operations are inherited
5073 -- using the type's Primitive_Operations list.
5075 if Chars (Id) = Name_Op_Eq
5076 and then Is_Dispatching_Operation (Id)
5077 and then Present (Alias (Id))
5078 and then Present (Overridden_Operation (Alias (Id)))
5079 and then Base_Type (Etype (First_Entity (Id))) =
5080 Base_Type (Etype (First_Entity (Alias (Id))))
5081 then
5082 null;
5084 -- Include the subprogram in the list of primitives
5086 else
5087 Append_Elmt (Id, Op_List);
5088 end if;
5089 end if;
5090 end if;
5092 Next_Entity (Id);
5094 -- For a type declared in System, some of its operations may
5095 -- appear in the target-specific extension to System.
5097 if No (Id)
5098 and then B_Scope = RTU_Entity (System)
5099 and then Present_System_Aux
5100 then
5101 B_Scope := System_Aux_Id;
5102 Id := First_Entity (System_Aux_Id);
5103 end if;
5104 end loop;
5105 end if;
5107 return Op_List;
5108 end Collect_Primitive_Operations;
5110 -----------------------------------
5111 -- Compile_Time_Constraint_Error --
5112 -----------------------------------
5114 function Compile_Time_Constraint_Error
5115 (N : Node_Id;
5116 Msg : String;
5117 Ent : Entity_Id := Empty;
5118 Loc : Source_Ptr := No_Location;
5119 Warn : Boolean := False) return Node_Id
5121 Msgc : String (1 .. Msg'Length + 3);
5122 -- Copy of message, with room for possible ?? or << and ! at end
5124 Msgl : Natural;
5125 Wmsg : Boolean;
5126 Eloc : Source_Ptr;
5128 -- Start of processing for Compile_Time_Constraint_Error
5130 begin
5131 -- If this is a warning, convert it into an error if we are in code
5132 -- subject to SPARK_Mode being set On, unless Warn is True to force a
5133 -- warning. The rationale is that a compile-time constraint error should
5134 -- lead to an error instead of a warning when SPARK_Mode is On, but in
5135 -- a few cases we prefer to issue a warning and generate both a suitable
5136 -- run-time error in GNAT and a suitable check message in GNATprove.
5137 -- Those cases are those that likely correspond to deactivated SPARK
5138 -- code, so that this kind of code can be compiled and analyzed instead
5139 -- of being rejected.
5141 Error_Msg_Warn := Warn or SPARK_Mode /= On;
5143 -- A static constraint error in an instance body is not a fatal error.
5144 -- we choose to inhibit the message altogether, because there is no
5145 -- obvious node (for now) on which to post it. On the other hand the
5146 -- offending node must be replaced with a constraint_error in any case.
5148 -- No messages are generated if we already posted an error on this node
5150 if not Error_Posted (N) then
5151 if Loc /= No_Location then
5152 Eloc := Loc;
5153 else
5154 Eloc := Sloc (N);
5155 end if;
5157 -- Copy message to Msgc, converting any ? in the message into <
5158 -- instead, so that we have an error in GNATprove mode.
5160 Msgl := Msg'Length;
5162 for J in 1 .. Msgl loop
5163 if Msg (J) = '?' and then (J = 1 or else Msg (J - 1) /= ''') then
5164 Msgc (J) := '<';
5165 else
5166 Msgc (J) := Msg (J);
5167 end if;
5168 end loop;
5170 -- Message is a warning, even in Ada 95 case
5172 if Msg (Msg'Last) = '?' or else Msg (Msg'Last) = '<' then
5173 Wmsg := True;
5175 -- In Ada 83, all messages are warnings. In the private part and the
5176 -- body of an instance, constraint_checks are only warnings. We also
5177 -- make this a warning if the Warn parameter is set.
5179 elsif Warn
5180 or else (Ada_Version = Ada_83 and then Comes_From_Source (N))
5181 or else In_Instance_Not_Visible
5182 then
5183 Msgl := Msgl + 1;
5184 Msgc (Msgl) := '<';
5185 Msgl := Msgl + 1;
5186 Msgc (Msgl) := '<';
5187 Wmsg := True;
5189 -- Otherwise we have a real error message (Ada 95 static case) and we
5190 -- make this an unconditional message. Note that in the warning case
5191 -- we do not make the message unconditional, it seems reasonable to
5192 -- delete messages like this (about exceptions that will be raised)
5193 -- in dead code.
5195 else
5196 Wmsg := False;
5197 Msgl := Msgl + 1;
5198 Msgc (Msgl) := '!';
5199 end if;
5201 -- One more test, skip the warning if the related expression is
5202 -- statically unevaluated, since we don't want to warn about what
5203 -- will happen when something is evaluated if it never will be
5204 -- evaluated.
5206 if not Is_Statically_Unevaluated (N) then
5207 if Present (Ent) then
5208 Error_Msg_NEL (Msgc (1 .. Msgl), N, Ent, Eloc);
5209 else
5210 Error_Msg_NEL (Msgc (1 .. Msgl), N, Etype (N), Eloc);
5211 end if;
5213 if Wmsg then
5215 -- Check whether the context is an Init_Proc
5217 if Inside_Init_Proc then
5218 declare
5219 Conc_Typ : constant Entity_Id :=
5220 Corresponding_Concurrent_Type
5221 (Entity (Parameter_Type (First
5222 (Parameter_Specifications
5223 (Parent (Current_Scope))))));
5225 begin
5226 -- Don't complain if the corresponding concurrent type
5227 -- doesn't come from source (i.e. a single task/protected
5228 -- object).
5230 if Present (Conc_Typ)
5231 and then not Comes_From_Source (Conc_Typ)
5232 then
5233 Error_Msg_NEL
5234 ("\& [<<", N, Standard_Constraint_Error, Eloc);
5236 else
5237 if GNATprove_Mode then
5238 Error_Msg_NEL
5239 ("\& would have been raised for objects of this "
5240 & "type", N, Standard_Constraint_Error, Eloc);
5241 else
5242 Error_Msg_NEL
5243 ("\& will be raised for objects of this type??",
5244 N, Standard_Constraint_Error, Eloc);
5245 end if;
5246 end if;
5247 end;
5249 else
5250 Error_Msg_NEL ("\& [<<", N, Standard_Constraint_Error, Eloc);
5251 end if;
5253 else
5254 Error_Msg ("\static expression fails Constraint_Check", Eloc);
5255 Set_Error_Posted (N);
5256 end if;
5257 end if;
5258 end if;
5260 return N;
5261 end Compile_Time_Constraint_Error;
5263 -----------------------
5264 -- Conditional_Delay --
5265 -----------------------
5267 procedure Conditional_Delay (New_Ent, Old_Ent : Entity_Id) is
5268 begin
5269 if Has_Delayed_Freeze (Old_Ent) and then not Is_Frozen (Old_Ent) then
5270 Set_Has_Delayed_Freeze (New_Ent);
5271 end if;
5272 end Conditional_Delay;
5274 ----------------------------
5275 -- Contains_Refined_State --
5276 ----------------------------
5278 function Contains_Refined_State (Prag : Node_Id) return Boolean is
5279 function Has_State_In_Dependency (List : Node_Id) return Boolean;
5280 -- Determine whether a dependency list mentions a state with a visible
5281 -- refinement.
5283 function Has_State_In_Global (List : Node_Id) return Boolean;
5284 -- Determine whether a global list mentions a state with a visible
5285 -- refinement.
5287 function Is_Refined_State (Item : Node_Id) return Boolean;
5288 -- Determine whether Item is a reference to an abstract state with a
5289 -- visible refinement.
5291 -----------------------------
5292 -- Has_State_In_Dependency --
5293 -----------------------------
5295 function Has_State_In_Dependency (List : Node_Id) return Boolean is
5296 Clause : Node_Id;
5297 Output : Node_Id;
5299 begin
5300 -- A null dependency list does not mention any states
5302 if Nkind (List) = N_Null then
5303 return False;
5305 -- Dependency clauses appear as component associations of an
5306 -- aggregate.
5308 elsif Nkind (List) = N_Aggregate
5309 and then Present (Component_Associations (List))
5310 then
5311 Clause := First (Component_Associations (List));
5312 while Present (Clause) loop
5314 -- Inspect the outputs of a dependency clause
5316 Output := First (Choices (Clause));
5317 while Present (Output) loop
5318 if Is_Refined_State (Output) then
5319 return True;
5320 end if;
5322 Next (Output);
5323 end loop;
5325 -- Inspect the outputs of a dependency clause
5327 if Is_Refined_State (Expression (Clause)) then
5328 return True;
5329 end if;
5331 Next (Clause);
5332 end loop;
5334 -- If we get here, then none of the dependency clauses mention a
5335 -- state with visible refinement.
5337 return False;
5339 -- An illegal pragma managed to sneak in
5341 else
5342 raise Program_Error;
5343 end if;
5344 end Has_State_In_Dependency;
5346 -------------------------
5347 -- Has_State_In_Global --
5348 -------------------------
5350 function Has_State_In_Global (List : Node_Id) return Boolean is
5351 Item : Node_Id;
5353 begin
5354 -- A null global list does not mention any states
5356 if Nkind (List) = N_Null then
5357 return False;
5359 -- Simple global list or moded global list declaration
5361 elsif Nkind (List) = N_Aggregate then
5363 -- The declaration of a simple global list appear as a collection
5364 -- of expressions.
5366 if Present (Expressions (List)) then
5367 Item := First (Expressions (List));
5368 while Present (Item) loop
5369 if Is_Refined_State (Item) then
5370 return True;
5371 end if;
5373 Next (Item);
5374 end loop;
5376 -- The declaration of a moded global list appears as a collection
5377 -- of component associations where individual choices denote
5378 -- modes.
5380 else
5381 Item := First (Component_Associations (List));
5382 while Present (Item) loop
5383 if Has_State_In_Global (Expression (Item)) then
5384 return True;
5385 end if;
5387 Next (Item);
5388 end loop;
5389 end if;
5391 -- If we get here, then the simple/moded global list did not
5392 -- mention any states with a visible refinement.
5394 return False;
5396 -- Single global item declaration
5398 elsif Is_Entity_Name (List) then
5399 return Is_Refined_State (List);
5401 -- An illegal pragma managed to sneak in
5403 else
5404 raise Program_Error;
5405 end if;
5406 end Has_State_In_Global;
5408 ----------------------
5409 -- Is_Refined_State --
5410 ----------------------
5412 function Is_Refined_State (Item : Node_Id) return Boolean is
5413 Elmt : Node_Id;
5414 Item_Id : Entity_Id;
5416 begin
5417 if Nkind (Item) = N_Null then
5418 return False;
5420 -- States cannot be subject to attribute 'Result. This case arises
5421 -- in dependency relations.
5423 elsif Nkind (Item) = N_Attribute_Reference
5424 and then Attribute_Name (Item) = Name_Result
5425 then
5426 return False;
5428 -- Multiple items appear as an aggregate. This case arises in
5429 -- dependency relations.
5431 elsif Nkind (Item) = N_Aggregate
5432 and then Present (Expressions (Item))
5433 then
5434 Elmt := First (Expressions (Item));
5435 while Present (Elmt) loop
5436 if Is_Refined_State (Elmt) then
5437 return True;
5438 end if;
5440 Next (Elmt);
5441 end loop;
5443 -- If we get here, then none of the inputs or outputs reference a
5444 -- state with visible refinement.
5446 return False;
5448 -- Single item
5450 else
5451 Item_Id := Entity_Of (Item);
5453 return
5454 Present (Item_Id)
5455 and then Ekind (Item_Id) = E_Abstract_State
5456 and then Has_Visible_Refinement (Item_Id);
5457 end if;
5458 end Is_Refined_State;
5460 -- Local variables
5462 Arg : constant Node_Id :=
5463 Get_Pragma_Arg (First (Pragma_Argument_Associations (Prag)));
5464 Nam : constant Name_Id := Pragma_Name (Prag);
5466 -- Start of processing for Contains_Refined_State
5468 begin
5469 if Nam = Name_Depends then
5470 return Has_State_In_Dependency (Arg);
5472 else pragma Assert (Nam = Name_Global);
5473 return Has_State_In_Global (Arg);
5474 end if;
5475 end Contains_Refined_State;
5477 -------------------------
5478 -- Copy_Component_List --
5479 -------------------------
5481 function Copy_Component_List
5482 (R_Typ : Entity_Id;
5483 Loc : Source_Ptr) return List_Id
5485 Comp : Node_Id;
5486 Comps : constant List_Id := New_List;
5488 begin
5489 Comp := First_Component (Underlying_Type (R_Typ));
5490 while Present (Comp) loop
5491 if Comes_From_Source (Comp) then
5492 declare
5493 Comp_Decl : constant Node_Id := Declaration_Node (Comp);
5494 begin
5495 Append_To (Comps,
5496 Make_Component_Declaration (Loc,
5497 Defining_Identifier =>
5498 Make_Defining_Identifier (Loc, Chars (Comp)),
5499 Component_Definition =>
5500 New_Copy_Tree
5501 (Component_Definition (Comp_Decl), New_Sloc => Loc)));
5502 end;
5503 end if;
5505 Next_Component (Comp);
5506 end loop;
5508 return Comps;
5509 end Copy_Component_List;
5511 -------------------------
5512 -- Copy_Parameter_List --
5513 -------------------------
5515 function Copy_Parameter_List (Subp_Id : Entity_Id) return List_Id is
5516 Loc : constant Source_Ptr := Sloc (Subp_Id);
5517 Plist : List_Id;
5518 Formal : Entity_Id;
5520 begin
5521 if No (First_Formal (Subp_Id)) then
5522 return No_List;
5523 else
5524 Plist := New_List;
5525 Formal := First_Formal (Subp_Id);
5526 while Present (Formal) loop
5527 Append_To (Plist,
5528 Make_Parameter_Specification (Loc,
5529 Defining_Identifier =>
5530 Make_Defining_Identifier (Sloc (Formal), Chars (Formal)),
5531 In_Present => In_Present (Parent (Formal)),
5532 Out_Present => Out_Present (Parent (Formal)),
5533 Parameter_Type =>
5534 New_Occurrence_Of (Etype (Formal), Loc),
5535 Expression =>
5536 New_Copy_Tree (Expression (Parent (Formal)))));
5538 Next_Formal (Formal);
5539 end loop;
5540 end if;
5542 return Plist;
5543 end Copy_Parameter_List;
5545 ----------------------------
5546 -- Copy_SPARK_Mode_Aspect --
5547 ----------------------------
5549 procedure Copy_SPARK_Mode_Aspect (From : Node_Id; To : Node_Id) is
5550 pragma Assert (not Has_Aspects (To));
5551 Asp : Node_Id;
5553 begin
5554 if Has_Aspects (From) then
5555 Asp := Find_Aspect (Defining_Entity (From), Aspect_SPARK_Mode);
5557 if Present (Asp) then
5558 Set_Aspect_Specifications (To, New_List (New_Copy_Tree (Asp)));
5559 Set_Has_Aspects (To, True);
5560 end if;
5561 end if;
5562 end Copy_SPARK_Mode_Aspect;
5564 --------------------------
5565 -- Copy_Subprogram_Spec --
5566 --------------------------
5568 function Copy_Subprogram_Spec (Spec : Node_Id) return Node_Id is
5569 Def_Id : Node_Id;
5570 Formal_Spec : Node_Id;
5571 Result : Node_Id;
5573 begin
5574 -- The structure of the original tree must be replicated without any
5575 -- alterations. Use New_Copy_Tree for this purpose.
5577 Result := New_Copy_Tree (Spec);
5579 -- However, the spec of a null procedure carries the corresponding null
5580 -- statement of the body (created by the parser), and this cannot be
5581 -- shared with the new subprogram spec.
5583 if Nkind (Result) = N_Procedure_Specification then
5584 Set_Null_Statement (Result, Empty);
5585 end if;
5587 -- Create a new entity for the defining unit name
5589 Def_Id := Defining_Unit_Name (Result);
5590 Set_Defining_Unit_Name (Result,
5591 Make_Defining_Identifier (Sloc (Def_Id), Chars (Def_Id)));
5593 -- Create new entities for the formal parameters
5595 if Present (Parameter_Specifications (Result)) then
5596 Formal_Spec := First (Parameter_Specifications (Result));
5597 while Present (Formal_Spec) loop
5598 Def_Id := Defining_Identifier (Formal_Spec);
5599 Set_Defining_Identifier (Formal_Spec,
5600 Make_Defining_Identifier (Sloc (Def_Id), Chars (Def_Id)));
5602 Next (Formal_Spec);
5603 end loop;
5604 end if;
5606 return Result;
5607 end Copy_Subprogram_Spec;
5609 --------------------------------
5610 -- Corresponding_Generic_Type --
5611 --------------------------------
5613 function Corresponding_Generic_Type (T : Entity_Id) return Entity_Id is
5614 Inst : Entity_Id;
5615 Gen : Entity_Id;
5616 Typ : Entity_Id;
5618 begin
5619 if not Is_Generic_Actual_Type (T) then
5620 return Any_Type;
5622 -- If the actual is the actual of an enclosing instance, resolution
5623 -- was correct in the generic.
5625 elsif Nkind (Parent (T)) = N_Subtype_Declaration
5626 and then Is_Entity_Name (Subtype_Indication (Parent (T)))
5627 and then
5628 Is_Generic_Actual_Type (Entity (Subtype_Indication (Parent (T))))
5629 then
5630 return Any_Type;
5632 else
5633 Inst := Scope (T);
5635 if Is_Wrapper_Package (Inst) then
5636 Inst := Related_Instance (Inst);
5637 end if;
5639 Gen :=
5640 Generic_Parent
5641 (Specification (Unit_Declaration_Node (Inst)));
5643 -- Generic actual has the same name as the corresponding formal
5645 Typ := First_Entity (Gen);
5646 while Present (Typ) loop
5647 if Chars (Typ) = Chars (T) then
5648 return Typ;
5649 end if;
5651 Next_Entity (Typ);
5652 end loop;
5654 return Any_Type;
5655 end if;
5656 end Corresponding_Generic_Type;
5658 --------------------
5659 -- Current_Entity --
5660 --------------------
5662 -- The currently visible definition for a given identifier is the
5663 -- one most chained at the start of the visibility chain, i.e. the
5664 -- one that is referenced by the Node_Id value of the name of the
5665 -- given identifier.
5667 function Current_Entity (N : Node_Id) return Entity_Id is
5668 begin
5669 return Get_Name_Entity_Id (Chars (N));
5670 end Current_Entity;
5672 -----------------------------
5673 -- Current_Entity_In_Scope --
5674 -----------------------------
5676 function Current_Entity_In_Scope (N : Node_Id) return Entity_Id is
5677 E : Entity_Id;
5678 CS : constant Entity_Id := Current_Scope;
5680 Transient_Case : constant Boolean := Scope_Is_Transient;
5682 begin
5683 E := Get_Name_Entity_Id (Chars (N));
5684 while Present (E)
5685 and then Scope (E) /= CS
5686 and then (not Transient_Case or else Scope (E) /= Scope (CS))
5687 loop
5688 E := Homonym (E);
5689 end loop;
5691 return E;
5692 end Current_Entity_In_Scope;
5694 -------------------
5695 -- Current_Scope --
5696 -------------------
5698 function Current_Scope return Entity_Id is
5699 begin
5700 if Scope_Stack.Last = -1 then
5701 return Standard_Standard;
5702 else
5703 declare
5704 C : constant Entity_Id :=
5705 Scope_Stack.Table (Scope_Stack.Last).Entity;
5706 begin
5707 if Present (C) then
5708 return C;
5709 else
5710 return Standard_Standard;
5711 end if;
5712 end;
5713 end if;
5714 end Current_Scope;
5716 ----------------------------
5717 -- Current_Scope_No_Loops --
5718 ----------------------------
5720 function Current_Scope_No_Loops return Entity_Id is
5721 S : Entity_Id;
5723 begin
5724 -- Examine the scope stack starting from the current scope and skip any
5725 -- internally generated loops.
5727 S := Current_Scope;
5728 while Present (S) and then S /= Standard_Standard loop
5729 if Ekind (S) = E_Loop and then not Comes_From_Source (S) then
5730 S := Scope (S);
5731 else
5732 exit;
5733 end if;
5734 end loop;
5736 return S;
5737 end Current_Scope_No_Loops;
5739 ------------------------
5740 -- Current_Subprogram --
5741 ------------------------
5743 function Current_Subprogram return Entity_Id is
5744 Scop : constant Entity_Id := Current_Scope;
5745 begin
5746 if Is_Subprogram_Or_Generic_Subprogram (Scop) then
5747 return Scop;
5748 else
5749 return Enclosing_Subprogram (Scop);
5750 end if;
5751 end Current_Subprogram;
5753 ----------------------------------
5754 -- Deepest_Type_Access_Level --
5755 ----------------------------------
5757 function Deepest_Type_Access_Level (Typ : Entity_Id) return Uint is
5758 begin
5759 if Ekind (Typ) = E_Anonymous_Access_Type
5760 and then not Is_Local_Anonymous_Access (Typ)
5761 and then Nkind (Associated_Node_For_Itype (Typ)) = N_Object_Declaration
5762 then
5763 -- Typ is the type of an Ada 2012 stand-alone object of an anonymous
5764 -- access type.
5766 return
5767 Scope_Depth (Enclosing_Dynamic_Scope
5768 (Defining_Identifier
5769 (Associated_Node_For_Itype (Typ))));
5771 -- For generic formal type, return Int'Last (infinite).
5772 -- See comment preceding Is_Generic_Type call in Type_Access_Level.
5774 elsif Is_Generic_Type (Root_Type (Typ)) then
5775 return UI_From_Int (Int'Last);
5777 else
5778 return Type_Access_Level (Typ);
5779 end if;
5780 end Deepest_Type_Access_Level;
5782 ---------------------
5783 -- Defining_Entity --
5784 ---------------------
5786 function Defining_Entity
5787 (N : Node_Id;
5788 Empty_On_Errors : Boolean := False) return Entity_Id
5790 Err : Entity_Id := Empty;
5792 begin
5793 case Nkind (N) is
5794 when N_Abstract_Subprogram_Declaration
5795 | N_Expression_Function
5796 | N_Formal_Subprogram_Declaration
5797 | N_Generic_Package_Declaration
5798 | N_Generic_Subprogram_Declaration
5799 | N_Package_Declaration
5800 | N_Subprogram_Body
5801 | N_Subprogram_Body_Stub
5802 | N_Subprogram_Declaration
5803 | N_Subprogram_Renaming_Declaration
5805 return Defining_Entity (Specification (N));
5807 when N_Component_Declaration
5808 | N_Defining_Program_Unit_Name
5809 | N_Discriminant_Specification
5810 | N_Entry_Body
5811 | N_Entry_Declaration
5812 | N_Entry_Index_Specification
5813 | N_Exception_Declaration
5814 | N_Exception_Renaming_Declaration
5815 | N_Formal_Object_Declaration
5816 | N_Formal_Package_Declaration
5817 | N_Formal_Type_Declaration
5818 | N_Full_Type_Declaration
5819 | N_Implicit_Label_Declaration
5820 | N_Incomplete_Type_Declaration
5821 | N_Iterator_Specification
5822 | N_Loop_Parameter_Specification
5823 | N_Number_Declaration
5824 | N_Object_Declaration
5825 | N_Object_Renaming_Declaration
5826 | N_Package_Body_Stub
5827 | N_Parameter_Specification
5828 | N_Private_Extension_Declaration
5829 | N_Private_Type_Declaration
5830 | N_Protected_Body
5831 | N_Protected_Body_Stub
5832 | N_Protected_Type_Declaration
5833 | N_Single_Protected_Declaration
5834 | N_Single_Task_Declaration
5835 | N_Subtype_Declaration
5836 | N_Task_Body
5837 | N_Task_Body_Stub
5838 | N_Task_Type_Declaration
5840 return Defining_Identifier (N);
5842 when N_Subunit =>
5843 return Defining_Entity (Proper_Body (N));
5845 when N_Function_Instantiation
5846 | N_Function_Specification
5847 | N_Generic_Function_Renaming_Declaration
5848 | N_Generic_Package_Renaming_Declaration
5849 | N_Generic_Procedure_Renaming_Declaration
5850 | N_Package_Body
5851 | N_Package_Instantiation
5852 | N_Package_Renaming_Declaration
5853 | N_Package_Specification
5854 | N_Procedure_Instantiation
5855 | N_Procedure_Specification
5857 declare
5858 Nam : constant Node_Id := Defining_Unit_Name (N);
5860 begin
5861 if Nkind (Nam) in N_Entity then
5862 return Nam;
5864 -- For Error, make up a name and attach to declaration so we
5865 -- can continue semantic analysis.
5867 elsif Nam = Error then
5868 if Empty_On_Errors then
5869 return Empty;
5870 else
5871 Err := Make_Temporary (Sloc (N), 'T');
5872 Set_Defining_Unit_Name (N, Err);
5874 return Err;
5875 end if;
5877 -- If not an entity, get defining identifier
5879 else
5880 return Defining_Identifier (Nam);
5881 end if;
5882 end;
5884 when N_Block_Statement
5885 | N_Loop_Statement
5887 return Entity (Identifier (N));
5889 when others =>
5890 if Empty_On_Errors then
5891 return Empty;
5892 else
5893 raise Program_Error;
5894 end if;
5895 end case;
5896 end Defining_Entity;
5898 --------------------------
5899 -- Denotes_Discriminant --
5900 --------------------------
5902 function Denotes_Discriminant
5903 (N : Node_Id;
5904 Check_Concurrent : Boolean := False) return Boolean
5906 E : Entity_Id;
5908 begin
5909 if not Is_Entity_Name (N) or else No (Entity (N)) then
5910 return False;
5911 else
5912 E := Entity (N);
5913 end if;
5915 -- If we are checking for a protected type, the discriminant may have
5916 -- been rewritten as the corresponding discriminal of the original type
5917 -- or of the corresponding concurrent record, depending on whether we
5918 -- are in the spec or body of the protected type.
5920 return Ekind (E) = E_Discriminant
5921 or else
5922 (Check_Concurrent
5923 and then Ekind (E) = E_In_Parameter
5924 and then Present (Discriminal_Link (E))
5925 and then
5926 (Is_Concurrent_Type (Scope (Discriminal_Link (E)))
5927 or else
5928 Is_Concurrent_Record_Type (Scope (Discriminal_Link (E)))));
5929 end Denotes_Discriminant;
5931 -------------------------
5932 -- Denotes_Same_Object --
5933 -------------------------
5935 function Denotes_Same_Object (A1, A2 : Node_Id) return Boolean is
5936 Obj1 : Node_Id := A1;
5937 Obj2 : Node_Id := A2;
5939 function Has_Prefix (N : Node_Id) return Boolean;
5940 -- Return True if N has attribute Prefix
5942 function Is_Renaming (N : Node_Id) return Boolean;
5943 -- Return true if N names a renaming entity
5945 function Is_Valid_Renaming (N : Node_Id) return Boolean;
5946 -- For renamings, return False if the prefix of any dereference within
5947 -- the renamed object_name is a variable, or any expression within the
5948 -- renamed object_name contains references to variables or calls on
5949 -- nonstatic functions; otherwise return True (RM 6.4.1(6.10/3))
5951 ----------------
5952 -- Has_Prefix --
5953 ----------------
5955 function Has_Prefix (N : Node_Id) return Boolean is
5956 begin
5957 return
5958 Nkind_In (N,
5959 N_Attribute_Reference,
5960 N_Expanded_Name,
5961 N_Explicit_Dereference,
5962 N_Indexed_Component,
5963 N_Reference,
5964 N_Selected_Component,
5965 N_Slice);
5966 end Has_Prefix;
5968 -----------------
5969 -- Is_Renaming --
5970 -----------------
5972 function Is_Renaming (N : Node_Id) return Boolean is
5973 begin
5974 return Is_Entity_Name (N)
5975 and then Present (Renamed_Entity (Entity (N)));
5976 end Is_Renaming;
5978 -----------------------
5979 -- Is_Valid_Renaming --
5980 -----------------------
5982 function Is_Valid_Renaming (N : Node_Id) return Boolean is
5984 function Check_Renaming (N : Node_Id) return Boolean;
5985 -- Recursive function used to traverse all the prefixes of N
5987 function Check_Renaming (N : Node_Id) return Boolean is
5988 begin
5989 if Is_Renaming (N)
5990 and then not Check_Renaming (Renamed_Entity (Entity (N)))
5991 then
5992 return False;
5993 end if;
5995 if Nkind (N) = N_Indexed_Component then
5996 declare
5997 Indx : Node_Id;
5999 begin
6000 Indx := First (Expressions (N));
6001 while Present (Indx) loop
6002 if not Is_OK_Static_Expression (Indx) then
6003 return False;
6004 end if;
6006 Next_Index (Indx);
6007 end loop;
6008 end;
6009 end if;
6011 if Has_Prefix (N) then
6012 declare
6013 P : constant Node_Id := Prefix (N);
6015 begin
6016 if Nkind (N) = N_Explicit_Dereference
6017 and then Is_Variable (P)
6018 then
6019 return False;
6021 elsif Is_Entity_Name (P)
6022 and then Ekind (Entity (P)) = E_Function
6023 then
6024 return False;
6026 elsif Nkind (P) = N_Function_Call then
6027 return False;
6028 end if;
6030 -- Recursion to continue traversing the prefix of the
6031 -- renaming expression
6033 return Check_Renaming (P);
6034 end;
6035 end if;
6037 return True;
6038 end Check_Renaming;
6040 -- Start of processing for Is_Valid_Renaming
6042 begin
6043 return Check_Renaming (N);
6044 end Is_Valid_Renaming;
6046 -- Start of processing for Denotes_Same_Object
6048 begin
6049 -- Both names statically denote the same stand-alone object or parameter
6050 -- (RM 6.4.1(6.5/3))
6052 if Is_Entity_Name (Obj1)
6053 and then Is_Entity_Name (Obj2)
6054 and then Entity (Obj1) = Entity (Obj2)
6055 then
6056 return True;
6057 end if;
6059 -- For renamings, the prefix of any dereference within the renamed
6060 -- object_name is not a variable, and any expression within the
6061 -- renamed object_name contains no references to variables nor
6062 -- calls on nonstatic functions (RM 6.4.1(6.10/3)).
6064 if Is_Renaming (Obj1) then
6065 if Is_Valid_Renaming (Obj1) then
6066 Obj1 := Renamed_Entity (Entity (Obj1));
6067 else
6068 return False;
6069 end if;
6070 end if;
6072 if Is_Renaming (Obj2) then
6073 if Is_Valid_Renaming (Obj2) then
6074 Obj2 := Renamed_Entity (Entity (Obj2));
6075 else
6076 return False;
6077 end if;
6078 end if;
6080 -- No match if not same node kind (such cases are handled by
6081 -- Denotes_Same_Prefix)
6083 if Nkind (Obj1) /= Nkind (Obj2) then
6084 return False;
6086 -- After handling valid renamings, one of the two names statically
6087 -- denoted a renaming declaration whose renamed object_name is known
6088 -- to denote the same object as the other (RM 6.4.1(6.10/3))
6090 elsif Is_Entity_Name (Obj1) then
6091 if Is_Entity_Name (Obj2) then
6092 return Entity (Obj1) = Entity (Obj2);
6093 else
6094 return False;
6095 end if;
6097 -- Both names are selected_components, their prefixes are known to
6098 -- denote the same object, and their selector_names denote the same
6099 -- component (RM 6.4.1(6.6/3)).
6101 elsif Nkind (Obj1) = N_Selected_Component then
6102 return Denotes_Same_Object (Prefix (Obj1), Prefix (Obj2))
6103 and then
6104 Entity (Selector_Name (Obj1)) = Entity (Selector_Name (Obj2));
6106 -- Both names are dereferences and the dereferenced names are known to
6107 -- denote the same object (RM 6.4.1(6.7/3))
6109 elsif Nkind (Obj1) = N_Explicit_Dereference then
6110 return Denotes_Same_Object (Prefix (Obj1), Prefix (Obj2));
6112 -- Both names are indexed_components, their prefixes are known to denote
6113 -- the same object, and each of the pairs of corresponding index values
6114 -- are either both static expressions with the same static value or both
6115 -- names that are known to denote the same object (RM 6.4.1(6.8/3))
6117 elsif Nkind (Obj1) = N_Indexed_Component then
6118 if not Denotes_Same_Object (Prefix (Obj1), Prefix (Obj2)) then
6119 return False;
6120 else
6121 declare
6122 Indx1 : Node_Id;
6123 Indx2 : Node_Id;
6125 begin
6126 Indx1 := First (Expressions (Obj1));
6127 Indx2 := First (Expressions (Obj2));
6128 while Present (Indx1) loop
6130 -- Indexes must denote the same static value or same object
6132 if Is_OK_Static_Expression (Indx1) then
6133 if not Is_OK_Static_Expression (Indx2) then
6134 return False;
6136 elsif Expr_Value (Indx1) /= Expr_Value (Indx2) then
6137 return False;
6138 end if;
6140 elsif not Denotes_Same_Object (Indx1, Indx2) then
6141 return False;
6142 end if;
6144 Next (Indx1);
6145 Next (Indx2);
6146 end loop;
6148 return True;
6149 end;
6150 end if;
6152 -- Both names are slices, their prefixes are known to denote the same
6153 -- object, and the two slices have statically matching index constraints
6154 -- (RM 6.4.1(6.9/3))
6156 elsif Nkind (Obj1) = N_Slice
6157 and then Denotes_Same_Object (Prefix (Obj1), Prefix (Obj2))
6158 then
6159 declare
6160 Lo1, Lo2, Hi1, Hi2 : Node_Id;
6162 begin
6163 Get_Index_Bounds (Etype (Obj1), Lo1, Hi1);
6164 Get_Index_Bounds (Etype (Obj2), Lo2, Hi2);
6166 -- Check whether bounds are statically identical. There is no
6167 -- attempt to detect partial overlap of slices.
6169 return Denotes_Same_Object (Lo1, Lo2)
6170 and then
6171 Denotes_Same_Object (Hi1, Hi2);
6172 end;
6174 -- In the recursion, literals appear as indexes
6176 elsif Nkind (Obj1) = N_Integer_Literal
6177 and then
6178 Nkind (Obj2) = N_Integer_Literal
6179 then
6180 return Intval (Obj1) = Intval (Obj2);
6182 else
6183 return False;
6184 end if;
6185 end Denotes_Same_Object;
6187 -------------------------
6188 -- Denotes_Same_Prefix --
6189 -------------------------
6191 function Denotes_Same_Prefix (A1, A2 : Node_Id) return Boolean is
6192 begin
6193 if Is_Entity_Name (A1) then
6194 if Nkind_In (A2, N_Selected_Component, N_Indexed_Component)
6195 and then not Is_Access_Type (Etype (A1))
6196 then
6197 return Denotes_Same_Object (A1, Prefix (A2))
6198 or else Denotes_Same_Prefix (A1, Prefix (A2));
6199 else
6200 return False;
6201 end if;
6203 elsif Is_Entity_Name (A2) then
6204 return Denotes_Same_Prefix (A1 => A2, A2 => A1);
6206 elsif Nkind_In (A1, N_Selected_Component, N_Indexed_Component, N_Slice)
6207 and then
6208 Nkind_In (A2, N_Selected_Component, N_Indexed_Component, N_Slice)
6209 then
6210 declare
6211 Root1, Root2 : Node_Id;
6212 Depth1, Depth2 : Nat := 0;
6214 begin
6215 Root1 := Prefix (A1);
6216 while not Is_Entity_Name (Root1) loop
6217 if not Nkind_In
6218 (Root1, N_Selected_Component, N_Indexed_Component)
6219 then
6220 return False;
6221 else
6222 Root1 := Prefix (Root1);
6223 end if;
6225 Depth1 := Depth1 + 1;
6226 end loop;
6228 Root2 := Prefix (A2);
6229 while not Is_Entity_Name (Root2) loop
6230 if not Nkind_In (Root2, N_Selected_Component,
6231 N_Indexed_Component)
6232 then
6233 return False;
6234 else
6235 Root2 := Prefix (Root2);
6236 end if;
6238 Depth2 := Depth2 + 1;
6239 end loop;
6241 -- If both have the same depth and they do not denote the same
6242 -- object, they are disjoint and no warning is needed.
6244 if Depth1 = Depth2 then
6245 return False;
6247 elsif Depth1 > Depth2 then
6248 Root1 := Prefix (A1);
6249 for J in 1 .. Depth1 - Depth2 - 1 loop
6250 Root1 := Prefix (Root1);
6251 end loop;
6253 return Denotes_Same_Object (Root1, A2);
6255 else
6256 Root2 := Prefix (A2);
6257 for J in 1 .. Depth2 - Depth1 - 1 loop
6258 Root2 := Prefix (Root2);
6259 end loop;
6261 return Denotes_Same_Object (A1, Root2);
6262 end if;
6263 end;
6265 else
6266 return False;
6267 end if;
6268 end Denotes_Same_Prefix;
6270 ----------------------
6271 -- Denotes_Variable --
6272 ----------------------
6274 function Denotes_Variable (N : Node_Id) return Boolean is
6275 begin
6276 return Is_Variable (N) and then Paren_Count (N) = 0;
6277 end Denotes_Variable;
6279 -----------------------------
6280 -- Depends_On_Discriminant --
6281 -----------------------------
6283 function Depends_On_Discriminant (N : Node_Id) return Boolean is
6284 L : Node_Id;
6285 H : Node_Id;
6287 begin
6288 Get_Index_Bounds (N, L, H);
6289 return Denotes_Discriminant (L) or else Denotes_Discriminant (H);
6290 end Depends_On_Discriminant;
6292 -------------------------
6293 -- Designate_Same_Unit --
6294 -------------------------
6296 function Designate_Same_Unit
6297 (Name1 : Node_Id;
6298 Name2 : Node_Id) return Boolean
6300 K1 : constant Node_Kind := Nkind (Name1);
6301 K2 : constant Node_Kind := Nkind (Name2);
6303 function Prefix_Node (N : Node_Id) return Node_Id;
6304 -- Returns the parent unit name node of a defining program unit name
6305 -- or the prefix if N is a selected component or an expanded name.
6307 function Select_Node (N : Node_Id) return Node_Id;
6308 -- Returns the defining identifier node of a defining program unit
6309 -- name or the selector node if N is a selected component or an
6310 -- expanded name.
6312 -----------------
6313 -- Prefix_Node --
6314 -----------------
6316 function Prefix_Node (N : Node_Id) return Node_Id is
6317 begin
6318 if Nkind (N) = N_Defining_Program_Unit_Name then
6319 return Name (N);
6320 else
6321 return Prefix (N);
6322 end if;
6323 end Prefix_Node;
6325 -----------------
6326 -- Select_Node --
6327 -----------------
6329 function Select_Node (N : Node_Id) return Node_Id is
6330 begin
6331 if Nkind (N) = N_Defining_Program_Unit_Name then
6332 return Defining_Identifier (N);
6333 else
6334 return Selector_Name (N);
6335 end if;
6336 end Select_Node;
6338 -- Start of processing for Designate_Same_Unit
6340 begin
6341 if Nkind_In (K1, N_Identifier, N_Defining_Identifier)
6342 and then
6343 Nkind_In (K2, N_Identifier, N_Defining_Identifier)
6344 then
6345 return Chars (Name1) = Chars (Name2);
6347 elsif Nkind_In (K1, N_Expanded_Name,
6348 N_Selected_Component,
6349 N_Defining_Program_Unit_Name)
6350 and then
6351 Nkind_In (K2, N_Expanded_Name,
6352 N_Selected_Component,
6353 N_Defining_Program_Unit_Name)
6354 then
6355 return
6356 (Chars (Select_Node (Name1)) = Chars (Select_Node (Name2)))
6357 and then
6358 Designate_Same_Unit (Prefix_Node (Name1), Prefix_Node (Name2));
6360 else
6361 return False;
6362 end if;
6363 end Designate_Same_Unit;
6365 ---------------------------------------------
6366 -- Diagnose_Iterated_Component_Association --
6367 ---------------------------------------------
6369 procedure Diagnose_Iterated_Component_Association (N : Node_Id) is
6370 Def_Id : constant Entity_Id := Defining_Identifier (N);
6371 Aggr : Node_Id;
6373 begin
6374 -- Determine whether the iterated component association appears within
6375 -- an aggregate. If this is the case, raise Program_Error because the
6376 -- iterated component association cannot be left in the tree as is and
6377 -- must always be processed by the related aggregate.
6379 Aggr := N;
6380 while Present (Aggr) loop
6381 if Nkind (Aggr) = N_Aggregate then
6382 raise Program_Error;
6384 -- Prevent the search from going too far
6386 elsif Is_Body_Or_Package_Declaration (Aggr) then
6387 exit;
6388 end if;
6390 Aggr := Parent (Aggr);
6391 end loop;
6393 -- At this point it is known that the iterated component association is
6394 -- not within an aggregate. This is really a quantified expression with
6395 -- a missing "all" or "some" quantifier.
6397 Error_Msg_N ("missing quantifier", Def_Id);
6399 -- Rewrite the iterated component association as True to prevent any
6400 -- cascaded errors.
6402 Rewrite (N, New_Occurrence_Of (Standard_True, Sloc (N)));
6403 Analyze (N);
6404 end Diagnose_Iterated_Component_Association;
6406 ---------------------------------
6407 -- Dynamic_Accessibility_Level --
6408 ---------------------------------
6410 function Dynamic_Accessibility_Level (Expr : Node_Id) return Node_Id is
6411 Loc : constant Source_Ptr := Sloc (Expr);
6413 function Make_Level_Literal (Level : Uint) return Node_Id;
6414 -- Construct an integer literal representing an accessibility level
6415 -- with its type set to Natural.
6417 ------------------------
6418 -- Make_Level_Literal --
6419 ------------------------
6421 function Make_Level_Literal (Level : Uint) return Node_Id is
6422 Result : constant Node_Id := Make_Integer_Literal (Loc, Level);
6424 begin
6425 Set_Etype (Result, Standard_Natural);
6426 return Result;
6427 end Make_Level_Literal;
6429 -- Local variables
6431 E : Entity_Id;
6433 -- Start of processing for Dynamic_Accessibility_Level
6435 begin
6436 if Is_Entity_Name (Expr) then
6437 E := Entity (Expr);
6439 if Present (Renamed_Object (E)) then
6440 return Dynamic_Accessibility_Level (Renamed_Object (E));
6441 end if;
6443 if Is_Formal (E) or else Ekind_In (E, E_Variable, E_Constant) then
6444 if Present (Extra_Accessibility (E)) then
6445 return New_Occurrence_Of (Extra_Accessibility (E), Loc);
6446 end if;
6447 end if;
6448 end if;
6450 -- Unimplemented: Ptr.all'Access, where Ptr has Extra_Accessibility ???
6452 case Nkind (Expr) is
6454 -- For access discriminant, the level of the enclosing object
6456 when N_Selected_Component =>
6457 if Ekind (Entity (Selector_Name (Expr))) = E_Discriminant
6458 and then Ekind (Etype (Entity (Selector_Name (Expr)))) =
6459 E_Anonymous_Access_Type
6460 then
6461 return Make_Level_Literal (Object_Access_Level (Expr));
6462 end if;
6464 when N_Attribute_Reference =>
6465 case Get_Attribute_Id (Attribute_Name (Expr)) is
6467 -- For X'Access, the level of the prefix X
6469 when Attribute_Access =>
6470 return Make_Level_Literal
6471 (Object_Access_Level (Prefix (Expr)));
6473 -- Treat the unchecked attributes as library-level
6475 when Attribute_Unchecked_Access
6476 | Attribute_Unrestricted_Access
6478 return Make_Level_Literal (Scope_Depth (Standard_Standard));
6480 -- No other access-valued attributes
6482 when others =>
6483 raise Program_Error;
6484 end case;
6486 when N_Allocator =>
6488 -- Unimplemented: depends on context. As an actual parameter where
6489 -- formal type is anonymous, use
6490 -- Scope_Depth (Current_Scope) + 1.
6491 -- For other cases, see 3.10.2(14/3) and following. ???
6493 null;
6495 when N_Type_Conversion =>
6496 if not Is_Local_Anonymous_Access (Etype (Expr)) then
6498 -- Handle type conversions introduced for a rename of an
6499 -- Ada 2012 stand-alone object of an anonymous access type.
6501 return Dynamic_Accessibility_Level (Expression (Expr));
6502 end if;
6504 when others =>
6505 null;
6506 end case;
6508 return Make_Level_Literal (Type_Access_Level (Etype (Expr)));
6509 end Dynamic_Accessibility_Level;
6511 ------------------------
6512 -- Discriminated_Size --
6513 ------------------------
6515 function Discriminated_Size (Comp : Entity_Id) return Boolean is
6516 function Non_Static_Bound (Bound : Node_Id) return Boolean;
6517 -- Check whether the bound of an index is non-static and does denote
6518 -- a discriminant, in which case any object of the type (protected or
6519 -- otherwise) will have a non-static size.
6521 ----------------------
6522 -- Non_Static_Bound --
6523 ----------------------
6525 function Non_Static_Bound (Bound : Node_Id) return Boolean is
6526 begin
6527 if Is_OK_Static_Expression (Bound) then
6528 return False;
6530 -- If the bound is given by a discriminant it is non-static
6531 -- (A static constraint replaces the reference with the value).
6532 -- In an protected object the discriminant has been replaced by
6533 -- the corresponding discriminal within the protected operation.
6535 elsif Is_Entity_Name (Bound)
6536 and then
6537 (Ekind (Entity (Bound)) = E_Discriminant
6538 or else Present (Discriminal_Link (Entity (Bound))))
6539 then
6540 return False;
6542 else
6543 return True;
6544 end if;
6545 end Non_Static_Bound;
6547 -- Local variables
6549 Typ : constant Entity_Id := Etype (Comp);
6550 Index : Node_Id;
6552 -- Start of processing for Discriminated_Size
6554 begin
6555 if not Is_Array_Type (Typ) then
6556 return False;
6557 end if;
6559 if Ekind (Typ) = E_Array_Subtype then
6560 Index := First_Index (Typ);
6561 while Present (Index) loop
6562 if Non_Static_Bound (Low_Bound (Index))
6563 or else Non_Static_Bound (High_Bound (Index))
6564 then
6565 return False;
6566 end if;
6568 Next_Index (Index);
6569 end loop;
6571 return True;
6572 end if;
6574 return False;
6575 end Discriminated_Size;
6577 -----------------------------------
6578 -- Effective_Extra_Accessibility --
6579 -----------------------------------
6581 function Effective_Extra_Accessibility (Id : Entity_Id) return Entity_Id is
6582 begin
6583 if Present (Renamed_Object (Id))
6584 and then Is_Entity_Name (Renamed_Object (Id))
6585 then
6586 return Effective_Extra_Accessibility (Entity (Renamed_Object (Id)));
6587 else
6588 return Extra_Accessibility (Id);
6589 end if;
6590 end Effective_Extra_Accessibility;
6592 -----------------------------
6593 -- Effective_Reads_Enabled --
6594 -----------------------------
6596 function Effective_Reads_Enabled (Id : Entity_Id) return Boolean is
6597 begin
6598 return Has_Enabled_Property (Id, Name_Effective_Reads);
6599 end Effective_Reads_Enabled;
6601 ------------------------------
6602 -- Effective_Writes_Enabled --
6603 ------------------------------
6605 function Effective_Writes_Enabled (Id : Entity_Id) return Boolean is
6606 begin
6607 return Has_Enabled_Property (Id, Name_Effective_Writes);
6608 end Effective_Writes_Enabled;
6610 ------------------------------
6611 -- Enclosing_Comp_Unit_Node --
6612 ------------------------------
6614 function Enclosing_Comp_Unit_Node (N : Node_Id) return Node_Id is
6615 Current_Node : Node_Id;
6617 begin
6618 Current_Node := N;
6619 while Present (Current_Node)
6620 and then Nkind (Current_Node) /= N_Compilation_Unit
6621 loop
6622 Current_Node := Parent (Current_Node);
6623 end loop;
6625 if Nkind (Current_Node) /= N_Compilation_Unit then
6626 return Empty;
6627 else
6628 return Current_Node;
6629 end if;
6630 end Enclosing_Comp_Unit_Node;
6632 --------------------------
6633 -- Enclosing_CPP_Parent --
6634 --------------------------
6636 function Enclosing_CPP_Parent (Typ : Entity_Id) return Entity_Id is
6637 Parent_Typ : Entity_Id := Typ;
6639 begin
6640 while not Is_CPP_Class (Parent_Typ)
6641 and then Etype (Parent_Typ) /= Parent_Typ
6642 loop
6643 Parent_Typ := Etype (Parent_Typ);
6645 if Is_Private_Type (Parent_Typ) then
6646 Parent_Typ := Full_View (Base_Type (Parent_Typ));
6647 end if;
6648 end loop;
6650 pragma Assert (Is_CPP_Class (Parent_Typ));
6651 return Parent_Typ;
6652 end Enclosing_CPP_Parent;
6654 ---------------------------
6655 -- Enclosing_Declaration --
6656 ---------------------------
6658 function Enclosing_Declaration (N : Node_Id) return Node_Id is
6659 Decl : Node_Id := N;
6661 begin
6662 while Present (Decl)
6663 and then not (Nkind (Decl) in N_Declaration
6664 or else
6665 Nkind (Decl) in N_Later_Decl_Item)
6666 loop
6667 Decl := Parent (Decl);
6668 end loop;
6670 return Decl;
6671 end Enclosing_Declaration;
6673 ----------------------------
6674 -- Enclosing_Generic_Body --
6675 ----------------------------
6677 function Enclosing_Generic_Body
6678 (N : Node_Id) return Node_Id
6680 P : Node_Id;
6681 Decl : Node_Id;
6682 Spec : Node_Id;
6684 begin
6685 P := Parent (N);
6686 while Present (P) loop
6687 if Nkind (P) = N_Package_Body
6688 or else Nkind (P) = N_Subprogram_Body
6689 then
6690 Spec := Corresponding_Spec (P);
6692 if Present (Spec) then
6693 Decl := Unit_Declaration_Node (Spec);
6695 if Nkind (Decl) = N_Generic_Package_Declaration
6696 or else Nkind (Decl) = N_Generic_Subprogram_Declaration
6697 then
6698 return P;
6699 end if;
6700 end if;
6701 end if;
6703 P := Parent (P);
6704 end loop;
6706 return Empty;
6707 end Enclosing_Generic_Body;
6709 ----------------------------
6710 -- Enclosing_Generic_Unit --
6711 ----------------------------
6713 function Enclosing_Generic_Unit
6714 (N : Node_Id) return Node_Id
6716 P : Node_Id;
6717 Decl : Node_Id;
6718 Spec : Node_Id;
6720 begin
6721 P := Parent (N);
6722 while Present (P) loop
6723 if Nkind (P) = N_Generic_Package_Declaration
6724 or else Nkind (P) = N_Generic_Subprogram_Declaration
6725 then
6726 return P;
6728 elsif Nkind (P) = N_Package_Body
6729 or else Nkind (P) = N_Subprogram_Body
6730 then
6731 Spec := Corresponding_Spec (P);
6733 if Present (Spec) then
6734 Decl := Unit_Declaration_Node (Spec);
6736 if Nkind (Decl) = N_Generic_Package_Declaration
6737 or else Nkind (Decl) = N_Generic_Subprogram_Declaration
6738 then
6739 return Decl;
6740 end if;
6741 end if;
6742 end if;
6744 P := Parent (P);
6745 end loop;
6747 return Empty;
6748 end Enclosing_Generic_Unit;
6750 -------------------------------
6751 -- Enclosing_Lib_Unit_Entity --
6752 -------------------------------
6754 function Enclosing_Lib_Unit_Entity
6755 (E : Entity_Id := Current_Scope) return Entity_Id
6757 Unit_Entity : Entity_Id;
6759 begin
6760 -- Look for enclosing library unit entity by following scope links.
6761 -- Equivalent to, but faster than indexing through the scope stack.
6763 Unit_Entity := E;
6764 while (Present (Scope (Unit_Entity))
6765 and then Scope (Unit_Entity) /= Standard_Standard)
6766 and not Is_Child_Unit (Unit_Entity)
6767 loop
6768 Unit_Entity := Scope (Unit_Entity);
6769 end loop;
6771 return Unit_Entity;
6772 end Enclosing_Lib_Unit_Entity;
6774 -----------------------------
6775 -- Enclosing_Lib_Unit_Node --
6776 -----------------------------
6778 function Enclosing_Lib_Unit_Node (N : Node_Id) return Node_Id is
6779 Encl_Unit : Node_Id;
6781 begin
6782 Encl_Unit := Enclosing_Comp_Unit_Node (N);
6783 while Present (Encl_Unit)
6784 and then Nkind (Unit (Encl_Unit)) = N_Subunit
6785 loop
6786 Encl_Unit := Library_Unit (Encl_Unit);
6787 end loop;
6789 pragma Assert (Nkind (Encl_Unit) = N_Compilation_Unit);
6790 return Encl_Unit;
6791 end Enclosing_Lib_Unit_Node;
6793 -----------------------
6794 -- Enclosing_Package --
6795 -----------------------
6797 function Enclosing_Package (E : Entity_Id) return Entity_Id is
6798 Dynamic_Scope : constant Entity_Id := Enclosing_Dynamic_Scope (E);
6800 begin
6801 if Dynamic_Scope = Standard_Standard then
6802 return Standard_Standard;
6804 elsif Dynamic_Scope = Empty then
6805 return Empty;
6807 elsif Ekind_In (Dynamic_Scope, E_Package, E_Package_Body,
6808 E_Generic_Package)
6809 then
6810 return Dynamic_Scope;
6812 else
6813 return Enclosing_Package (Dynamic_Scope);
6814 end if;
6815 end Enclosing_Package;
6817 -------------------------------------
6818 -- Enclosing_Package_Or_Subprogram --
6819 -------------------------------------
6821 function Enclosing_Package_Or_Subprogram (E : Entity_Id) return Entity_Id is
6822 S : Entity_Id;
6824 begin
6825 S := Scope (E);
6826 while Present (S) loop
6827 if Is_Package_Or_Generic_Package (S)
6828 or else Ekind (S) = E_Package_Body
6829 then
6830 return S;
6832 elsif Is_Subprogram_Or_Generic_Subprogram (S)
6833 or else Ekind (S) = E_Subprogram_Body
6834 then
6835 return S;
6837 else
6838 S := Scope (S);
6839 end if;
6840 end loop;
6842 return Empty;
6843 end Enclosing_Package_Or_Subprogram;
6845 --------------------------
6846 -- Enclosing_Subprogram --
6847 --------------------------
6849 function Enclosing_Subprogram (E : Entity_Id) return Entity_Id is
6850 Dynamic_Scope : constant Entity_Id := Enclosing_Dynamic_Scope (E);
6852 begin
6853 if Dynamic_Scope = Standard_Standard then
6854 return Empty;
6856 elsif Dynamic_Scope = Empty then
6857 return Empty;
6859 elsif Ekind (Dynamic_Scope) = E_Subprogram_Body then
6860 return Corresponding_Spec (Parent (Parent (Dynamic_Scope)));
6862 elsif Ekind (Dynamic_Scope) = E_Block
6863 or else Ekind (Dynamic_Scope) = E_Return_Statement
6864 then
6865 return Enclosing_Subprogram (Dynamic_Scope);
6867 elsif Ekind (Dynamic_Scope) = E_Task_Type then
6868 return Get_Task_Body_Procedure (Dynamic_Scope);
6870 elsif Ekind (Dynamic_Scope) = E_Limited_Private_Type
6871 and then Present (Full_View (Dynamic_Scope))
6872 and then Ekind (Full_View (Dynamic_Scope)) = E_Task_Type
6873 then
6874 return Get_Task_Body_Procedure (Full_View (Dynamic_Scope));
6876 -- No body is generated if the protected operation is eliminated
6878 elsif Convention (Dynamic_Scope) = Convention_Protected
6879 and then not Is_Eliminated (Dynamic_Scope)
6880 and then Present (Protected_Body_Subprogram (Dynamic_Scope))
6881 then
6882 return Protected_Body_Subprogram (Dynamic_Scope);
6884 else
6885 return Dynamic_Scope;
6886 end if;
6887 end Enclosing_Subprogram;
6889 ------------------------
6890 -- Ensure_Freeze_Node --
6891 ------------------------
6893 procedure Ensure_Freeze_Node (E : Entity_Id) is
6894 FN : Node_Id;
6895 begin
6896 if No (Freeze_Node (E)) then
6897 FN := Make_Freeze_Entity (Sloc (E));
6898 Set_Has_Delayed_Freeze (E);
6899 Set_Freeze_Node (E, FN);
6900 Set_Access_Types_To_Process (FN, No_Elist);
6901 Set_TSS_Elist (FN, No_Elist);
6902 Set_Entity (FN, E);
6903 end if;
6904 end Ensure_Freeze_Node;
6906 ----------------
6907 -- Enter_Name --
6908 ----------------
6910 procedure Enter_Name (Def_Id : Entity_Id) is
6911 C : constant Entity_Id := Current_Entity (Def_Id);
6912 E : constant Entity_Id := Current_Entity_In_Scope (Def_Id);
6913 S : constant Entity_Id := Current_Scope;
6915 begin
6916 Generate_Definition (Def_Id);
6918 -- Add new name to current scope declarations. Check for duplicate
6919 -- declaration, which may or may not be a genuine error.
6921 if Present (E) then
6923 -- Case of previous entity entered because of a missing declaration
6924 -- or else a bad subtype indication. Best is to use the new entity,
6925 -- and make the previous one invisible.
6927 if Etype (E) = Any_Type then
6928 Set_Is_Immediately_Visible (E, False);
6930 -- Case of renaming declaration constructed for package instances.
6931 -- if there is an explicit declaration with the same identifier,
6932 -- the renaming is not immediately visible any longer, but remains
6933 -- visible through selected component notation.
6935 elsif Nkind (Parent (E)) = N_Package_Renaming_Declaration
6936 and then not Comes_From_Source (E)
6937 then
6938 Set_Is_Immediately_Visible (E, False);
6940 -- The new entity may be the package renaming, which has the same
6941 -- same name as a generic formal which has been seen already.
6943 elsif Nkind (Parent (Def_Id)) = N_Package_Renaming_Declaration
6944 and then not Comes_From_Source (Def_Id)
6945 then
6946 Set_Is_Immediately_Visible (E, False);
6948 -- For a fat pointer corresponding to a remote access to subprogram,
6949 -- we use the same identifier as the RAS type, so that the proper
6950 -- name appears in the stub. This type is only retrieved through
6951 -- the RAS type and never by visibility, and is not added to the
6952 -- visibility list (see below).
6954 elsif Nkind (Parent (Def_Id)) = N_Full_Type_Declaration
6955 and then Ekind (Def_Id) = E_Record_Type
6956 and then Present (Corresponding_Remote_Type (Def_Id))
6957 then
6958 null;
6960 -- Case of an implicit operation or derived literal. The new entity
6961 -- hides the implicit one, which is removed from all visibility,
6962 -- i.e. the entity list of its scope, and homonym chain of its name.
6964 elsif (Is_Overloadable (E) and then Is_Inherited_Operation (E))
6965 or else Is_Internal (E)
6966 then
6967 declare
6968 Decl : constant Node_Id := Parent (E);
6969 Prev : Entity_Id;
6970 Prev_Vis : Entity_Id;
6972 begin
6973 -- If E is an implicit declaration, it cannot be the first
6974 -- entity in the scope.
6976 Prev := First_Entity (Current_Scope);
6977 while Present (Prev) and then Next_Entity (Prev) /= E loop
6978 Next_Entity (Prev);
6979 end loop;
6981 if No (Prev) then
6983 -- If E is not on the entity chain of the current scope,
6984 -- it is an implicit declaration in the generic formal
6985 -- part of a generic subprogram. When analyzing the body,
6986 -- the generic formals are visible but not on the entity
6987 -- chain of the subprogram. The new entity will become
6988 -- the visible one in the body.
6990 pragma Assert
6991 (Nkind (Parent (Decl)) = N_Generic_Subprogram_Declaration);
6992 null;
6994 else
6995 Set_Next_Entity (Prev, Next_Entity (E));
6997 if No (Next_Entity (Prev)) then
6998 Set_Last_Entity (Current_Scope, Prev);
6999 end if;
7001 if E = Current_Entity (E) then
7002 Prev_Vis := Empty;
7004 else
7005 Prev_Vis := Current_Entity (E);
7006 while Homonym (Prev_Vis) /= E loop
7007 Prev_Vis := Homonym (Prev_Vis);
7008 end loop;
7009 end if;
7011 if Present (Prev_Vis) then
7013 -- Skip E in the visibility chain
7015 Set_Homonym (Prev_Vis, Homonym (E));
7017 else
7018 Set_Name_Entity_Id (Chars (E), Homonym (E));
7019 end if;
7020 end if;
7021 end;
7023 -- This section of code could use a comment ???
7025 elsif Present (Etype (E))
7026 and then Is_Concurrent_Type (Etype (E))
7027 and then E = Def_Id
7028 then
7029 return;
7031 -- If the homograph is a protected component renaming, it should not
7032 -- be hiding the current entity. Such renamings are treated as weak
7033 -- declarations.
7035 elsif Is_Prival (E) then
7036 Set_Is_Immediately_Visible (E, False);
7038 -- In this case the current entity is a protected component renaming.
7039 -- Perform minimal decoration by setting the scope and return since
7040 -- the prival should not be hiding other visible entities.
7042 elsif Is_Prival (Def_Id) then
7043 Set_Scope (Def_Id, Current_Scope);
7044 return;
7046 -- Analogous to privals, the discriminal generated for an entry index
7047 -- parameter acts as a weak declaration. Perform minimal decoration
7048 -- to avoid bogus errors.
7050 elsif Is_Discriminal (Def_Id)
7051 and then Ekind (Discriminal_Link (Def_Id)) = E_Entry_Index_Parameter
7052 then
7053 Set_Scope (Def_Id, Current_Scope);
7054 return;
7056 -- In the body or private part of an instance, a type extension may
7057 -- introduce a component with the same name as that of an actual. The
7058 -- legality rule is not enforced, but the semantics of the full type
7059 -- with two components of same name are not clear at this point???
7061 elsif In_Instance_Not_Visible then
7062 null;
7064 -- When compiling a package body, some child units may have become
7065 -- visible. They cannot conflict with local entities that hide them.
7067 elsif Is_Child_Unit (E)
7068 and then In_Open_Scopes (Scope (E))
7069 and then not Is_Immediately_Visible (E)
7070 then
7071 null;
7073 -- Conversely, with front-end inlining we may compile the parent body
7074 -- first, and a child unit subsequently. The context is now the
7075 -- parent spec, and body entities are not visible.
7077 elsif Is_Child_Unit (Def_Id)
7078 and then Is_Package_Body_Entity (E)
7079 and then not In_Package_Body (Current_Scope)
7080 then
7081 null;
7083 -- Case of genuine duplicate declaration
7085 else
7086 Error_Msg_Sloc := Sloc (E);
7088 -- If the previous declaration is an incomplete type declaration
7089 -- this may be an attempt to complete it with a private type. The
7090 -- following avoids confusing cascaded errors.
7092 if Nkind (Parent (E)) = N_Incomplete_Type_Declaration
7093 and then Nkind (Parent (Def_Id)) = N_Private_Type_Declaration
7094 then
7095 Error_Msg_N
7096 ("incomplete type cannot be completed with a private " &
7097 "declaration", Parent (Def_Id));
7098 Set_Is_Immediately_Visible (E, False);
7099 Set_Full_View (E, Def_Id);
7101 -- An inherited component of a record conflicts with a new
7102 -- discriminant. The discriminant is inserted first in the scope,
7103 -- but the error should be posted on it, not on the component.
7105 elsif Ekind (E) = E_Discriminant
7106 and then Present (Scope (Def_Id))
7107 and then Scope (Def_Id) /= Current_Scope
7108 then
7109 Error_Msg_Sloc := Sloc (Def_Id);
7110 Error_Msg_N ("& conflicts with declaration#", E);
7111 return;
7113 -- If the name of the unit appears in its own context clause, a
7114 -- dummy package with the name has already been created, and the
7115 -- error emitted. Try to continue quietly.
7117 elsif Error_Posted (E)
7118 and then Sloc (E) = No_Location
7119 and then Nkind (Parent (E)) = N_Package_Specification
7120 and then Current_Scope = Standard_Standard
7121 then
7122 Set_Scope (Def_Id, Current_Scope);
7123 return;
7125 else
7126 Error_Msg_N ("& conflicts with declaration#", Def_Id);
7128 -- Avoid cascaded messages with duplicate components in
7129 -- derived types.
7131 if Ekind_In (E, E_Component, E_Discriminant) then
7132 return;
7133 end if;
7134 end if;
7136 if Nkind (Parent (Parent (Def_Id))) =
7137 N_Generic_Subprogram_Declaration
7138 and then Def_Id =
7139 Defining_Entity (Specification (Parent (Parent (Def_Id))))
7140 then
7141 Error_Msg_N ("\generic units cannot be overloaded", Def_Id);
7142 end if;
7144 -- If entity is in standard, then we are in trouble, because it
7145 -- means that we have a library package with a duplicated name.
7146 -- That's hard to recover from, so abort.
7148 if S = Standard_Standard then
7149 raise Unrecoverable_Error;
7151 -- Otherwise we continue with the declaration. Having two
7152 -- identical declarations should not cause us too much trouble.
7154 else
7155 null;
7156 end if;
7157 end if;
7158 end if;
7160 -- If we fall through, declaration is OK, at least OK enough to continue
7162 -- If Def_Id is a discriminant or a record component we are in the midst
7163 -- of inheriting components in a derived record definition. Preserve
7164 -- their Ekind and Etype.
7166 if Ekind_In (Def_Id, E_Discriminant, E_Component) then
7167 null;
7169 -- If a type is already set, leave it alone (happens when a type
7170 -- declaration is reanalyzed following a call to the optimizer).
7172 elsif Present (Etype (Def_Id)) then
7173 null;
7175 -- Otherwise, the kind E_Void insures that premature uses of the entity
7176 -- will be detected. Any_Type insures that no cascaded errors will occur
7178 else
7179 Set_Ekind (Def_Id, E_Void);
7180 Set_Etype (Def_Id, Any_Type);
7181 end if;
7183 -- Inherited discriminants and components in derived record types are
7184 -- immediately visible. Itypes are not.
7186 -- Unless the Itype is for a record type with a corresponding remote
7187 -- type (what is that about, it was not commented ???)
7189 if Ekind_In (Def_Id, E_Discriminant, E_Component)
7190 or else
7191 ((not Is_Record_Type (Def_Id)
7192 or else No (Corresponding_Remote_Type (Def_Id)))
7193 and then not Is_Itype (Def_Id))
7194 then
7195 Set_Is_Immediately_Visible (Def_Id);
7196 Set_Current_Entity (Def_Id);
7197 end if;
7199 Set_Homonym (Def_Id, C);
7200 Append_Entity (Def_Id, S);
7201 Set_Public_Status (Def_Id);
7203 -- Declaring a homonym is not allowed in SPARK ...
7205 if Present (C) and then Restriction_Check_Required (SPARK_05) then
7206 declare
7207 Enclosing_Subp : constant Node_Id := Enclosing_Subprogram (Def_Id);
7208 Enclosing_Pack : constant Node_Id := Enclosing_Package (Def_Id);
7209 Other_Scope : constant Node_Id := Enclosing_Dynamic_Scope (C);
7211 begin
7212 -- ... unless the new declaration is in a subprogram, and the
7213 -- visible declaration is a variable declaration or a parameter
7214 -- specification outside that subprogram.
7216 if Present (Enclosing_Subp)
7217 and then Nkind_In (Parent (C), N_Object_Declaration,
7218 N_Parameter_Specification)
7219 and then not Scope_Within_Or_Same (Other_Scope, Enclosing_Subp)
7220 then
7221 null;
7223 -- ... or the new declaration is in a package, and the visible
7224 -- declaration occurs outside that package.
7226 elsif Present (Enclosing_Pack)
7227 and then not Scope_Within_Or_Same (Other_Scope, Enclosing_Pack)
7228 then
7229 null;
7231 -- ... or the new declaration is a component declaration in a
7232 -- record type definition.
7234 elsif Nkind (Parent (Def_Id)) = N_Component_Declaration then
7235 null;
7237 -- Don't issue error for non-source entities
7239 elsif Comes_From_Source (Def_Id)
7240 and then Comes_From_Source (C)
7241 then
7242 Error_Msg_Sloc := Sloc (C);
7243 Check_SPARK_05_Restriction
7244 ("redeclaration of identifier &#", Def_Id);
7245 end if;
7246 end;
7247 end if;
7249 -- Warn if new entity hides an old one
7251 if Warn_On_Hiding and then Present (C)
7253 -- Don't warn for record components since they always have a well
7254 -- defined scope which does not confuse other uses. Note that in
7255 -- some cases, Ekind has not been set yet.
7257 and then Ekind (C) /= E_Component
7258 and then Ekind (C) /= E_Discriminant
7259 and then Nkind (Parent (C)) /= N_Component_Declaration
7260 and then Ekind (Def_Id) /= E_Component
7261 and then Ekind (Def_Id) /= E_Discriminant
7262 and then Nkind (Parent (Def_Id)) /= N_Component_Declaration
7264 -- Don't warn for one character variables. It is too common to use
7265 -- such variables as locals and will just cause too many false hits.
7267 and then Length_Of_Name (Chars (C)) /= 1
7269 -- Don't warn for non-source entities
7271 and then Comes_From_Source (C)
7272 and then Comes_From_Source (Def_Id)
7274 -- Don't warn unless entity in question is in extended main source
7276 and then In_Extended_Main_Source_Unit (Def_Id)
7278 -- Finally, the hidden entity must be either immediately visible or
7279 -- use visible (i.e. from a used package).
7281 and then
7282 (Is_Immediately_Visible (C)
7283 or else
7284 Is_Potentially_Use_Visible (C))
7285 then
7286 Error_Msg_Sloc := Sloc (C);
7287 Error_Msg_N ("declaration hides &#?h?", Def_Id);
7288 end if;
7289 end Enter_Name;
7291 ---------------
7292 -- Entity_Of --
7293 ---------------
7295 function Entity_Of (N : Node_Id) return Entity_Id is
7296 Id : Entity_Id;
7297 Ren : Node_Id;
7299 begin
7300 -- Assume that the arbitrary node does not have an entity
7302 Id := Empty;
7304 if Is_Entity_Name (N) then
7305 Id := Entity (N);
7307 -- Follow a possible chain of renamings to reach the earliest renamed
7308 -- source object.
7310 while Present (Id)
7311 and then Is_Object (Id)
7312 and then Present (Renamed_Object (Id))
7313 loop
7314 Ren := Renamed_Object (Id);
7316 -- The reference renames an abstract state or a whole object
7318 -- Obj : ...;
7319 -- Ren : ... renames Obj;
7321 if Is_Entity_Name (Ren) then
7322 Id := Entity (Ren);
7324 -- The reference renames a function result. Check the original
7325 -- node in case expansion relocates the function call.
7327 -- Ren : ... renames Func_Call;
7329 elsif Nkind (Original_Node (Ren)) = N_Function_Call then
7330 exit;
7332 -- Otherwise the reference renames something which does not yield
7333 -- an abstract state or a whole object. Treat the reference as not
7334 -- having a proper entity for SPARK legality purposes.
7336 else
7337 Id := Empty;
7338 exit;
7339 end if;
7340 end loop;
7341 end if;
7343 return Id;
7344 end Entity_Of;
7346 --------------------------
7347 -- Explain_Limited_Type --
7348 --------------------------
7350 procedure Explain_Limited_Type (T : Entity_Id; N : Node_Id) is
7351 C : Entity_Id;
7353 begin
7354 -- For array, component type must be limited
7356 if Is_Array_Type (T) then
7357 Error_Msg_Node_2 := T;
7358 Error_Msg_NE
7359 ("\component type& of type& is limited", N, Component_Type (T));
7360 Explain_Limited_Type (Component_Type (T), N);
7362 elsif Is_Record_Type (T) then
7364 -- No need for extra messages if explicit limited record
7366 if Is_Limited_Record (Base_Type (T)) then
7367 return;
7368 end if;
7370 -- Otherwise find a limited component. Check only components that
7371 -- come from source, or inherited components that appear in the
7372 -- source of the ancestor.
7374 C := First_Component (T);
7375 while Present (C) loop
7376 if Is_Limited_Type (Etype (C))
7377 and then
7378 (Comes_From_Source (C)
7379 or else
7380 (Present (Original_Record_Component (C))
7381 and then
7382 Comes_From_Source (Original_Record_Component (C))))
7383 then
7384 Error_Msg_Node_2 := T;
7385 Error_Msg_NE ("\component& of type& has limited type", N, C);
7386 Explain_Limited_Type (Etype (C), N);
7387 return;
7388 end if;
7390 Next_Component (C);
7391 end loop;
7393 -- The type may be declared explicitly limited, even if no component
7394 -- of it is limited, in which case we fall out of the loop.
7395 return;
7396 end if;
7397 end Explain_Limited_Type;
7399 ---------------------------------------
7400 -- Expression_Of_Expression_Function --
7401 ---------------------------------------
7403 function Expression_Of_Expression_Function
7404 (Subp : Entity_Id) return Node_Id
7406 Expr_Func : Node_Id;
7408 begin
7409 pragma Assert (Is_Expression_Function_Or_Completion (Subp));
7411 if Nkind (Original_Node (Subprogram_Spec (Subp))) =
7412 N_Expression_Function
7413 then
7414 Expr_Func := Original_Node (Subprogram_Spec (Subp));
7416 elsif Nkind (Original_Node (Subprogram_Body (Subp))) =
7417 N_Expression_Function
7418 then
7419 Expr_Func := Original_Node (Subprogram_Body (Subp));
7421 else
7422 pragma Assert (False);
7423 null;
7424 end if;
7426 return Original_Node (Expression (Expr_Func));
7427 end Expression_Of_Expression_Function;
7429 -------------------------------
7430 -- Extensions_Visible_Status --
7431 -------------------------------
7433 function Extensions_Visible_Status
7434 (Id : Entity_Id) return Extensions_Visible_Mode
7436 Arg : Node_Id;
7437 Decl : Node_Id;
7438 Expr : Node_Id;
7439 Prag : Node_Id;
7440 Subp : Entity_Id;
7442 begin
7443 -- When a formal parameter is subject to Extensions_Visible, the pragma
7444 -- is stored in the contract of related subprogram.
7446 if Is_Formal (Id) then
7447 Subp := Scope (Id);
7449 elsif Is_Subprogram_Or_Generic_Subprogram (Id) then
7450 Subp := Id;
7452 -- No other construct carries this pragma
7454 else
7455 return Extensions_Visible_None;
7456 end if;
7458 Prag := Get_Pragma (Subp, Pragma_Extensions_Visible);
7460 -- In certain cases analysis may request the Extensions_Visible status
7461 -- of an expression function before the pragma has been analyzed yet.
7462 -- Inspect the declarative items after the expression function looking
7463 -- for the pragma (if any).
7465 if No (Prag) and then Is_Expression_Function (Subp) then
7466 Decl := Next (Unit_Declaration_Node (Subp));
7467 while Present (Decl) loop
7468 if Nkind (Decl) = N_Pragma
7469 and then Pragma_Name (Decl) = Name_Extensions_Visible
7470 then
7471 Prag := Decl;
7472 exit;
7474 -- A source construct ends the region where Extensions_Visible may
7475 -- appear, stop the traversal. An expanded expression function is
7476 -- no longer a source construct, but it must still be recognized.
7478 elsif Comes_From_Source (Decl)
7479 or else
7480 (Nkind_In (Decl, N_Subprogram_Body,
7481 N_Subprogram_Declaration)
7482 and then Is_Expression_Function (Defining_Entity (Decl)))
7483 then
7484 exit;
7485 end if;
7487 Next (Decl);
7488 end loop;
7489 end if;
7491 -- Extract the value from the Boolean expression (if any)
7493 if Present (Prag) then
7494 Arg := First (Pragma_Argument_Associations (Prag));
7496 if Present (Arg) then
7497 Expr := Get_Pragma_Arg (Arg);
7499 -- When the associated subprogram is an expression function, the
7500 -- argument of the pragma may not have been analyzed.
7502 if not Analyzed (Expr) then
7503 Preanalyze_And_Resolve (Expr, Standard_Boolean);
7504 end if;
7506 -- Guard against cascading errors when the argument of pragma
7507 -- Extensions_Visible is not a valid static Boolean expression.
7509 if Error_Posted (Expr) then
7510 return Extensions_Visible_None;
7512 elsif Is_True (Expr_Value (Expr)) then
7513 return Extensions_Visible_True;
7515 else
7516 return Extensions_Visible_False;
7517 end if;
7519 -- Otherwise the aspect or pragma defaults to True
7521 else
7522 return Extensions_Visible_True;
7523 end if;
7525 -- Otherwise aspect or pragma Extensions_Visible is not inherited or
7526 -- directly specified. In SPARK code, its value defaults to "False".
7528 elsif SPARK_Mode = On then
7529 return Extensions_Visible_False;
7531 -- In non-SPARK code, aspect or pragma Extensions_Visible defaults to
7532 -- "True".
7534 else
7535 return Extensions_Visible_True;
7536 end if;
7537 end Extensions_Visible_Status;
7539 -----------------
7540 -- Find_Actual --
7541 -----------------
7543 procedure Find_Actual
7544 (N : Node_Id;
7545 Formal : out Entity_Id;
7546 Call : out Node_Id)
7548 Context : constant Node_Id := Parent (N);
7549 Actual : Node_Id;
7550 Call_Nam : Node_Id;
7552 begin
7553 if Nkind_In (Context, N_Indexed_Component, N_Selected_Component)
7554 and then N = Prefix (Context)
7555 then
7556 Find_Actual (Context, Formal, Call);
7557 return;
7559 elsif Nkind (Context) = N_Parameter_Association
7560 and then N = Explicit_Actual_Parameter (Context)
7561 then
7562 Call := Parent (Context);
7564 elsif Nkind_In (Context, N_Entry_Call_Statement,
7565 N_Function_Call,
7566 N_Procedure_Call_Statement)
7567 then
7568 Call := Context;
7570 else
7571 Formal := Empty;
7572 Call := Empty;
7573 return;
7574 end if;
7576 -- If we have a call to a subprogram look for the parameter. Note that
7577 -- we exclude overloaded calls, since we don't know enough to be sure
7578 -- of giving the right answer in this case.
7580 if Nkind_In (Call, N_Entry_Call_Statement,
7581 N_Function_Call,
7582 N_Procedure_Call_Statement)
7583 then
7584 Call_Nam := Name (Call);
7586 -- A call to a protected or task entry appears as a selected
7587 -- component rather than an expanded name.
7589 if Nkind (Call_Nam) = N_Selected_Component then
7590 Call_Nam := Selector_Name (Call_Nam);
7591 end if;
7593 if Is_Entity_Name (Call_Nam)
7594 and then Present (Entity (Call_Nam))
7595 and then Is_Overloadable (Entity (Call_Nam))
7596 and then not Is_Overloaded (Call_Nam)
7597 then
7598 -- If node is name in call it is not an actual
7600 if N = Call_Nam then
7601 Formal := Empty;
7602 Call := Empty;
7603 return;
7604 end if;
7606 -- Fall here if we are definitely a parameter
7608 Actual := First_Actual (Call);
7609 Formal := First_Formal (Entity (Call_Nam));
7610 while Present (Formal) and then Present (Actual) loop
7611 if Actual = N then
7612 return;
7614 -- An actual that is the prefix in a prefixed call may have
7615 -- been rewritten in the call, after the deferred reference
7616 -- was collected. Check if sloc and kinds and names match.
7618 elsif Sloc (Actual) = Sloc (N)
7619 and then Nkind (Actual) = N_Identifier
7620 and then Nkind (Actual) = Nkind (N)
7621 and then Chars (Actual) = Chars (N)
7622 then
7623 return;
7625 else
7626 Actual := Next_Actual (Actual);
7627 Formal := Next_Formal (Formal);
7628 end if;
7629 end loop;
7630 end if;
7631 end if;
7633 -- Fall through here if we did not find matching actual
7635 Formal := Empty;
7636 Call := Empty;
7637 end Find_Actual;
7639 ---------------------------
7640 -- Find_Body_Discriminal --
7641 ---------------------------
7643 function Find_Body_Discriminal
7644 (Spec_Discriminant : Entity_Id) return Entity_Id
7646 Tsk : Entity_Id;
7647 Disc : Entity_Id;
7649 begin
7650 -- If expansion is suppressed, then the scope can be the concurrent type
7651 -- itself rather than a corresponding concurrent record type.
7653 if Is_Concurrent_Type (Scope (Spec_Discriminant)) then
7654 Tsk := Scope (Spec_Discriminant);
7656 else
7657 pragma Assert (Is_Concurrent_Record_Type (Scope (Spec_Discriminant)));
7659 Tsk := Corresponding_Concurrent_Type (Scope (Spec_Discriminant));
7660 end if;
7662 -- Find discriminant of original concurrent type, and use its current
7663 -- discriminal, which is the renaming within the task/protected body.
7665 Disc := First_Discriminant (Tsk);
7666 while Present (Disc) loop
7667 if Chars (Disc) = Chars (Spec_Discriminant) then
7668 return Discriminal (Disc);
7669 end if;
7671 Next_Discriminant (Disc);
7672 end loop;
7674 -- That loop should always succeed in finding a matching entry and
7675 -- returning. Fatal error if not.
7677 raise Program_Error;
7678 end Find_Body_Discriminal;
7680 -------------------------------------
7681 -- Find_Corresponding_Discriminant --
7682 -------------------------------------
7684 function Find_Corresponding_Discriminant
7685 (Id : Node_Id;
7686 Typ : Entity_Id) return Entity_Id
7688 Par_Disc : Entity_Id;
7689 Old_Disc : Entity_Id;
7690 New_Disc : Entity_Id;
7692 begin
7693 Par_Disc := Original_Record_Component (Original_Discriminant (Id));
7695 -- The original type may currently be private, and the discriminant
7696 -- only appear on its full view.
7698 if Is_Private_Type (Scope (Par_Disc))
7699 and then not Has_Discriminants (Scope (Par_Disc))
7700 and then Present (Full_View (Scope (Par_Disc)))
7701 then
7702 Old_Disc := First_Discriminant (Full_View (Scope (Par_Disc)));
7703 else
7704 Old_Disc := First_Discriminant (Scope (Par_Disc));
7705 end if;
7707 if Is_Class_Wide_Type (Typ) then
7708 New_Disc := First_Discriminant (Root_Type (Typ));
7709 else
7710 New_Disc := First_Discriminant (Typ);
7711 end if;
7713 while Present (Old_Disc) and then Present (New_Disc) loop
7714 if Old_Disc = Par_Disc then
7715 return New_Disc;
7716 end if;
7718 Next_Discriminant (Old_Disc);
7719 Next_Discriminant (New_Disc);
7720 end loop;
7722 -- Should always find it
7724 raise Program_Error;
7725 end Find_Corresponding_Discriminant;
7727 ----------------------------------
7728 -- Find_Enclosing_Iterator_Loop --
7729 ----------------------------------
7731 function Find_Enclosing_Iterator_Loop (Id : Entity_Id) return Entity_Id is
7732 Constr : Node_Id;
7733 S : Entity_Id;
7735 begin
7736 -- Traverse the scope chain looking for an iterator loop. Such loops are
7737 -- usually transformed into blocks, hence the use of Original_Node.
7739 S := Id;
7740 while Present (S) and then S /= Standard_Standard loop
7741 if Ekind (S) = E_Loop
7742 and then Nkind (Parent (S)) = N_Implicit_Label_Declaration
7743 then
7744 Constr := Original_Node (Label_Construct (Parent (S)));
7746 if Nkind (Constr) = N_Loop_Statement
7747 and then Present (Iteration_Scheme (Constr))
7748 and then Nkind (Iterator_Specification
7749 (Iteration_Scheme (Constr))) =
7750 N_Iterator_Specification
7751 then
7752 return S;
7753 end if;
7754 end if;
7756 S := Scope (S);
7757 end loop;
7759 return Empty;
7760 end Find_Enclosing_Iterator_Loop;
7762 ------------------------------------
7763 -- Find_Loop_In_Conditional_Block --
7764 ------------------------------------
7766 function Find_Loop_In_Conditional_Block (N : Node_Id) return Node_Id is
7767 Stmt : Node_Id;
7769 begin
7770 Stmt := N;
7772 if Nkind (Stmt) = N_If_Statement then
7773 Stmt := First (Then_Statements (Stmt));
7774 end if;
7776 pragma Assert (Nkind (Stmt) = N_Block_Statement);
7778 -- Inspect the statements of the conditional block. In general the loop
7779 -- should be the first statement in the statement sequence of the block,
7780 -- but the finalization machinery may have introduced extra object
7781 -- declarations.
7783 Stmt := First (Statements (Handled_Statement_Sequence (Stmt)));
7784 while Present (Stmt) loop
7785 if Nkind (Stmt) = N_Loop_Statement then
7786 return Stmt;
7787 end if;
7789 Next (Stmt);
7790 end loop;
7792 -- The expansion of attribute 'Loop_Entry produced a malformed block
7794 raise Program_Error;
7795 end Find_Loop_In_Conditional_Block;
7797 --------------------------
7798 -- Find_Overlaid_Entity --
7799 --------------------------
7801 procedure Find_Overlaid_Entity
7802 (N : Node_Id;
7803 Ent : out Entity_Id;
7804 Off : out Boolean)
7806 Expr : Node_Id;
7808 begin
7809 -- We are looking for one of the two following forms:
7811 -- for X'Address use Y'Address
7813 -- or
7815 -- Const : constant Address := expr;
7816 -- ...
7817 -- for X'Address use Const;
7819 -- In the second case, the expr is either Y'Address, or recursively a
7820 -- constant that eventually references Y'Address.
7822 Ent := Empty;
7823 Off := False;
7825 if Nkind (N) = N_Attribute_Definition_Clause
7826 and then Chars (N) = Name_Address
7827 then
7828 Expr := Expression (N);
7830 -- This loop checks the form of the expression for Y'Address,
7831 -- using recursion to deal with intermediate constants.
7833 loop
7834 -- Check for Y'Address
7836 if Nkind (Expr) = N_Attribute_Reference
7837 and then Attribute_Name (Expr) = Name_Address
7838 then
7839 Expr := Prefix (Expr);
7840 exit;
7842 -- Check for Const where Const is a constant entity
7844 elsif Is_Entity_Name (Expr)
7845 and then Ekind (Entity (Expr)) = E_Constant
7846 then
7847 Expr := Constant_Value (Entity (Expr));
7849 -- Anything else does not need checking
7851 else
7852 return;
7853 end if;
7854 end loop;
7856 -- This loop checks the form of the prefix for an entity, using
7857 -- recursion to deal with intermediate components.
7859 loop
7860 -- Check for Y where Y is an entity
7862 if Is_Entity_Name (Expr) then
7863 Ent := Entity (Expr);
7864 return;
7866 -- Check for components
7868 elsif
7869 Nkind_In (Expr, N_Selected_Component, N_Indexed_Component)
7870 then
7871 Expr := Prefix (Expr);
7872 Off := True;
7874 -- Anything else does not need checking
7876 else
7877 return;
7878 end if;
7879 end loop;
7880 end if;
7881 end Find_Overlaid_Entity;
7883 -------------------------
7884 -- Find_Parameter_Type --
7885 -------------------------
7887 function Find_Parameter_Type (Param : Node_Id) return Entity_Id is
7888 begin
7889 if Nkind (Param) /= N_Parameter_Specification then
7890 return Empty;
7892 -- For an access parameter, obtain the type from the formal entity
7893 -- itself, because access to subprogram nodes do not carry a type.
7894 -- Shouldn't we always use the formal entity ???
7896 elsif Nkind (Parameter_Type (Param)) = N_Access_Definition then
7897 return Etype (Defining_Identifier (Param));
7899 else
7900 return Etype (Parameter_Type (Param));
7901 end if;
7902 end Find_Parameter_Type;
7904 -----------------------------------
7905 -- Find_Placement_In_State_Space --
7906 -----------------------------------
7908 procedure Find_Placement_In_State_Space
7909 (Item_Id : Entity_Id;
7910 Placement : out State_Space_Kind;
7911 Pack_Id : out Entity_Id)
7913 Context : Entity_Id;
7915 begin
7916 -- Assume that the item does not appear in the state space of a package
7918 Placement := Not_In_Package;
7919 Pack_Id := Empty;
7921 -- Climb the scope stack and examine the enclosing context
7923 Context := Scope (Item_Id);
7924 while Present (Context) and then Context /= Standard_Standard loop
7925 if Ekind (Context) = E_Package then
7926 Pack_Id := Context;
7928 -- A package body is a cut off point for the traversal as the item
7929 -- cannot be visible to the outside from this point on. Note that
7930 -- this test must be done first as a body is also classified as a
7931 -- private part.
7933 if In_Package_Body (Context) then
7934 Placement := Body_State_Space;
7935 return;
7937 -- The private part of a package is a cut off point for the
7938 -- traversal as the item cannot be visible to the outside from
7939 -- this point on.
7941 elsif In_Private_Part (Context) then
7942 Placement := Private_State_Space;
7943 return;
7945 -- When the item appears in the visible state space of a package,
7946 -- continue to climb the scope stack as this may not be the final
7947 -- state space.
7949 else
7950 Placement := Visible_State_Space;
7952 -- The visible state space of a child unit acts as the proper
7953 -- placement of an item.
7955 if Is_Child_Unit (Context) then
7956 return;
7957 end if;
7958 end if;
7960 -- The item or its enclosing package appear in a construct that has
7961 -- no state space.
7963 else
7964 Placement := Not_In_Package;
7965 return;
7966 end if;
7968 Context := Scope (Context);
7969 end loop;
7970 end Find_Placement_In_State_Space;
7972 ------------------------
7973 -- Find_Specific_Type --
7974 ------------------------
7976 function Find_Specific_Type (CW : Entity_Id) return Entity_Id is
7977 Typ : Entity_Id := Root_Type (CW);
7979 begin
7980 if Ekind (Typ) = E_Incomplete_Type then
7981 if From_Limited_With (Typ) then
7982 Typ := Non_Limited_View (Typ);
7983 else
7984 Typ := Full_View (Typ);
7985 end if;
7986 end if;
7988 if Is_Private_Type (Typ)
7989 and then not Is_Tagged_Type (Typ)
7990 and then Present (Full_View (Typ))
7991 then
7992 return Full_View (Typ);
7993 else
7994 return Typ;
7995 end if;
7996 end Find_Specific_Type;
7998 -----------------------------
7999 -- Find_Static_Alternative --
8000 -----------------------------
8002 function Find_Static_Alternative (N : Node_Id) return Node_Id is
8003 Expr : constant Node_Id := Expression (N);
8004 Val : constant Uint := Expr_Value (Expr);
8005 Alt : Node_Id;
8006 Choice : Node_Id;
8008 begin
8009 Alt := First (Alternatives (N));
8011 Search : loop
8012 if Nkind (Alt) /= N_Pragma then
8013 Choice := First (Discrete_Choices (Alt));
8014 while Present (Choice) loop
8016 -- Others choice, always matches
8018 if Nkind (Choice) = N_Others_Choice then
8019 exit Search;
8021 -- Range, check if value is in the range
8023 elsif Nkind (Choice) = N_Range then
8024 exit Search when
8025 Val >= Expr_Value (Low_Bound (Choice))
8026 and then
8027 Val <= Expr_Value (High_Bound (Choice));
8029 -- Choice is a subtype name. Note that we know it must
8030 -- be a static subtype, since otherwise it would have
8031 -- been diagnosed as illegal.
8033 elsif Is_Entity_Name (Choice)
8034 and then Is_Type (Entity (Choice))
8035 then
8036 exit Search when Is_In_Range (Expr, Etype (Choice),
8037 Assume_Valid => False);
8039 -- Choice is a subtype indication
8041 elsif Nkind (Choice) = N_Subtype_Indication then
8042 declare
8043 C : constant Node_Id := Constraint (Choice);
8044 R : constant Node_Id := Range_Expression (C);
8046 begin
8047 exit Search when
8048 Val >= Expr_Value (Low_Bound (R))
8049 and then
8050 Val <= Expr_Value (High_Bound (R));
8051 end;
8053 -- Choice is a simple expression
8055 else
8056 exit Search when Val = Expr_Value (Choice);
8057 end if;
8059 Next (Choice);
8060 end loop;
8061 end if;
8063 Next (Alt);
8064 pragma Assert (Present (Alt));
8065 end loop Search;
8067 -- The above loop *must* terminate by finding a match, since we know the
8068 -- case statement is valid, and the value of the expression is known at
8069 -- compile time. When we fall out of the loop, Alt points to the
8070 -- alternative that we know will be selected at run time.
8072 return Alt;
8073 end Find_Static_Alternative;
8075 ------------------
8076 -- First_Actual --
8077 ------------------
8079 function First_Actual (Node : Node_Id) return Node_Id is
8080 N : Node_Id;
8082 begin
8083 if No (Parameter_Associations (Node)) then
8084 return Empty;
8085 end if;
8087 N := First (Parameter_Associations (Node));
8089 if Nkind (N) = N_Parameter_Association then
8090 return First_Named_Actual (Node);
8091 else
8092 return N;
8093 end if;
8094 end First_Actual;
8096 ------------------
8097 -- First_Global --
8098 ------------------
8100 function First_Global
8101 (Subp : Entity_Id;
8102 Global_Mode : Name_Id;
8103 Refined : Boolean := False) return Node_Id
8105 function First_From_Global_List
8106 (List : Node_Id;
8107 Global_Mode : Name_Id := Name_Input) return Entity_Id;
8108 -- Get the first item with suitable mode from List
8110 ----------------------------
8111 -- First_From_Global_List --
8112 ----------------------------
8114 function First_From_Global_List
8115 (List : Node_Id;
8116 Global_Mode : Name_Id := Name_Input) return Entity_Id
8118 Assoc : Node_Id;
8120 begin
8121 -- Empty list (no global items)
8123 if Nkind (List) = N_Null then
8124 return Empty;
8126 -- Single global item declaration (only input items)
8128 elsif Nkind_In (List, N_Expanded_Name,
8129 N_Identifier,
8130 N_Selected_Component)
8131 then
8132 if Global_Mode = Name_Input then
8133 return List;
8134 else
8135 return Empty;
8136 end if;
8138 -- Simple global list (only input items) or moded global list
8139 -- declaration.
8141 elsif Nkind (List) = N_Aggregate then
8142 if Present (Expressions (List)) then
8143 if Global_Mode = Name_Input then
8144 return First (Expressions (List));
8145 else
8146 return Empty;
8147 end if;
8149 else
8150 Assoc := First (Component_Associations (List));
8151 while Present (Assoc) loop
8153 -- When we find the desired mode in an association, call
8154 -- recursively First_From_Global_List as if the mode was
8155 -- Name_Input, in order to reuse the existing machinery
8156 -- for the other cases.
8158 if Chars (First (Choices (Assoc))) = Global_Mode then
8159 return First_From_Global_List (Expression (Assoc));
8160 end if;
8162 Next (Assoc);
8163 end loop;
8165 return Empty;
8166 end if;
8168 -- To accommodate partial decoration of disabled SPARK features,
8169 -- this routine may be called with illegal input. If this is the
8170 -- case, do not raise Program_Error.
8172 else
8173 return Empty;
8174 end if;
8175 end First_From_Global_List;
8177 -- Local variables
8179 Global : Node_Id := Empty;
8180 Body_Id : Entity_Id;
8182 begin
8183 pragma Assert (Global_Mode = Name_Input
8184 or else Global_Mode = Name_Output
8185 or else Global_Mode = Name_In_Out
8186 or else Global_Mode = Name_Proof_In);
8188 -- Retrieve the suitable pragma Global or Refined_Global. In the second
8189 -- case, it can only be located on the body entity.
8191 if Refined then
8192 Body_Id := Subprogram_Body_Entity (Subp);
8193 if Present (Body_Id) then
8194 Global := Get_Pragma (Body_Id, Pragma_Refined_Global);
8195 end if;
8196 else
8197 Global := Get_Pragma (Subp, Pragma_Global);
8198 end if;
8200 -- No corresponding global if pragma is not present
8202 if No (Global) then
8203 return Empty;
8205 -- Otherwise retrieve the corresponding list of items depending on the
8206 -- Global_Mode.
8208 else
8209 return First_From_Global_List
8210 (Expression (Get_Argument (Global, Subp)), Global_Mode);
8211 end if;
8212 end First_Global;
8214 -------------
8215 -- Fix_Msg --
8216 -------------
8218 function Fix_Msg (Id : Entity_Id; Msg : String) return String is
8219 Is_Task : constant Boolean :=
8220 Ekind_In (Id, E_Task_Body, E_Task_Type)
8221 or else Is_Single_Task_Object (Id);
8222 Msg_Last : constant Natural := Msg'Last;
8223 Msg_Index : Natural;
8224 Res : String (Msg'Range) := (others => ' ');
8225 Res_Index : Natural;
8227 begin
8228 -- Copy all characters from the input message Msg to result Res with
8229 -- suitable replacements.
8231 Msg_Index := Msg'First;
8232 Res_Index := Res'First;
8233 while Msg_Index <= Msg_Last loop
8235 -- Replace "subprogram" with a different word
8237 if Msg_Index <= Msg_Last - 10
8238 and then Msg (Msg_Index .. Msg_Index + 9) = "subprogram"
8239 then
8240 if Ekind_In (Id, E_Entry, E_Entry_Family) then
8241 Res (Res_Index .. Res_Index + 4) := "entry";
8242 Res_Index := Res_Index + 5;
8244 elsif Is_Task then
8245 Res (Res_Index .. Res_Index + 8) := "task type";
8246 Res_Index := Res_Index + 9;
8248 else
8249 Res (Res_Index .. Res_Index + 9) := "subprogram";
8250 Res_Index := Res_Index + 10;
8251 end if;
8253 Msg_Index := Msg_Index + 10;
8255 -- Replace "protected" with a different word
8257 elsif Msg_Index <= Msg_Last - 9
8258 and then Msg (Msg_Index .. Msg_Index + 8) = "protected"
8259 and then Is_Task
8260 then
8261 Res (Res_Index .. Res_Index + 3) := "task";
8262 Res_Index := Res_Index + 4;
8263 Msg_Index := Msg_Index + 9;
8265 -- Otherwise copy the character
8267 else
8268 Res (Res_Index) := Msg (Msg_Index);
8269 Msg_Index := Msg_Index + 1;
8270 Res_Index := Res_Index + 1;
8271 end if;
8272 end loop;
8274 return Res (Res'First .. Res_Index - 1);
8275 end Fix_Msg;
8277 -------------------------
8278 -- From_Nested_Package --
8279 -------------------------
8281 function From_Nested_Package (T : Entity_Id) return Boolean is
8282 Pack : constant Entity_Id := Scope (T);
8284 begin
8285 return
8286 Ekind (Pack) = E_Package
8287 and then not Is_Frozen (Pack)
8288 and then not Scope_Within_Or_Same (Current_Scope, Pack)
8289 and then In_Open_Scopes (Scope (Pack));
8290 end From_Nested_Package;
8292 -----------------------
8293 -- Gather_Components --
8294 -----------------------
8296 procedure Gather_Components
8297 (Typ : Entity_Id;
8298 Comp_List : Node_Id;
8299 Governed_By : List_Id;
8300 Into : Elist_Id;
8301 Report_Errors : out Boolean)
8303 Assoc : Node_Id;
8304 Variant : Node_Id;
8305 Discrete_Choice : Node_Id;
8306 Comp_Item : Node_Id;
8308 Discrim : Entity_Id;
8309 Discrim_Name : Node_Id;
8310 Discrim_Value : Node_Id;
8312 begin
8313 Report_Errors := False;
8315 if No (Comp_List) or else Null_Present (Comp_List) then
8316 return;
8318 elsif Present (Component_Items (Comp_List)) then
8319 Comp_Item := First (Component_Items (Comp_List));
8321 else
8322 Comp_Item := Empty;
8323 end if;
8325 while Present (Comp_Item) loop
8327 -- Skip the tag of a tagged record, the interface tags, as well
8328 -- as all items that are not user components (anonymous types,
8329 -- rep clauses, Parent field, controller field).
8331 if Nkind (Comp_Item) = N_Component_Declaration then
8332 declare
8333 Comp : constant Entity_Id := Defining_Identifier (Comp_Item);
8334 begin
8335 if not Is_Tag (Comp) and then Chars (Comp) /= Name_uParent then
8336 Append_Elmt (Comp, Into);
8337 end if;
8338 end;
8339 end if;
8341 Next (Comp_Item);
8342 end loop;
8344 if No (Variant_Part (Comp_List)) then
8345 return;
8346 else
8347 Discrim_Name := Name (Variant_Part (Comp_List));
8348 Variant := First_Non_Pragma (Variants (Variant_Part (Comp_List)));
8349 end if;
8351 -- Look for the discriminant that governs this variant part.
8352 -- The discriminant *must* be in the Governed_By List
8354 Assoc := First (Governed_By);
8355 Find_Constraint : loop
8356 Discrim := First (Choices (Assoc));
8357 exit Find_Constraint when Chars (Discrim_Name) = Chars (Discrim)
8358 or else (Present (Corresponding_Discriminant (Entity (Discrim)))
8359 and then
8360 Chars (Corresponding_Discriminant (Entity (Discrim))) =
8361 Chars (Discrim_Name))
8362 or else Chars (Original_Record_Component (Entity (Discrim)))
8363 = Chars (Discrim_Name);
8365 if No (Next (Assoc)) then
8366 if not Is_Constrained (Typ)
8367 and then Is_Derived_Type (Typ)
8368 and then Present (Stored_Constraint (Typ))
8369 then
8370 -- If the type is a tagged type with inherited discriminants,
8371 -- use the stored constraint on the parent in order to find
8372 -- the values of discriminants that are otherwise hidden by an
8373 -- explicit constraint. Renamed discriminants are handled in
8374 -- the code above.
8376 -- If several parent discriminants are renamed by a single
8377 -- discriminant of the derived type, the call to obtain the
8378 -- Corresponding_Discriminant field only retrieves the last
8379 -- of them. We recover the constraint on the others from the
8380 -- Stored_Constraint as well.
8382 declare
8383 D : Entity_Id;
8384 C : Elmt_Id;
8386 begin
8387 D := First_Discriminant (Etype (Typ));
8388 C := First_Elmt (Stored_Constraint (Typ));
8389 while Present (D) and then Present (C) loop
8390 if Chars (Discrim_Name) = Chars (D) then
8391 if Is_Entity_Name (Node (C))
8392 and then Entity (Node (C)) = Entity (Discrim)
8393 then
8394 -- D is renamed by Discrim, whose value is given in
8395 -- Assoc.
8397 null;
8399 else
8400 Assoc :=
8401 Make_Component_Association (Sloc (Typ),
8402 New_List
8403 (New_Occurrence_Of (D, Sloc (Typ))),
8404 Duplicate_Subexpr_No_Checks (Node (C)));
8405 end if;
8406 exit Find_Constraint;
8407 end if;
8409 Next_Discriminant (D);
8410 Next_Elmt (C);
8411 end loop;
8412 end;
8413 end if;
8414 end if;
8416 if No (Next (Assoc)) then
8417 Error_Msg_NE (" missing value for discriminant&",
8418 First (Governed_By), Discrim_Name);
8419 Report_Errors := True;
8420 return;
8421 end if;
8423 Next (Assoc);
8424 end loop Find_Constraint;
8426 Discrim_Value := Expression (Assoc);
8428 if not Is_OK_Static_Expression (Discrim_Value) then
8430 -- If the variant part is governed by a discriminant of the type
8431 -- this is an error. If the variant part and the discriminant are
8432 -- inherited from an ancestor this is legal (AI05-120) unless the
8433 -- components are being gathered for an aggregate, in which case
8434 -- the caller must check Report_Errors.
8436 if Scope (Original_Record_Component
8437 ((Entity (First (Choices (Assoc)))))) = Typ
8438 then
8439 Error_Msg_FE
8440 ("value for discriminant & must be static!",
8441 Discrim_Value, Discrim);
8442 Why_Not_Static (Discrim_Value);
8443 end if;
8445 Report_Errors := True;
8446 return;
8447 end if;
8449 Search_For_Discriminant_Value : declare
8450 Low : Node_Id;
8451 High : Node_Id;
8453 UI_High : Uint;
8454 UI_Low : Uint;
8455 UI_Discrim_Value : constant Uint := Expr_Value (Discrim_Value);
8457 begin
8458 Find_Discrete_Value : while Present (Variant) loop
8459 Discrete_Choice := First (Discrete_Choices (Variant));
8460 while Present (Discrete_Choice) loop
8461 exit Find_Discrete_Value when
8462 Nkind (Discrete_Choice) = N_Others_Choice;
8464 Get_Index_Bounds (Discrete_Choice, Low, High);
8466 UI_Low := Expr_Value (Low);
8467 UI_High := Expr_Value (High);
8469 exit Find_Discrete_Value when
8470 UI_Low <= UI_Discrim_Value
8471 and then
8472 UI_High >= UI_Discrim_Value;
8474 Next (Discrete_Choice);
8475 end loop;
8477 Next_Non_Pragma (Variant);
8478 end loop Find_Discrete_Value;
8479 end Search_For_Discriminant_Value;
8481 -- The case statement must include a variant that corresponds to the
8482 -- value of the discriminant, unless the discriminant type has a
8483 -- static predicate. In that case the absence of an others_choice that
8484 -- would cover this value becomes a run-time error (3.8,1 (21.1/2)).
8486 if No (Variant)
8487 and then not Has_Static_Predicate (Etype (Discrim_Name))
8488 then
8489 Error_Msg_NE
8490 ("value of discriminant & is out of range", Discrim_Value, Discrim);
8491 Report_Errors := True;
8492 return;
8493 end if;
8495 -- If we have found the corresponding choice, recursively add its
8496 -- components to the Into list. The nested components are part of
8497 -- the same record type.
8499 if Present (Variant) then
8500 Gather_Components
8501 (Typ, Component_List (Variant), Governed_By, Into, Report_Errors);
8502 end if;
8503 end Gather_Components;
8505 ------------------------
8506 -- Get_Actual_Subtype --
8507 ------------------------
8509 function Get_Actual_Subtype (N : Node_Id) return Entity_Id is
8510 Typ : constant Entity_Id := Etype (N);
8511 Utyp : Entity_Id := Underlying_Type (Typ);
8512 Decl : Node_Id;
8513 Atyp : Entity_Id;
8515 begin
8516 if No (Utyp) then
8517 Utyp := Typ;
8518 end if;
8520 -- If what we have is an identifier that references a subprogram
8521 -- formal, or a variable or constant object, then we get the actual
8522 -- subtype from the referenced entity if one has been built.
8524 if Nkind (N) = N_Identifier
8525 and then
8526 (Is_Formal (Entity (N))
8527 or else Ekind (Entity (N)) = E_Constant
8528 or else Ekind (Entity (N)) = E_Variable)
8529 and then Present (Actual_Subtype (Entity (N)))
8530 then
8531 return Actual_Subtype (Entity (N));
8533 -- Actual subtype of unchecked union is always itself. We never need
8534 -- the "real" actual subtype. If we did, we couldn't get it anyway
8535 -- because the discriminant is not available. The restrictions on
8536 -- Unchecked_Union are designed to make sure that this is OK.
8538 elsif Is_Unchecked_Union (Base_Type (Utyp)) then
8539 return Typ;
8541 -- Here for the unconstrained case, we must find actual subtype
8542 -- No actual subtype is available, so we must build it on the fly.
8544 -- Checking the type, not the underlying type, for constrainedness
8545 -- seems to be necessary. Maybe all the tests should be on the type???
8547 elsif (not Is_Constrained (Typ))
8548 and then (Is_Array_Type (Utyp)
8549 or else (Is_Record_Type (Utyp)
8550 and then Has_Discriminants (Utyp)))
8551 and then not Has_Unknown_Discriminants (Utyp)
8552 and then not (Ekind (Utyp) = E_String_Literal_Subtype)
8553 then
8554 -- Nothing to do if in spec expression (why not???)
8556 if In_Spec_Expression then
8557 return Typ;
8559 elsif Is_Private_Type (Typ) and then not Has_Discriminants (Typ) then
8561 -- If the type has no discriminants, there is no subtype to
8562 -- build, even if the underlying type is discriminated.
8564 return Typ;
8566 -- Else build the actual subtype
8568 else
8569 Decl := Build_Actual_Subtype (Typ, N);
8570 Atyp := Defining_Identifier (Decl);
8572 -- If Build_Actual_Subtype generated a new declaration then use it
8574 if Atyp /= Typ then
8576 -- The actual subtype is an Itype, so analyze the declaration,
8577 -- but do not attach it to the tree, to get the type defined.
8579 Set_Parent (Decl, N);
8580 Set_Is_Itype (Atyp);
8581 Analyze (Decl, Suppress => All_Checks);
8582 Set_Associated_Node_For_Itype (Atyp, N);
8583 Set_Has_Delayed_Freeze (Atyp, False);
8585 -- We need to freeze the actual subtype immediately. This is
8586 -- needed, because otherwise this Itype will not get frozen
8587 -- at all, and it is always safe to freeze on creation because
8588 -- any associated types must be frozen at this point.
8590 Freeze_Itype (Atyp, N);
8591 return Atyp;
8593 -- Otherwise we did not build a declaration, so return original
8595 else
8596 return Typ;
8597 end if;
8598 end if;
8600 -- For all remaining cases, the actual subtype is the same as
8601 -- the nominal type.
8603 else
8604 return Typ;
8605 end if;
8606 end Get_Actual_Subtype;
8608 -------------------------------------
8609 -- Get_Actual_Subtype_If_Available --
8610 -------------------------------------
8612 function Get_Actual_Subtype_If_Available (N : Node_Id) return Entity_Id is
8613 Typ : constant Entity_Id := Etype (N);
8615 begin
8616 -- If what we have is an identifier that references a subprogram
8617 -- formal, or a variable or constant object, then we get the actual
8618 -- subtype from the referenced entity if one has been built.
8620 if Nkind (N) = N_Identifier
8621 and then
8622 (Is_Formal (Entity (N))
8623 or else Ekind (Entity (N)) = E_Constant
8624 or else Ekind (Entity (N)) = E_Variable)
8625 and then Present (Actual_Subtype (Entity (N)))
8626 then
8627 return Actual_Subtype (Entity (N));
8629 -- Otherwise the Etype of N is returned unchanged
8631 else
8632 return Typ;
8633 end if;
8634 end Get_Actual_Subtype_If_Available;
8636 ------------------------
8637 -- Get_Body_From_Stub --
8638 ------------------------
8640 function Get_Body_From_Stub (N : Node_Id) return Node_Id is
8641 begin
8642 return Proper_Body (Unit (Library_Unit (N)));
8643 end Get_Body_From_Stub;
8645 ---------------------
8646 -- Get_Cursor_Type --
8647 ---------------------
8649 function Get_Cursor_Type
8650 (Aspect : Node_Id;
8651 Typ : Entity_Id) return Entity_Id
8653 Assoc : Node_Id;
8654 Func : Entity_Id;
8655 First_Op : Entity_Id;
8656 Cursor : Entity_Id;
8658 begin
8659 -- If error already detected, return
8661 if Error_Posted (Aspect) then
8662 return Any_Type;
8663 end if;
8665 -- The cursor type for an Iterable aspect is the return type of a
8666 -- non-overloaded First primitive operation. Locate association for
8667 -- First.
8669 Assoc := First (Component_Associations (Expression (Aspect)));
8670 First_Op := Any_Id;
8671 while Present (Assoc) loop
8672 if Chars (First (Choices (Assoc))) = Name_First then
8673 First_Op := Expression (Assoc);
8674 exit;
8675 end if;
8677 Next (Assoc);
8678 end loop;
8680 if First_Op = Any_Id then
8681 Error_Msg_N ("aspect Iterable must specify First operation", Aspect);
8682 return Any_Type;
8683 end if;
8685 Cursor := Any_Type;
8687 -- Locate function with desired name and profile in scope of type
8688 -- In the rare case where the type is an integer type, a base type
8689 -- is created for it, check that the base type of the first formal
8690 -- of First matches the base type of the domain.
8692 Func := First_Entity (Scope (Typ));
8693 while Present (Func) loop
8694 if Chars (Func) = Chars (First_Op)
8695 and then Ekind (Func) = E_Function
8696 and then Present (First_Formal (Func))
8697 and then Base_Type (Etype (First_Formal (Func))) = Base_Type (Typ)
8698 and then No (Next_Formal (First_Formal (Func)))
8699 then
8700 if Cursor /= Any_Type then
8701 Error_Msg_N
8702 ("Operation First for iterable type must be unique", Aspect);
8703 return Any_Type;
8704 else
8705 Cursor := Etype (Func);
8706 end if;
8707 end if;
8709 Next_Entity (Func);
8710 end loop;
8712 -- If not found, no way to resolve remaining primitives.
8714 if Cursor = Any_Type then
8715 Error_Msg_N
8716 ("No legal primitive operation First for Iterable type", Aspect);
8717 end if;
8719 return Cursor;
8720 end Get_Cursor_Type;
8722 function Get_Cursor_Type (Typ : Entity_Id) return Entity_Id is
8723 begin
8724 return Etype (Get_Iterable_Type_Primitive (Typ, Name_First));
8725 end Get_Cursor_Type;
8727 -------------------------------
8728 -- Get_Default_External_Name --
8729 -------------------------------
8731 function Get_Default_External_Name (E : Node_Or_Entity_Id) return Node_Id is
8732 begin
8733 Get_Decoded_Name_String (Chars (E));
8735 if Opt.External_Name_Imp_Casing = Uppercase then
8736 Set_Casing (All_Upper_Case);
8737 else
8738 Set_Casing (All_Lower_Case);
8739 end if;
8741 return
8742 Make_String_Literal (Sloc (E),
8743 Strval => String_From_Name_Buffer);
8744 end Get_Default_External_Name;
8746 --------------------------
8747 -- Get_Enclosing_Object --
8748 --------------------------
8750 function Get_Enclosing_Object (N : Node_Id) return Entity_Id is
8751 begin
8752 if Is_Entity_Name (N) then
8753 return Entity (N);
8754 else
8755 case Nkind (N) is
8756 when N_Indexed_Component
8757 | N_Selected_Component
8758 | N_Slice
8760 -- If not generating code, a dereference may be left implicit.
8761 -- In thoses cases, return Empty.
8763 if Is_Access_Type (Etype (Prefix (N))) then
8764 return Empty;
8765 else
8766 return Get_Enclosing_Object (Prefix (N));
8767 end if;
8769 when N_Type_Conversion =>
8770 return Get_Enclosing_Object (Expression (N));
8772 when others =>
8773 return Empty;
8774 end case;
8775 end if;
8776 end Get_Enclosing_Object;
8778 ---------------------------
8779 -- Get_Enum_Lit_From_Pos --
8780 ---------------------------
8782 function Get_Enum_Lit_From_Pos
8783 (T : Entity_Id;
8784 Pos : Uint;
8785 Loc : Source_Ptr) return Node_Id
8787 Btyp : Entity_Id := Base_Type (T);
8788 Lit : Node_Id;
8789 LLoc : Source_Ptr;
8791 begin
8792 -- In the case where the literal is of type Character, Wide_Character
8793 -- or Wide_Wide_Character or of a type derived from them, there needs
8794 -- to be some special handling since there is no explicit chain of
8795 -- literals to search. Instead, an N_Character_Literal node is created
8796 -- with the appropriate Char_Code and Chars fields.
8798 if Is_Standard_Character_Type (T) then
8799 Set_Character_Literal_Name (UI_To_CC (Pos));
8801 return
8802 Make_Character_Literal (Loc,
8803 Chars => Name_Find,
8804 Char_Literal_Value => Pos);
8806 -- For all other cases, we have a complete table of literals, and
8807 -- we simply iterate through the chain of literal until the one
8808 -- with the desired position value is found.
8810 else
8811 if Is_Private_Type (Btyp) and then Present (Full_View (Btyp)) then
8812 Btyp := Full_View (Btyp);
8813 end if;
8815 Lit := First_Literal (Btyp);
8816 for J in 1 .. UI_To_Int (Pos) loop
8817 Next_Literal (Lit);
8819 -- If Lit is Empty, Pos is not in range, so raise Constraint_Error
8820 -- inside the loop to avoid calling Next_Literal on Empty.
8822 if No (Lit) then
8823 raise Constraint_Error;
8824 end if;
8825 end loop;
8827 -- Create a new node from Lit, with source location provided by Loc
8828 -- if not equal to No_Location, or by copying the source location of
8829 -- Lit otherwise.
8831 LLoc := Loc;
8833 if LLoc = No_Location then
8834 LLoc := Sloc (Lit);
8835 end if;
8837 return New_Occurrence_Of (Lit, LLoc);
8838 end if;
8839 end Get_Enum_Lit_From_Pos;
8841 ------------------------
8842 -- Get_Generic_Entity --
8843 ------------------------
8845 function Get_Generic_Entity (N : Node_Id) return Entity_Id is
8846 Ent : constant Entity_Id := Entity (Name (N));
8847 begin
8848 if Present (Renamed_Object (Ent)) then
8849 return Renamed_Object (Ent);
8850 else
8851 return Ent;
8852 end if;
8853 end Get_Generic_Entity;
8855 -------------------------------------
8856 -- Get_Incomplete_View_Of_Ancestor --
8857 -------------------------------------
8859 function Get_Incomplete_View_Of_Ancestor (E : Entity_Id) return Entity_Id is
8860 Cur_Unit : constant Entity_Id := Cunit_Entity (Current_Sem_Unit);
8861 Par_Scope : Entity_Id;
8862 Par_Type : Entity_Id;
8864 begin
8865 -- The incomplete view of an ancestor is only relevant for private
8866 -- derived types in child units.
8868 if not Is_Derived_Type (E)
8869 or else not Is_Child_Unit (Cur_Unit)
8870 then
8871 return Empty;
8873 else
8874 Par_Scope := Scope (Cur_Unit);
8875 if No (Par_Scope) then
8876 return Empty;
8877 end if;
8879 Par_Type := Etype (Base_Type (E));
8881 -- Traverse list of ancestor types until we find one declared in
8882 -- a parent or grandparent unit (two levels seem sufficient).
8884 while Present (Par_Type) loop
8885 if Scope (Par_Type) = Par_Scope
8886 or else Scope (Par_Type) = Scope (Par_Scope)
8887 then
8888 return Par_Type;
8890 elsif not Is_Derived_Type (Par_Type) then
8891 return Empty;
8893 else
8894 Par_Type := Etype (Base_Type (Par_Type));
8895 end if;
8896 end loop;
8898 -- If none found, there is no relevant ancestor type.
8900 return Empty;
8901 end if;
8902 end Get_Incomplete_View_Of_Ancestor;
8904 ----------------------
8905 -- Get_Index_Bounds --
8906 ----------------------
8908 procedure Get_Index_Bounds
8909 (N : Node_Id;
8910 L : out Node_Id;
8911 H : out Node_Id;
8912 Use_Full_View : Boolean := False)
8914 function Scalar_Range_Of_Type (Typ : Entity_Id) return Node_Id;
8915 -- Obtain the scalar range of type Typ. If flag Use_Full_View is set and
8916 -- Typ qualifies, the scalar range is obtained from the full view of the
8917 -- type.
8919 --------------------------
8920 -- Scalar_Range_Of_Type --
8921 --------------------------
8923 function Scalar_Range_Of_Type (Typ : Entity_Id) return Node_Id is
8924 T : Entity_Id := Typ;
8926 begin
8927 if Use_Full_View and then Present (Full_View (T)) then
8928 T := Full_View (T);
8929 end if;
8931 return Scalar_Range (T);
8932 end Scalar_Range_Of_Type;
8934 -- Local variables
8936 Kind : constant Node_Kind := Nkind (N);
8937 Rng : Node_Id;
8939 -- Start of processing for Get_Index_Bounds
8941 begin
8942 if Kind = N_Range then
8943 L := Low_Bound (N);
8944 H := High_Bound (N);
8946 elsif Kind = N_Subtype_Indication then
8947 Rng := Range_Expression (Constraint (N));
8949 if Rng = Error then
8950 L := Error;
8951 H := Error;
8952 return;
8954 else
8955 L := Low_Bound (Range_Expression (Constraint (N)));
8956 H := High_Bound (Range_Expression (Constraint (N)));
8957 end if;
8959 elsif Is_Entity_Name (N) and then Is_Type (Entity (N)) then
8960 Rng := Scalar_Range_Of_Type (Entity (N));
8962 if Error_Posted (Rng) then
8963 L := Error;
8964 H := Error;
8966 elsif Nkind (Rng) = N_Subtype_Indication then
8967 Get_Index_Bounds (Rng, L, H);
8969 else
8970 L := Low_Bound (Rng);
8971 H := High_Bound (Rng);
8972 end if;
8974 else
8975 -- N is an expression, indicating a range with one value
8977 L := N;
8978 H := N;
8979 end if;
8980 end Get_Index_Bounds;
8982 -----------------------------
8983 -- Get_Interfacing_Aspects --
8984 -----------------------------
8986 procedure Get_Interfacing_Aspects
8987 (Iface_Asp : Node_Id;
8988 Conv_Asp : out Node_Id;
8989 EN_Asp : out Node_Id;
8990 Expo_Asp : out Node_Id;
8991 Imp_Asp : out Node_Id;
8992 LN_Asp : out Node_Id;
8993 Do_Checks : Boolean := False)
8995 procedure Save_Or_Duplication_Error
8996 (Asp : Node_Id;
8997 To : in out Node_Id);
8998 -- Save the value of aspect Asp in node To. If To already has a value,
8999 -- then this is considered a duplicate use of aspect. Emit an error if
9000 -- flag Do_Checks is set.
9002 -------------------------------
9003 -- Save_Or_Duplication_Error --
9004 -------------------------------
9006 procedure Save_Or_Duplication_Error
9007 (Asp : Node_Id;
9008 To : in out Node_Id)
9010 begin
9011 -- Detect an extra aspect and issue an error
9013 if Present (To) then
9014 if Do_Checks then
9015 Error_Msg_Name_1 := Chars (Identifier (Asp));
9016 Error_Msg_Sloc := Sloc (To);
9017 Error_Msg_N ("aspect % previously given #", Asp);
9018 end if;
9020 -- Otherwise capture the aspect
9022 else
9023 To := Asp;
9024 end if;
9025 end Save_Or_Duplication_Error;
9027 -- Local variables
9029 Asp : Node_Id;
9030 Asp_Id : Aspect_Id;
9032 -- The following variables capture each individual aspect
9034 Conv : Node_Id := Empty;
9035 EN : Node_Id := Empty;
9036 Expo : Node_Id := Empty;
9037 Imp : Node_Id := Empty;
9038 LN : Node_Id := Empty;
9040 -- Start of processing for Get_Interfacing_Aspects
9042 begin
9043 -- The input interfacing aspect should reside in an aspect specification
9044 -- list.
9046 pragma Assert (Is_List_Member (Iface_Asp));
9048 -- Examine the aspect specifications of the related entity. Find and
9049 -- capture all interfacing aspects. Detect duplicates and emit errors
9050 -- if applicable.
9052 Asp := First (List_Containing (Iface_Asp));
9053 while Present (Asp) loop
9054 Asp_Id := Get_Aspect_Id (Asp);
9056 if Asp_Id = Aspect_Convention then
9057 Save_Or_Duplication_Error (Asp, Conv);
9059 elsif Asp_Id = Aspect_External_Name then
9060 Save_Or_Duplication_Error (Asp, EN);
9062 elsif Asp_Id = Aspect_Export then
9063 Save_Or_Duplication_Error (Asp, Expo);
9065 elsif Asp_Id = Aspect_Import then
9066 Save_Or_Duplication_Error (Asp, Imp);
9068 elsif Asp_Id = Aspect_Link_Name then
9069 Save_Or_Duplication_Error (Asp, LN);
9070 end if;
9072 Next (Asp);
9073 end loop;
9075 Conv_Asp := Conv;
9076 EN_Asp := EN;
9077 Expo_Asp := Expo;
9078 Imp_Asp := Imp;
9079 LN_Asp := LN;
9080 end Get_Interfacing_Aspects;
9082 ---------------------------------
9083 -- Get_Iterable_Type_Primitive --
9084 ---------------------------------
9086 function Get_Iterable_Type_Primitive
9087 (Typ : Entity_Id;
9088 Nam : Name_Id) return Entity_Id
9090 Funcs : constant Node_Id := Find_Value_Of_Aspect (Typ, Aspect_Iterable);
9091 Assoc : Node_Id;
9093 begin
9094 if No (Funcs) then
9095 return Empty;
9097 else
9098 Assoc := First (Component_Associations (Funcs));
9099 while Present (Assoc) loop
9100 if Chars (First (Choices (Assoc))) = Nam then
9101 return Entity (Expression (Assoc));
9102 end if;
9104 Assoc := Next (Assoc);
9105 end loop;
9107 return Empty;
9108 end if;
9109 end Get_Iterable_Type_Primitive;
9111 ----------------------------------
9112 -- Get_Library_Unit_Name_string --
9113 ----------------------------------
9115 procedure Get_Library_Unit_Name_String (Decl_Node : Node_Id) is
9116 Unit_Name_Id : constant Unit_Name_Type := Get_Unit_Name (Decl_Node);
9118 begin
9119 Get_Unit_Name_String (Unit_Name_Id);
9121 -- Remove seven last character (" (spec)" or " (body)")
9123 Name_Len := Name_Len - 7;
9124 pragma Assert (Name_Buffer (Name_Len + 1) = ' ');
9125 end Get_Library_Unit_Name_String;
9127 --------------------------
9128 -- Get_Max_Queue_Length --
9129 --------------------------
9131 function Get_Max_Queue_Length (Id : Entity_Id) return Uint is
9132 pragma Assert (Is_Entry (Id));
9133 Prag : constant Entity_Id := Get_Pragma (Id, Pragma_Max_Queue_Length);
9135 begin
9136 -- A value of 0 represents no maximum specified, and entries and entry
9137 -- families with no Max_Queue_Length aspect or pragma default to it.
9139 if not Present (Prag) then
9140 return Uint_0;
9141 end if;
9143 return Intval (Expression (First (Pragma_Argument_Associations (Prag))));
9144 end Get_Max_Queue_Length;
9146 ------------------------
9147 -- Get_Name_Entity_Id --
9148 ------------------------
9150 function Get_Name_Entity_Id (Id : Name_Id) return Entity_Id is
9151 begin
9152 return Entity_Id (Get_Name_Table_Int (Id));
9153 end Get_Name_Entity_Id;
9155 ------------------------------
9156 -- Get_Name_From_CTC_Pragma --
9157 ------------------------------
9159 function Get_Name_From_CTC_Pragma (N : Node_Id) return String_Id is
9160 Arg : constant Node_Id :=
9161 Get_Pragma_Arg (First (Pragma_Argument_Associations (N)));
9162 begin
9163 return Strval (Expr_Value_S (Arg));
9164 end Get_Name_From_CTC_Pragma;
9166 -----------------------
9167 -- Get_Parent_Entity --
9168 -----------------------
9170 function Get_Parent_Entity (Unit : Node_Id) return Entity_Id is
9171 begin
9172 if Nkind (Unit) = N_Package_Body
9173 and then Nkind (Original_Node (Unit)) = N_Package_Instantiation
9174 then
9175 return Defining_Entity
9176 (Specification (Instance_Spec (Original_Node (Unit))));
9177 elsif Nkind (Unit) = N_Package_Instantiation then
9178 return Defining_Entity (Specification (Instance_Spec (Unit)));
9179 else
9180 return Defining_Entity (Unit);
9181 end if;
9182 end Get_Parent_Entity;
9184 -------------------
9185 -- Get_Pragma_Id --
9186 -------------------
9188 function Get_Pragma_Id (N : Node_Id) return Pragma_Id is
9189 begin
9190 return Get_Pragma_Id (Pragma_Name_Unmapped (N));
9191 end Get_Pragma_Id;
9193 ------------------------
9194 -- Get_Qualified_Name --
9195 ------------------------
9197 function Get_Qualified_Name
9198 (Id : Entity_Id;
9199 Suffix : Entity_Id := Empty) return Name_Id
9201 Suffix_Nam : Name_Id := No_Name;
9203 begin
9204 if Present (Suffix) then
9205 Suffix_Nam := Chars (Suffix);
9206 end if;
9208 return Get_Qualified_Name (Chars (Id), Suffix_Nam, Scope (Id));
9209 end Get_Qualified_Name;
9211 function Get_Qualified_Name
9212 (Nam : Name_Id;
9213 Suffix : Name_Id := No_Name;
9214 Scop : Entity_Id := Current_Scope) return Name_Id
9216 procedure Add_Scope (S : Entity_Id);
9217 -- Add the fully qualified form of scope S to the name buffer. The
9218 -- format is:
9219 -- s-1__s__
9221 ---------------
9222 -- Add_Scope --
9223 ---------------
9225 procedure Add_Scope (S : Entity_Id) is
9226 begin
9227 if S = Empty then
9228 null;
9230 elsif S = Standard_Standard then
9231 null;
9233 else
9234 Add_Scope (Scope (S));
9235 Get_Name_String_And_Append (Chars (S));
9236 Add_Str_To_Name_Buffer ("__");
9237 end if;
9238 end Add_Scope;
9240 -- Start of processing for Get_Qualified_Name
9242 begin
9243 Name_Len := 0;
9244 Add_Scope (Scop);
9246 -- Append the base name after all scopes have been chained
9248 Get_Name_String_And_Append (Nam);
9250 -- Append the suffix (if present)
9252 if Suffix /= No_Name then
9253 Add_Str_To_Name_Buffer ("__");
9254 Get_Name_String_And_Append (Suffix);
9255 end if;
9257 return Name_Find;
9258 end Get_Qualified_Name;
9260 -----------------------
9261 -- Get_Reason_String --
9262 -----------------------
9264 procedure Get_Reason_String (N : Node_Id) is
9265 begin
9266 if Nkind (N) = N_String_Literal then
9267 Store_String_Chars (Strval (N));
9269 elsif Nkind (N) = N_Op_Concat then
9270 Get_Reason_String (Left_Opnd (N));
9271 Get_Reason_String (Right_Opnd (N));
9273 -- If not of required form, error
9275 else
9276 Error_Msg_N
9277 ("Reason for pragma Warnings has wrong form", N);
9278 Error_Msg_N
9279 ("\must be string literal or concatenation of string literals", N);
9280 return;
9281 end if;
9282 end Get_Reason_String;
9284 --------------------------------
9285 -- Get_Reference_Discriminant --
9286 --------------------------------
9288 function Get_Reference_Discriminant (Typ : Entity_Id) return Entity_Id is
9289 D : Entity_Id;
9291 begin
9292 D := First_Discriminant (Typ);
9293 while Present (D) loop
9294 if Has_Implicit_Dereference (D) then
9295 return D;
9296 end if;
9297 Next_Discriminant (D);
9298 end loop;
9300 return Empty;
9301 end Get_Reference_Discriminant;
9303 ---------------------------
9304 -- Get_Referenced_Object --
9305 ---------------------------
9307 function Get_Referenced_Object (N : Node_Id) return Node_Id is
9308 R : Node_Id;
9310 begin
9311 R := N;
9312 while Is_Entity_Name (R)
9313 and then Present (Renamed_Object (Entity (R)))
9314 loop
9315 R := Renamed_Object (Entity (R));
9316 end loop;
9318 return R;
9319 end Get_Referenced_Object;
9321 ------------------------
9322 -- Get_Renamed_Entity --
9323 ------------------------
9325 function Get_Renamed_Entity (E : Entity_Id) return Entity_Id is
9326 R : Entity_Id;
9328 begin
9329 R := E;
9330 while Present (Renamed_Entity (R)) loop
9331 R := Renamed_Entity (R);
9332 end loop;
9334 return R;
9335 end Get_Renamed_Entity;
9337 -----------------------
9338 -- Get_Return_Object --
9339 -----------------------
9341 function Get_Return_Object (N : Node_Id) return Entity_Id is
9342 Decl : Node_Id;
9344 begin
9345 Decl := First (Return_Object_Declarations (N));
9346 while Present (Decl) loop
9347 exit when Nkind (Decl) = N_Object_Declaration
9348 and then Is_Return_Object (Defining_Identifier (Decl));
9349 Next (Decl);
9350 end loop;
9352 pragma Assert (Present (Decl));
9353 return Defining_Identifier (Decl);
9354 end Get_Return_Object;
9356 ---------------------------
9357 -- Get_Subprogram_Entity --
9358 ---------------------------
9360 function Get_Subprogram_Entity (Nod : Node_Id) return Entity_Id is
9361 Subp : Node_Id;
9362 Subp_Id : Entity_Id;
9364 begin
9365 if Nkind (Nod) = N_Accept_Statement then
9366 Subp := Entry_Direct_Name (Nod);
9368 elsif Nkind (Nod) = N_Slice then
9369 Subp := Prefix (Nod);
9371 else
9372 Subp := Name (Nod);
9373 end if;
9375 -- Strip the subprogram call
9377 loop
9378 if Nkind_In (Subp, N_Explicit_Dereference,
9379 N_Indexed_Component,
9380 N_Selected_Component)
9381 then
9382 Subp := Prefix (Subp);
9384 elsif Nkind_In (Subp, N_Type_Conversion,
9385 N_Unchecked_Type_Conversion)
9386 then
9387 Subp := Expression (Subp);
9389 else
9390 exit;
9391 end if;
9392 end loop;
9394 -- Extract the entity of the subprogram call
9396 if Is_Entity_Name (Subp) then
9397 Subp_Id := Entity (Subp);
9399 if Ekind (Subp_Id) = E_Access_Subprogram_Type then
9400 Subp_Id := Directly_Designated_Type (Subp_Id);
9401 end if;
9403 if Is_Subprogram (Subp_Id) then
9404 return Subp_Id;
9405 else
9406 return Empty;
9407 end if;
9409 -- The search did not find a construct that denotes a subprogram
9411 else
9412 return Empty;
9413 end if;
9414 end Get_Subprogram_Entity;
9416 -----------------------------
9417 -- Get_Task_Body_Procedure --
9418 -----------------------------
9420 function Get_Task_Body_Procedure (E : Entity_Id) return Node_Id is
9421 begin
9422 -- Note: A task type may be the completion of a private type with
9423 -- discriminants. When performing elaboration checks on a task
9424 -- declaration, the current view of the type may be the private one,
9425 -- and the procedure that holds the body of the task is held in its
9426 -- underlying type.
9428 -- This is an odd function, why not have Task_Body_Procedure do
9429 -- the following digging???
9431 return Task_Body_Procedure (Underlying_Type (Root_Type (E)));
9432 end Get_Task_Body_Procedure;
9434 -------------------------
9435 -- Get_User_Defined_Eq --
9436 -------------------------
9438 function Get_User_Defined_Eq (E : Entity_Id) return Entity_Id is
9439 Prim : Elmt_Id;
9440 Op : Entity_Id;
9442 begin
9443 Prim := First_Elmt (Collect_Primitive_Operations (E));
9444 while Present (Prim) loop
9445 Op := Node (Prim);
9447 if Chars (Op) = Name_Op_Eq
9448 and then Etype (Op) = Standard_Boolean
9449 and then Etype (First_Formal (Op)) = E
9450 and then Etype (Next_Formal (First_Formal (Op))) = E
9451 then
9452 return Op;
9453 end if;
9455 Next_Elmt (Prim);
9456 end loop;
9458 return Empty;
9459 end Get_User_Defined_Eq;
9461 ---------------
9462 -- Get_Views --
9463 ---------------
9465 procedure Get_Views
9466 (Typ : Entity_Id;
9467 Priv_Typ : out Entity_Id;
9468 Full_Typ : out Entity_Id;
9469 Full_Base : out Entity_Id;
9470 CRec_Typ : out Entity_Id)
9472 IP_View : Entity_Id;
9474 begin
9475 -- Assume that none of the views can be recovered
9477 Priv_Typ := Empty;
9478 Full_Typ := Empty;
9479 Full_Base := Empty;
9480 CRec_Typ := Empty;
9482 -- The input type is the corresponding record type of a protected or a
9483 -- task type.
9485 if Ekind (Typ) = E_Record_Type
9486 and then Is_Concurrent_Record_Type (Typ)
9487 then
9488 CRec_Typ := Typ;
9489 Full_Typ := Corresponding_Concurrent_Type (CRec_Typ);
9490 Full_Base := Base_Type (Full_Typ);
9491 Priv_Typ := Incomplete_Or_Partial_View (Full_Typ);
9493 -- Otherwise the input type denotes an arbitrary type
9495 else
9496 IP_View := Incomplete_Or_Partial_View (Typ);
9498 -- The input type denotes the full view of a private type
9500 if Present (IP_View) then
9501 Priv_Typ := IP_View;
9502 Full_Typ := Typ;
9504 -- The input type is a private type
9506 elsif Is_Private_Type (Typ) then
9507 Priv_Typ := Typ;
9508 Full_Typ := Full_View (Priv_Typ);
9510 -- Otherwise the input type does not have any views
9512 else
9513 Full_Typ := Typ;
9514 end if;
9516 if Present (Full_Typ) then
9517 Full_Base := Base_Type (Full_Typ);
9519 if Ekind_In (Full_Typ, E_Protected_Type, E_Task_Type) then
9520 CRec_Typ := Corresponding_Record_Type (Full_Typ);
9521 end if;
9522 end if;
9523 end if;
9524 end Get_Views;
9526 -----------------------
9527 -- Has_Access_Values --
9528 -----------------------
9530 function Has_Access_Values (T : Entity_Id) return Boolean is
9531 Typ : constant Entity_Id := Underlying_Type (T);
9533 begin
9534 -- Case of a private type which is not completed yet. This can only
9535 -- happen in the case of a generic format type appearing directly, or
9536 -- as a component of the type to which this function is being applied
9537 -- at the top level. Return False in this case, since we certainly do
9538 -- not know that the type contains access types.
9540 if No (Typ) then
9541 return False;
9543 elsif Is_Access_Type (Typ) then
9544 return True;
9546 elsif Is_Array_Type (Typ) then
9547 return Has_Access_Values (Component_Type (Typ));
9549 elsif Is_Record_Type (Typ) then
9550 declare
9551 Comp : Entity_Id;
9553 begin
9554 -- Loop to Check components
9556 Comp := First_Component_Or_Discriminant (Typ);
9557 while Present (Comp) loop
9559 -- Check for access component, tag field does not count, even
9560 -- though it is implemented internally using an access type.
9562 if Has_Access_Values (Etype (Comp))
9563 and then Chars (Comp) /= Name_uTag
9564 then
9565 return True;
9566 end if;
9568 Next_Component_Or_Discriminant (Comp);
9569 end loop;
9570 end;
9572 return False;
9574 else
9575 return False;
9576 end if;
9577 end Has_Access_Values;
9579 ------------------------------
9580 -- Has_Compatible_Alignment --
9581 ------------------------------
9583 function Has_Compatible_Alignment
9584 (Obj : Entity_Id;
9585 Expr : Node_Id;
9586 Layout_Done : Boolean) return Alignment_Result
9588 function Has_Compatible_Alignment_Internal
9589 (Obj : Entity_Id;
9590 Expr : Node_Id;
9591 Layout_Done : Boolean;
9592 Default : Alignment_Result) return Alignment_Result;
9593 -- This is the internal recursive function that actually does the work.
9594 -- There is one additional parameter, which says what the result should
9595 -- be if no alignment information is found, and there is no definite
9596 -- indication of compatible alignments. At the outer level, this is set
9597 -- to Unknown, but for internal recursive calls in the case where types
9598 -- are known to be correct, it is set to Known_Compatible.
9600 ---------------------------------------
9601 -- Has_Compatible_Alignment_Internal --
9602 ---------------------------------------
9604 function Has_Compatible_Alignment_Internal
9605 (Obj : Entity_Id;
9606 Expr : Node_Id;
9607 Layout_Done : Boolean;
9608 Default : Alignment_Result) return Alignment_Result
9610 Result : Alignment_Result := Known_Compatible;
9611 -- Holds the current status of the result. Note that once a value of
9612 -- Known_Incompatible is set, it is sticky and does not get changed
9613 -- to Unknown (the value in Result only gets worse as we go along,
9614 -- never better).
9616 Offs : Uint := No_Uint;
9617 -- Set to a factor of the offset from the base object when Expr is a
9618 -- selected or indexed component, based on Component_Bit_Offset and
9619 -- Component_Size respectively. A negative value is used to represent
9620 -- a value which is not known at compile time.
9622 procedure Check_Prefix;
9623 -- Checks the prefix recursively in the case where the expression
9624 -- is an indexed or selected component.
9626 procedure Set_Result (R : Alignment_Result);
9627 -- If R represents a worse outcome (unknown instead of known
9628 -- compatible, or known incompatible), then set Result to R.
9630 ------------------
9631 -- Check_Prefix --
9632 ------------------
9634 procedure Check_Prefix is
9635 begin
9636 -- The subtlety here is that in doing a recursive call to check
9637 -- the prefix, we have to decide what to do in the case where we
9638 -- don't find any specific indication of an alignment problem.
9640 -- At the outer level, we normally set Unknown as the result in
9641 -- this case, since we can only set Known_Compatible if we really
9642 -- know that the alignment value is OK, but for the recursive
9643 -- call, in the case where the types match, and we have not
9644 -- specified a peculiar alignment for the object, we are only
9645 -- concerned about suspicious rep clauses, the default case does
9646 -- not affect us, since the compiler will, in the absence of such
9647 -- rep clauses, ensure that the alignment is correct.
9649 if Default = Known_Compatible
9650 or else
9651 (Etype (Obj) = Etype (Expr)
9652 and then (Unknown_Alignment (Obj)
9653 or else
9654 Alignment (Obj) = Alignment (Etype (Obj))))
9655 then
9656 Set_Result
9657 (Has_Compatible_Alignment_Internal
9658 (Obj, Prefix (Expr), Layout_Done, Known_Compatible));
9660 -- In all other cases, we need a full check on the prefix
9662 else
9663 Set_Result
9664 (Has_Compatible_Alignment_Internal
9665 (Obj, Prefix (Expr), Layout_Done, Unknown));
9666 end if;
9667 end Check_Prefix;
9669 ----------------
9670 -- Set_Result --
9671 ----------------
9673 procedure Set_Result (R : Alignment_Result) is
9674 begin
9675 if R > Result then
9676 Result := R;
9677 end if;
9678 end Set_Result;
9680 -- Start of processing for Has_Compatible_Alignment_Internal
9682 begin
9683 -- If Expr is a selected component, we must make sure there is no
9684 -- potentially troublesome component clause and that the record is
9685 -- not packed if the layout is not done.
9687 if Nkind (Expr) = N_Selected_Component then
9689 -- Packing generates unknown alignment if layout is not done
9691 if Is_Packed (Etype (Prefix (Expr))) and then not Layout_Done then
9692 Set_Result (Unknown);
9693 end if;
9695 -- Check prefix and component offset
9697 Check_Prefix;
9698 Offs := Component_Bit_Offset (Entity (Selector_Name (Expr)));
9700 -- If Expr is an indexed component, we must make sure there is no
9701 -- potentially troublesome Component_Size clause and that the array
9702 -- is not bit-packed if the layout is not done.
9704 elsif Nkind (Expr) = N_Indexed_Component then
9705 declare
9706 Typ : constant Entity_Id := Etype (Prefix (Expr));
9708 begin
9709 -- Packing generates unknown alignment if layout is not done
9711 if Is_Bit_Packed_Array (Typ) and then not Layout_Done then
9712 Set_Result (Unknown);
9713 end if;
9715 -- Check prefix and component offset (or at least size)
9717 Check_Prefix;
9718 Offs := Indexed_Component_Bit_Offset (Expr);
9719 if Offs = No_Uint then
9720 Offs := Component_Size (Typ);
9721 end if;
9722 end;
9723 end if;
9725 -- If we have a null offset, the result is entirely determined by
9726 -- the base object and has already been computed recursively.
9728 if Offs = Uint_0 then
9729 null;
9731 -- Case where we know the alignment of the object
9733 elsif Known_Alignment (Obj) then
9734 declare
9735 ObjA : constant Uint := Alignment (Obj);
9736 ExpA : Uint := No_Uint;
9737 SizA : Uint := No_Uint;
9739 begin
9740 -- If alignment of Obj is 1, then we are always OK
9742 if ObjA = 1 then
9743 Set_Result (Known_Compatible);
9745 -- Alignment of Obj is greater than 1, so we need to check
9747 else
9748 -- If we have an offset, see if it is compatible
9750 if Offs /= No_Uint and Offs > Uint_0 then
9751 if Offs mod (System_Storage_Unit * ObjA) /= 0 then
9752 Set_Result (Known_Incompatible);
9753 end if;
9755 -- See if Expr is an object with known alignment
9757 elsif Is_Entity_Name (Expr)
9758 and then Known_Alignment (Entity (Expr))
9759 then
9760 ExpA := Alignment (Entity (Expr));
9762 -- Otherwise, we can use the alignment of the type of
9763 -- Expr given that we already checked for
9764 -- discombobulating rep clauses for the cases of indexed
9765 -- and selected components above.
9767 elsif Known_Alignment (Etype (Expr)) then
9768 ExpA := Alignment (Etype (Expr));
9770 -- Otherwise the alignment is unknown
9772 else
9773 Set_Result (Default);
9774 end if;
9776 -- If we got an alignment, see if it is acceptable
9778 if ExpA /= No_Uint and then ExpA < ObjA then
9779 Set_Result (Known_Incompatible);
9780 end if;
9782 -- If Expr is not a piece of a larger object, see if size
9783 -- is given. If so, check that it is not too small for the
9784 -- required alignment.
9786 if Offs /= No_Uint then
9787 null;
9789 -- See if Expr is an object with known size
9791 elsif Is_Entity_Name (Expr)
9792 and then Known_Static_Esize (Entity (Expr))
9793 then
9794 SizA := Esize (Entity (Expr));
9796 -- Otherwise, we check the object size of the Expr type
9798 elsif Known_Static_Esize (Etype (Expr)) then
9799 SizA := Esize (Etype (Expr));
9800 end if;
9802 -- If we got a size, see if it is a multiple of the Obj
9803 -- alignment, if not, then the alignment cannot be
9804 -- acceptable, since the size is always a multiple of the
9805 -- alignment.
9807 if SizA /= No_Uint then
9808 if SizA mod (ObjA * Ttypes.System_Storage_Unit) /= 0 then
9809 Set_Result (Known_Incompatible);
9810 end if;
9811 end if;
9812 end if;
9813 end;
9815 -- If we do not know required alignment, any non-zero offset is a
9816 -- potential problem (but certainly may be OK, so result is unknown).
9818 elsif Offs /= No_Uint then
9819 Set_Result (Unknown);
9821 -- If we can't find the result by direct comparison of alignment
9822 -- values, then there is still one case that we can determine known
9823 -- result, and that is when we can determine that the types are the
9824 -- same, and no alignments are specified. Then we known that the
9825 -- alignments are compatible, even if we don't know the alignment
9826 -- value in the front end.
9828 elsif Etype (Obj) = Etype (Expr) then
9830 -- Types are the same, but we have to check for possible size
9831 -- and alignments on the Expr object that may make the alignment
9832 -- different, even though the types are the same.
9834 if Is_Entity_Name (Expr) then
9836 -- First check alignment of the Expr object. Any alignment less
9837 -- than Maximum_Alignment is worrisome since this is the case
9838 -- where we do not know the alignment of Obj.
9840 if Known_Alignment (Entity (Expr))
9841 and then UI_To_Int (Alignment (Entity (Expr))) <
9842 Ttypes.Maximum_Alignment
9843 then
9844 Set_Result (Unknown);
9846 -- Now check size of Expr object. Any size that is not an
9847 -- even multiple of Maximum_Alignment is also worrisome
9848 -- since it may cause the alignment of the object to be less
9849 -- than the alignment of the type.
9851 elsif Known_Static_Esize (Entity (Expr))
9852 and then
9853 (UI_To_Int (Esize (Entity (Expr))) mod
9854 (Ttypes.Maximum_Alignment * Ttypes.System_Storage_Unit))
9855 /= 0
9856 then
9857 Set_Result (Unknown);
9859 -- Otherwise same type is decisive
9861 else
9862 Set_Result (Known_Compatible);
9863 end if;
9864 end if;
9866 -- Another case to deal with is when there is an explicit size or
9867 -- alignment clause when the types are not the same. If so, then the
9868 -- result is Unknown. We don't need to do this test if the Default is
9869 -- Unknown, since that result will be set in any case.
9871 elsif Default /= Unknown
9872 and then (Has_Size_Clause (Etype (Expr))
9873 or else
9874 Has_Alignment_Clause (Etype (Expr)))
9875 then
9876 Set_Result (Unknown);
9878 -- If no indication found, set default
9880 else
9881 Set_Result (Default);
9882 end if;
9884 -- Return worst result found
9886 return Result;
9887 end Has_Compatible_Alignment_Internal;
9889 -- Start of processing for Has_Compatible_Alignment
9891 begin
9892 -- If Obj has no specified alignment, then set alignment from the type
9893 -- alignment. Perhaps we should always do this, but for sure we should
9894 -- do it when there is an address clause since we can do more if the
9895 -- alignment is known.
9897 if Unknown_Alignment (Obj) then
9898 Set_Alignment (Obj, Alignment (Etype (Obj)));
9899 end if;
9901 -- Now do the internal call that does all the work
9903 return
9904 Has_Compatible_Alignment_Internal (Obj, Expr, Layout_Done, Unknown);
9905 end Has_Compatible_Alignment;
9907 ----------------------
9908 -- Has_Declarations --
9909 ----------------------
9911 function Has_Declarations (N : Node_Id) return Boolean is
9912 begin
9913 return Nkind_In (Nkind (N), N_Accept_Statement,
9914 N_Block_Statement,
9915 N_Compilation_Unit_Aux,
9916 N_Entry_Body,
9917 N_Package_Body,
9918 N_Protected_Body,
9919 N_Subprogram_Body,
9920 N_Task_Body,
9921 N_Package_Specification);
9922 end Has_Declarations;
9924 ---------------------------------
9925 -- Has_Defaulted_Discriminants --
9926 ---------------------------------
9928 function Has_Defaulted_Discriminants (Typ : Entity_Id) return Boolean is
9929 begin
9930 return Has_Discriminants (Typ)
9931 and then Present (First_Discriminant (Typ))
9932 and then Present (Discriminant_Default_Value
9933 (First_Discriminant (Typ)));
9934 end Has_Defaulted_Discriminants;
9936 -------------------
9937 -- Has_Denormals --
9938 -------------------
9940 function Has_Denormals (E : Entity_Id) return Boolean is
9941 begin
9942 return Is_Floating_Point_Type (E) and then Denorm_On_Target;
9943 end Has_Denormals;
9945 -------------------------------------------
9946 -- Has_Discriminant_Dependent_Constraint --
9947 -------------------------------------------
9949 function Has_Discriminant_Dependent_Constraint
9950 (Comp : Entity_Id) return Boolean
9952 Comp_Decl : constant Node_Id := Parent (Comp);
9953 Subt_Indic : Node_Id;
9954 Constr : Node_Id;
9955 Assn : Node_Id;
9957 begin
9958 -- Discriminants can't depend on discriminants
9960 if Ekind (Comp) = E_Discriminant then
9961 return False;
9963 else
9964 Subt_Indic := Subtype_Indication (Component_Definition (Comp_Decl));
9966 if Nkind (Subt_Indic) = N_Subtype_Indication then
9967 Constr := Constraint (Subt_Indic);
9969 if Nkind (Constr) = N_Index_Or_Discriminant_Constraint then
9970 Assn := First (Constraints (Constr));
9971 while Present (Assn) loop
9972 case Nkind (Assn) is
9973 when N_Identifier
9974 | N_Range
9975 | N_Subtype_Indication
9977 if Depends_On_Discriminant (Assn) then
9978 return True;
9979 end if;
9981 when N_Discriminant_Association =>
9982 if Depends_On_Discriminant (Expression (Assn)) then
9983 return True;
9984 end if;
9986 when others =>
9987 null;
9988 end case;
9990 Next (Assn);
9991 end loop;
9992 end if;
9993 end if;
9994 end if;
9996 return False;
9997 end Has_Discriminant_Dependent_Constraint;
9999 --------------------------------------
10000 -- Has_Effectively_Volatile_Profile --
10001 --------------------------------------
10003 function Has_Effectively_Volatile_Profile
10004 (Subp_Id : Entity_Id) return Boolean
10006 Formal : Entity_Id;
10008 begin
10009 -- Inspect the formal parameters looking for an effectively volatile
10010 -- type.
10012 Formal := First_Formal (Subp_Id);
10013 while Present (Formal) loop
10014 if Is_Effectively_Volatile (Etype (Formal)) then
10015 return True;
10016 end if;
10018 Next_Formal (Formal);
10019 end loop;
10021 -- Inspect the return type of functions
10023 if Ekind_In (Subp_Id, E_Function, E_Generic_Function)
10024 and then Is_Effectively_Volatile (Etype (Subp_Id))
10025 then
10026 return True;
10027 end if;
10029 return False;
10030 end Has_Effectively_Volatile_Profile;
10032 --------------------------
10033 -- Has_Enabled_Property --
10034 --------------------------
10036 function Has_Enabled_Property
10037 (Item_Id : Entity_Id;
10038 Property : Name_Id) return Boolean
10040 function Protected_Object_Has_Enabled_Property return Boolean;
10041 -- Determine whether a protected object denoted by Item_Id has the
10042 -- property enabled.
10044 function State_Has_Enabled_Property return Boolean;
10045 -- Determine whether a state denoted by Item_Id has the property enabled
10047 function Variable_Has_Enabled_Property return Boolean;
10048 -- Determine whether a variable denoted by Item_Id has the property
10049 -- enabled.
10051 -------------------------------------------
10052 -- Protected_Object_Has_Enabled_Property --
10053 -------------------------------------------
10055 function Protected_Object_Has_Enabled_Property return Boolean is
10056 Constits : constant Elist_Id := Part_Of_Constituents (Item_Id);
10057 Constit_Elmt : Elmt_Id;
10058 Constit_Id : Entity_Id;
10060 begin
10061 -- Protected objects always have the properties Async_Readers and
10062 -- Async_Writers (SPARK RM 7.1.2(16)).
10064 if Property = Name_Async_Readers
10065 or else Property = Name_Async_Writers
10066 then
10067 return True;
10069 -- Protected objects that have Part_Of components also inherit their
10070 -- properties Effective_Reads and Effective_Writes
10071 -- (SPARK RM 7.1.2(16)).
10073 elsif Present (Constits) then
10074 Constit_Elmt := First_Elmt (Constits);
10075 while Present (Constit_Elmt) loop
10076 Constit_Id := Node (Constit_Elmt);
10078 if Has_Enabled_Property (Constit_Id, Property) then
10079 return True;
10080 end if;
10082 Next_Elmt (Constit_Elmt);
10083 end loop;
10084 end if;
10086 return False;
10087 end Protected_Object_Has_Enabled_Property;
10089 --------------------------------
10090 -- State_Has_Enabled_Property --
10091 --------------------------------
10093 function State_Has_Enabled_Property return Boolean is
10094 Decl : constant Node_Id := Parent (Item_Id);
10095 Opt : Node_Id;
10096 Opt_Nam : Node_Id;
10097 Prop : Node_Id;
10098 Prop_Nam : Node_Id;
10099 Props : Node_Id;
10101 begin
10102 -- The declaration of an external abstract state appears as an
10103 -- extension aggregate. If this is not the case, properties can never
10104 -- be set.
10106 if Nkind (Decl) /= N_Extension_Aggregate then
10107 return False;
10108 end if;
10110 -- When External appears as a simple option, it automatically enables
10111 -- all properties.
10113 Opt := First (Expressions (Decl));
10114 while Present (Opt) loop
10115 if Nkind (Opt) = N_Identifier
10116 and then Chars (Opt) = Name_External
10117 then
10118 return True;
10119 end if;
10121 Next (Opt);
10122 end loop;
10124 -- When External specifies particular properties, inspect those and
10125 -- find the desired one (if any).
10127 Opt := First (Component_Associations (Decl));
10128 while Present (Opt) loop
10129 Opt_Nam := First (Choices (Opt));
10131 if Nkind (Opt_Nam) = N_Identifier
10132 and then Chars (Opt_Nam) = Name_External
10133 then
10134 Props := Expression (Opt);
10136 -- Multiple properties appear as an aggregate
10138 if Nkind (Props) = N_Aggregate then
10140 -- Simple property form
10142 Prop := First (Expressions (Props));
10143 while Present (Prop) loop
10144 if Chars (Prop) = Property then
10145 return True;
10146 end if;
10148 Next (Prop);
10149 end loop;
10151 -- Property with expression form
10153 Prop := First (Component_Associations (Props));
10154 while Present (Prop) loop
10155 Prop_Nam := First (Choices (Prop));
10157 -- The property can be represented in two ways:
10158 -- others => <value>
10159 -- <property> => <value>
10161 if Nkind (Prop_Nam) = N_Others_Choice
10162 or else (Nkind (Prop_Nam) = N_Identifier
10163 and then Chars (Prop_Nam) = Property)
10164 then
10165 return Is_True (Expr_Value (Expression (Prop)));
10166 end if;
10168 Next (Prop);
10169 end loop;
10171 -- Single property
10173 else
10174 return Chars (Props) = Property;
10175 end if;
10176 end if;
10178 Next (Opt);
10179 end loop;
10181 return False;
10182 end State_Has_Enabled_Property;
10184 -----------------------------------
10185 -- Variable_Has_Enabled_Property --
10186 -----------------------------------
10188 function Variable_Has_Enabled_Property return Boolean is
10189 function Is_Enabled (Prag : Node_Id) return Boolean;
10190 -- Determine whether property pragma Prag (if present) denotes an
10191 -- enabled property.
10193 ----------------
10194 -- Is_Enabled --
10195 ----------------
10197 function Is_Enabled (Prag : Node_Id) return Boolean is
10198 Arg1 : Node_Id;
10200 begin
10201 if Present (Prag) then
10202 Arg1 := First (Pragma_Argument_Associations (Prag));
10204 -- The pragma has an optional Boolean expression, the related
10205 -- property is enabled only when the expression evaluates to
10206 -- True.
10208 if Present (Arg1) then
10209 return Is_True (Expr_Value (Get_Pragma_Arg (Arg1)));
10211 -- Otherwise the lack of expression enables the property by
10212 -- default.
10214 else
10215 return True;
10216 end if;
10218 -- The property was never set in the first place
10220 else
10221 return False;
10222 end if;
10223 end Is_Enabled;
10225 -- Local variables
10227 AR : constant Node_Id :=
10228 Get_Pragma (Item_Id, Pragma_Async_Readers);
10229 AW : constant Node_Id :=
10230 Get_Pragma (Item_Id, Pragma_Async_Writers);
10231 ER : constant Node_Id :=
10232 Get_Pragma (Item_Id, Pragma_Effective_Reads);
10233 EW : constant Node_Id :=
10234 Get_Pragma (Item_Id, Pragma_Effective_Writes);
10236 -- Start of processing for Variable_Has_Enabled_Property
10238 begin
10239 -- A non-effectively volatile object can never possess external
10240 -- properties.
10242 if not Is_Effectively_Volatile (Item_Id) then
10243 return False;
10245 -- External properties related to variables come in two flavors -
10246 -- explicit and implicit. The explicit case is characterized by the
10247 -- presence of a property pragma with an optional Boolean flag. The
10248 -- property is enabled when the flag evaluates to True or the flag is
10249 -- missing altogether.
10251 elsif Property = Name_Async_Readers and then Is_Enabled (AR) then
10252 return True;
10254 elsif Property = Name_Async_Writers and then Is_Enabled (AW) then
10255 return True;
10257 elsif Property = Name_Effective_Reads and then Is_Enabled (ER) then
10258 return True;
10260 elsif Property = Name_Effective_Writes and then Is_Enabled (EW) then
10261 return True;
10263 -- The implicit case lacks all property pragmas
10265 elsif No (AR) and then No (AW) and then No (ER) and then No (EW) then
10266 if Is_Protected_Type (Etype (Item_Id)) then
10267 return Protected_Object_Has_Enabled_Property;
10268 else
10269 return True;
10270 end if;
10272 else
10273 return False;
10274 end if;
10275 end Variable_Has_Enabled_Property;
10277 -- Start of processing for Has_Enabled_Property
10279 begin
10280 -- Abstract states and variables have a flexible scheme of specifying
10281 -- external properties.
10283 if Ekind (Item_Id) = E_Abstract_State then
10284 return State_Has_Enabled_Property;
10286 elsif Ekind (Item_Id) = E_Variable then
10287 return Variable_Has_Enabled_Property;
10289 -- By default, protected objects only have the properties Async_Readers
10290 -- and Async_Writers. If they have Part_Of components, they also inherit
10291 -- their properties Effective_Reads and Effective_Writes
10292 -- (SPARK RM 7.1.2(16)).
10294 elsif Ekind (Item_Id) = E_Protected_Object then
10295 return Protected_Object_Has_Enabled_Property;
10297 -- Otherwise a property is enabled when the related item is effectively
10298 -- volatile.
10300 else
10301 return Is_Effectively_Volatile (Item_Id);
10302 end if;
10303 end Has_Enabled_Property;
10305 -------------------------------------
10306 -- Has_Full_Default_Initialization --
10307 -------------------------------------
10309 function Has_Full_Default_Initialization (Typ : Entity_Id) return Boolean is
10310 Comp : Entity_Id;
10311 Prag : Node_Id;
10313 begin
10314 -- A type subject to pragma Default_Initial_Condition is fully default
10315 -- initialized when the pragma appears with a non-null argument. Since
10316 -- any type may act as the full view of a private type, this check must
10317 -- be performed prior to the specialized tests below.
10319 if Has_DIC (Typ) then
10320 Prag := Get_Pragma (Typ, Pragma_Default_Initial_Condition);
10321 pragma Assert (Present (Prag));
10323 return Is_Verifiable_DIC_Pragma (Prag);
10324 end if;
10326 -- A scalar type is fully default initialized if it is subject to aspect
10327 -- Default_Value.
10329 if Is_Scalar_Type (Typ) then
10330 return Has_Default_Aspect (Typ);
10332 -- An array type is fully default initialized if its element type is
10333 -- scalar and the array type carries aspect Default_Component_Value or
10334 -- the element type is fully default initialized.
10336 elsif Is_Array_Type (Typ) then
10337 return
10338 Has_Default_Aspect (Typ)
10339 or else Has_Full_Default_Initialization (Component_Type (Typ));
10341 -- A protected type, record type, or type extension is fully default
10342 -- initialized if all its components either carry an initialization
10343 -- expression or have a type that is fully default initialized. The
10344 -- parent type of a type extension must be fully default initialized.
10346 elsif Is_Record_Type (Typ) or else Is_Protected_Type (Typ) then
10348 -- Inspect all entities defined in the scope of the type, looking for
10349 -- uninitialized components.
10351 Comp := First_Entity (Typ);
10352 while Present (Comp) loop
10353 if Ekind (Comp) = E_Component
10354 and then Comes_From_Source (Comp)
10355 and then No (Expression (Parent (Comp)))
10356 and then not Has_Full_Default_Initialization (Etype (Comp))
10357 then
10358 return False;
10359 end if;
10361 Next_Entity (Comp);
10362 end loop;
10364 -- Ensure that the parent type of a type extension is fully default
10365 -- initialized.
10367 if Etype (Typ) /= Typ
10368 and then not Has_Full_Default_Initialization (Etype (Typ))
10369 then
10370 return False;
10371 end if;
10373 -- If we get here, then all components and parent portion are fully
10374 -- default initialized.
10376 return True;
10378 -- A task type is fully default initialized by default
10380 elsif Is_Task_Type (Typ) then
10381 return True;
10383 -- Otherwise the type is not fully default initialized
10385 else
10386 return False;
10387 end if;
10388 end Has_Full_Default_Initialization;
10390 --------------------
10391 -- Has_Infinities --
10392 --------------------
10394 function Has_Infinities (E : Entity_Id) return Boolean is
10395 begin
10396 return
10397 Is_Floating_Point_Type (E)
10398 and then Nkind (Scalar_Range (E)) = N_Range
10399 and then Includes_Infinities (Scalar_Range (E));
10400 end Has_Infinities;
10402 --------------------
10403 -- Has_Interfaces --
10404 --------------------
10406 function Has_Interfaces
10407 (T : Entity_Id;
10408 Use_Full_View : Boolean := True) return Boolean
10410 Typ : Entity_Id := Base_Type (T);
10412 begin
10413 -- Handle concurrent types
10415 if Is_Concurrent_Type (Typ) then
10416 Typ := Corresponding_Record_Type (Typ);
10417 end if;
10419 if not Present (Typ)
10420 or else not Is_Record_Type (Typ)
10421 or else not Is_Tagged_Type (Typ)
10422 then
10423 return False;
10424 end if;
10426 -- Handle private types
10428 if Use_Full_View and then Present (Full_View (Typ)) then
10429 Typ := Full_View (Typ);
10430 end if;
10432 -- Handle concurrent record types
10434 if Is_Concurrent_Record_Type (Typ)
10435 and then Is_Non_Empty_List (Abstract_Interface_List (Typ))
10436 then
10437 return True;
10438 end if;
10440 loop
10441 if Is_Interface (Typ)
10442 or else
10443 (Is_Record_Type (Typ)
10444 and then Present (Interfaces (Typ))
10445 and then not Is_Empty_Elmt_List (Interfaces (Typ)))
10446 then
10447 return True;
10448 end if;
10450 exit when Etype (Typ) = Typ
10452 -- Handle private types
10454 or else (Present (Full_View (Etype (Typ)))
10455 and then Full_View (Etype (Typ)) = Typ)
10457 -- Protect frontend against wrong sources with cyclic derivations
10459 or else Etype (Typ) = T;
10461 -- Climb to the ancestor type handling private types
10463 if Present (Full_View (Etype (Typ))) then
10464 Typ := Full_View (Etype (Typ));
10465 else
10466 Typ := Etype (Typ);
10467 end if;
10468 end loop;
10470 return False;
10471 end Has_Interfaces;
10473 --------------------------
10474 -- Has_Max_Queue_Length --
10475 --------------------------
10477 function Has_Max_Queue_Length (Id : Entity_Id) return Boolean is
10478 begin
10479 return
10480 Ekind (Id) = E_Entry
10481 and then Present (Get_Pragma (Id, Pragma_Max_Queue_Length));
10482 end Has_Max_Queue_Length;
10484 ---------------------------------
10485 -- Has_No_Obvious_Side_Effects --
10486 ---------------------------------
10488 function Has_No_Obvious_Side_Effects (N : Node_Id) return Boolean is
10489 begin
10490 -- For now handle literals, constants, and non-volatile variables and
10491 -- expressions combining these with operators or short circuit forms.
10493 if Nkind (N) in N_Numeric_Or_String_Literal then
10494 return True;
10496 elsif Nkind (N) = N_Character_Literal then
10497 return True;
10499 elsif Nkind (N) in N_Unary_Op then
10500 return Has_No_Obvious_Side_Effects (Right_Opnd (N));
10502 elsif Nkind (N) in N_Binary_Op or else Nkind (N) in N_Short_Circuit then
10503 return Has_No_Obvious_Side_Effects (Left_Opnd (N))
10504 and then
10505 Has_No_Obvious_Side_Effects (Right_Opnd (N));
10507 elsif Nkind (N) = N_Expression_With_Actions
10508 and then Is_Empty_List (Actions (N))
10509 then
10510 return Has_No_Obvious_Side_Effects (Expression (N));
10512 elsif Nkind (N) in N_Has_Entity then
10513 return Present (Entity (N))
10514 and then Ekind_In (Entity (N), E_Variable,
10515 E_Constant,
10516 E_Enumeration_Literal,
10517 E_In_Parameter,
10518 E_Out_Parameter,
10519 E_In_Out_Parameter)
10520 and then not Is_Volatile (Entity (N));
10522 else
10523 return False;
10524 end if;
10525 end Has_No_Obvious_Side_Effects;
10527 -----------------------------
10528 -- Has_Non_Null_Refinement --
10529 -----------------------------
10531 function Has_Non_Null_Refinement (Id : Entity_Id) return Boolean is
10532 Constits : Elist_Id;
10534 begin
10535 pragma Assert (Ekind (Id) = E_Abstract_State);
10536 Constits := Refinement_Constituents (Id);
10538 -- For a refinement to be non-null, the first constituent must be
10539 -- anything other than null.
10541 return
10542 Present (Constits)
10543 and then Nkind (Node (First_Elmt (Constits))) /= N_Null;
10544 end Has_Non_Null_Refinement;
10546 ----------------------------------
10547 -- Has_Non_Trivial_Precondition --
10548 ----------------------------------
10550 function Has_Non_Trivial_Precondition (P : Entity_Id) return Boolean is
10551 Cont : constant Node_Id := Find_Aspect (P, Aspect_Pre);
10552 begin
10553 return Present (Cont)
10554 and then Class_Present (Cont)
10555 and then not Is_Entity_Name (Expression (Cont));
10556 end Has_Non_Trivial_Precondition;
10558 -------------------
10559 -- Has_Null_Body --
10560 -------------------
10562 function Has_Null_Body (Proc_Id : Entity_Id) return Boolean is
10563 Body_Id : Entity_Id;
10564 Decl : Node_Id;
10565 Spec : Node_Id;
10566 Stmt1 : Node_Id;
10567 Stmt2 : Node_Id;
10569 begin
10570 Spec := Parent (Proc_Id);
10571 Decl := Parent (Spec);
10573 -- Retrieve the entity of the procedure body (e.g. invariant proc).
10575 if Nkind (Spec) = N_Procedure_Specification
10576 and then Nkind (Decl) = N_Subprogram_Declaration
10577 then
10578 Body_Id := Corresponding_Body (Decl);
10580 -- The body acts as a spec
10582 else
10583 Body_Id := Proc_Id;
10584 end if;
10586 -- The body will be generated later
10588 if No (Body_Id) then
10589 return False;
10590 end if;
10592 Spec := Parent (Body_Id);
10593 Decl := Parent (Spec);
10595 pragma Assert
10596 (Nkind (Spec) = N_Procedure_Specification
10597 and then Nkind (Decl) = N_Subprogram_Body);
10599 Stmt1 := First (Statements (Handled_Statement_Sequence (Decl)));
10601 -- Look for a null statement followed by an optional return
10602 -- statement.
10604 if Nkind (Stmt1) = N_Null_Statement then
10605 Stmt2 := Next (Stmt1);
10607 if Present (Stmt2) then
10608 return Nkind (Stmt2) = N_Simple_Return_Statement;
10609 else
10610 return True;
10611 end if;
10612 end if;
10614 return False;
10615 end Has_Null_Body;
10617 ------------------------
10618 -- Has_Null_Exclusion --
10619 ------------------------
10621 function Has_Null_Exclusion (N : Node_Id) return Boolean is
10622 begin
10623 case Nkind (N) is
10624 when N_Access_Definition
10625 | N_Access_Function_Definition
10626 | N_Access_Procedure_Definition
10627 | N_Access_To_Object_Definition
10628 | N_Allocator
10629 | N_Derived_Type_Definition
10630 | N_Function_Specification
10631 | N_Subtype_Declaration
10633 return Null_Exclusion_Present (N);
10635 when N_Component_Definition
10636 | N_Formal_Object_Declaration
10637 | N_Object_Renaming_Declaration
10639 if Present (Subtype_Mark (N)) then
10640 return Null_Exclusion_Present (N);
10641 else pragma Assert (Present (Access_Definition (N)));
10642 return Null_Exclusion_Present (Access_Definition (N));
10643 end if;
10645 when N_Discriminant_Specification =>
10646 if Nkind (Discriminant_Type (N)) = N_Access_Definition then
10647 return Null_Exclusion_Present (Discriminant_Type (N));
10648 else
10649 return Null_Exclusion_Present (N);
10650 end if;
10652 when N_Object_Declaration =>
10653 if Nkind (Object_Definition (N)) = N_Access_Definition then
10654 return Null_Exclusion_Present (Object_Definition (N));
10655 else
10656 return Null_Exclusion_Present (N);
10657 end if;
10659 when N_Parameter_Specification =>
10660 if Nkind (Parameter_Type (N)) = N_Access_Definition then
10661 return Null_Exclusion_Present (Parameter_Type (N));
10662 else
10663 return Null_Exclusion_Present (N);
10664 end if;
10666 when others =>
10667 return False;
10668 end case;
10669 end Has_Null_Exclusion;
10671 ------------------------
10672 -- Has_Null_Extension --
10673 ------------------------
10675 function Has_Null_Extension (T : Entity_Id) return Boolean is
10676 B : constant Entity_Id := Base_Type (T);
10677 Comps : Node_Id;
10678 Ext : Node_Id;
10680 begin
10681 if Nkind (Parent (B)) = N_Full_Type_Declaration
10682 and then Present (Record_Extension_Part (Type_Definition (Parent (B))))
10683 then
10684 Ext := Record_Extension_Part (Type_Definition (Parent (B)));
10686 if Present (Ext) then
10687 if Null_Present (Ext) then
10688 return True;
10689 else
10690 Comps := Component_List (Ext);
10692 -- The null component list is rewritten during analysis to
10693 -- include the parent component. Any other component indicates
10694 -- that the extension was not originally null.
10696 return Null_Present (Comps)
10697 or else No (Next (First (Component_Items (Comps))));
10698 end if;
10699 else
10700 return False;
10701 end if;
10703 else
10704 return False;
10705 end if;
10706 end Has_Null_Extension;
10708 -------------------------
10709 -- Has_Null_Refinement --
10710 -------------------------
10712 function Has_Null_Refinement (Id : Entity_Id) return Boolean is
10713 Constits : Elist_Id;
10715 begin
10716 pragma Assert (Ekind (Id) = E_Abstract_State);
10717 Constits := Refinement_Constituents (Id);
10719 -- For a refinement to be null, the state's sole constituent must be a
10720 -- null.
10722 return
10723 Present (Constits)
10724 and then Nkind (Node (First_Elmt (Constits))) = N_Null;
10725 end Has_Null_Refinement;
10727 -------------------------------
10728 -- Has_Overriding_Initialize --
10729 -------------------------------
10731 function Has_Overriding_Initialize (T : Entity_Id) return Boolean is
10732 BT : constant Entity_Id := Base_Type (T);
10733 P : Elmt_Id;
10735 begin
10736 if Is_Controlled (BT) then
10737 if Is_RTU (Scope (BT), Ada_Finalization) then
10738 return False;
10740 elsif Present (Primitive_Operations (BT)) then
10741 P := First_Elmt (Primitive_Operations (BT));
10742 while Present (P) loop
10743 declare
10744 Init : constant Entity_Id := Node (P);
10745 Formal : constant Entity_Id := First_Formal (Init);
10746 begin
10747 if Ekind (Init) = E_Procedure
10748 and then Chars (Init) = Name_Initialize
10749 and then Comes_From_Source (Init)
10750 and then Present (Formal)
10751 and then Etype (Formal) = BT
10752 and then No (Next_Formal (Formal))
10753 and then (Ada_Version < Ada_2012
10754 or else not Null_Present (Parent (Init)))
10755 then
10756 return True;
10757 end if;
10758 end;
10760 Next_Elmt (P);
10761 end loop;
10762 end if;
10764 -- Here if type itself does not have a non-null Initialize operation:
10765 -- check immediate ancestor.
10767 if Is_Derived_Type (BT)
10768 and then Has_Overriding_Initialize (Etype (BT))
10769 then
10770 return True;
10771 end if;
10772 end if;
10774 return False;
10775 end Has_Overriding_Initialize;
10777 --------------------------------------
10778 -- Has_Preelaborable_Initialization --
10779 --------------------------------------
10781 function Has_Preelaborable_Initialization (E : Entity_Id) return Boolean is
10782 Has_PE : Boolean;
10784 procedure Check_Components (E : Entity_Id);
10785 -- Check component/discriminant chain, sets Has_PE False if a component
10786 -- or discriminant does not meet the preelaborable initialization rules.
10788 ----------------------
10789 -- Check_Components --
10790 ----------------------
10792 procedure Check_Components (E : Entity_Id) is
10793 Ent : Entity_Id;
10794 Exp : Node_Id;
10796 function Is_Preelaborable_Expression (N : Node_Id) return Boolean;
10797 -- Returns True if and only if the expression denoted by N does not
10798 -- violate restrictions on preelaborable constructs (RM-10.2.1(5-9)).
10800 ---------------------------------
10801 -- Is_Preelaborable_Expression --
10802 ---------------------------------
10804 function Is_Preelaborable_Expression (N : Node_Id) return Boolean is
10805 Exp : Node_Id;
10806 Assn : Node_Id;
10807 Choice : Node_Id;
10808 Comp_Type : Entity_Id;
10809 Is_Array_Aggr : Boolean;
10811 begin
10812 if Is_OK_Static_Expression (N) then
10813 return True;
10815 elsif Nkind (N) = N_Null then
10816 return True;
10818 -- Attributes are allowed in general, even if their prefix is a
10819 -- formal type. (It seems that certain attributes known not to be
10820 -- static might not be allowed, but there are no rules to prevent
10821 -- them.)
10823 elsif Nkind (N) = N_Attribute_Reference then
10824 return True;
10826 -- The name of a discriminant evaluated within its parent type is
10827 -- defined to be preelaborable (10.2.1(8)). Note that we test for
10828 -- names that denote discriminals as well as discriminants to
10829 -- catch references occurring within init procs.
10831 elsif Is_Entity_Name (N)
10832 and then
10833 (Ekind (Entity (N)) = E_Discriminant
10834 or else (Ekind_In (Entity (N), E_Constant, E_In_Parameter)
10835 and then Present (Discriminal_Link (Entity (N)))))
10836 then
10837 return True;
10839 elsif Nkind (N) = N_Qualified_Expression then
10840 return Is_Preelaborable_Expression (Expression (N));
10842 -- For aggregates we have to check that each of the associations
10843 -- is preelaborable.
10845 elsif Nkind_In (N, N_Aggregate, N_Extension_Aggregate) then
10846 Is_Array_Aggr := Is_Array_Type (Etype (N));
10848 if Is_Array_Aggr then
10849 Comp_Type := Component_Type (Etype (N));
10850 end if;
10852 -- Check the ancestor part of extension aggregates, which must
10853 -- be either the name of a type that has preelaborable init or
10854 -- an expression that is preelaborable.
10856 if Nkind (N) = N_Extension_Aggregate then
10857 declare
10858 Anc_Part : constant Node_Id := Ancestor_Part (N);
10860 begin
10861 if Is_Entity_Name (Anc_Part)
10862 and then Is_Type (Entity (Anc_Part))
10863 then
10864 if not Has_Preelaborable_Initialization
10865 (Entity (Anc_Part))
10866 then
10867 return False;
10868 end if;
10870 elsif not Is_Preelaborable_Expression (Anc_Part) then
10871 return False;
10872 end if;
10873 end;
10874 end if;
10876 -- Check positional associations
10878 Exp := First (Expressions (N));
10879 while Present (Exp) loop
10880 if not Is_Preelaborable_Expression (Exp) then
10881 return False;
10882 end if;
10884 Next (Exp);
10885 end loop;
10887 -- Check named associations
10889 Assn := First (Component_Associations (N));
10890 while Present (Assn) loop
10891 Choice := First (Choices (Assn));
10892 while Present (Choice) loop
10893 if Is_Array_Aggr then
10894 if Nkind (Choice) = N_Others_Choice then
10895 null;
10897 elsif Nkind (Choice) = N_Range then
10898 if not Is_OK_Static_Range (Choice) then
10899 return False;
10900 end if;
10902 elsif not Is_OK_Static_Expression (Choice) then
10903 return False;
10904 end if;
10906 else
10907 Comp_Type := Etype (Choice);
10908 end if;
10910 Next (Choice);
10911 end loop;
10913 -- If the association has a <> at this point, then we have
10914 -- to check whether the component's type has preelaborable
10915 -- initialization. Note that this only occurs when the
10916 -- association's corresponding component does not have a
10917 -- default expression, the latter case having already been
10918 -- expanded as an expression for the association.
10920 if Box_Present (Assn) then
10921 if not Has_Preelaborable_Initialization (Comp_Type) then
10922 return False;
10923 end if;
10925 -- In the expression case we check whether the expression
10926 -- is preelaborable.
10928 elsif
10929 not Is_Preelaborable_Expression (Expression (Assn))
10930 then
10931 return False;
10932 end if;
10934 Next (Assn);
10935 end loop;
10937 -- If we get here then aggregate as a whole is preelaborable
10939 return True;
10941 -- All other cases are not preelaborable
10943 else
10944 return False;
10945 end if;
10946 end Is_Preelaborable_Expression;
10948 -- Start of processing for Check_Components
10950 begin
10951 -- Loop through entities of record or protected type
10953 Ent := E;
10954 while Present (Ent) loop
10956 -- We are interested only in components and discriminants
10958 Exp := Empty;
10960 case Ekind (Ent) is
10961 when E_Component =>
10963 -- Get default expression if any. If there is no declaration
10964 -- node, it means we have an internal entity. The parent and
10965 -- tag fields are examples of such entities. For such cases,
10966 -- we just test the type of the entity.
10968 if Present (Declaration_Node (Ent)) then
10969 Exp := Expression (Declaration_Node (Ent));
10970 end if;
10972 when E_Discriminant =>
10974 -- Note: for a renamed discriminant, the Declaration_Node
10975 -- may point to the one from the ancestor, and have a
10976 -- different expression, so use the proper attribute to
10977 -- retrieve the expression from the derived constraint.
10979 Exp := Discriminant_Default_Value (Ent);
10981 when others =>
10982 goto Check_Next_Entity;
10983 end case;
10985 -- A component has PI if it has no default expression and the
10986 -- component type has PI.
10988 if No (Exp) then
10989 if not Has_Preelaborable_Initialization (Etype (Ent)) then
10990 Has_PE := False;
10991 exit;
10992 end if;
10994 -- Require the default expression to be preelaborable
10996 elsif not Is_Preelaborable_Expression (Exp) then
10997 Has_PE := False;
10998 exit;
10999 end if;
11001 <<Check_Next_Entity>>
11002 Next_Entity (Ent);
11003 end loop;
11004 end Check_Components;
11006 -- Start of processing for Has_Preelaborable_Initialization
11008 begin
11009 -- Immediate return if already marked as known preelaborable init. This
11010 -- covers types for which this function has already been called once
11011 -- and returned True (in which case the result is cached), and also
11012 -- types to which a pragma Preelaborable_Initialization applies.
11014 if Known_To_Have_Preelab_Init (E) then
11015 return True;
11016 end if;
11018 -- If the type is a subtype representing a generic actual type, then
11019 -- test whether its base type has preelaborable initialization since
11020 -- the subtype representing the actual does not inherit this attribute
11021 -- from the actual or formal. (but maybe it should???)
11023 if Is_Generic_Actual_Type (E) then
11024 return Has_Preelaborable_Initialization (Base_Type (E));
11025 end if;
11027 -- All elementary types have preelaborable initialization
11029 if Is_Elementary_Type (E) then
11030 Has_PE := True;
11032 -- Array types have PI if the component type has PI
11034 elsif Is_Array_Type (E) then
11035 Has_PE := Has_Preelaborable_Initialization (Component_Type (E));
11037 -- A derived type has preelaborable initialization if its parent type
11038 -- has preelaborable initialization and (in the case of a derived record
11039 -- extension) if the non-inherited components all have preelaborable
11040 -- initialization. However, a user-defined controlled type with an
11041 -- overriding Initialize procedure does not have preelaborable
11042 -- initialization.
11044 elsif Is_Derived_Type (E) then
11046 -- If the derived type is a private extension then it doesn't have
11047 -- preelaborable initialization.
11049 if Ekind (Base_Type (E)) = E_Record_Type_With_Private then
11050 return False;
11051 end if;
11053 -- First check whether ancestor type has preelaborable initialization
11055 Has_PE := Has_Preelaborable_Initialization (Etype (Base_Type (E)));
11057 -- If OK, check extension components (if any)
11059 if Has_PE and then Is_Record_Type (E) then
11060 Check_Components (First_Entity (E));
11061 end if;
11063 -- Check specifically for 10.2.1(11.4/2) exception: a controlled type
11064 -- with a user defined Initialize procedure does not have PI. If
11065 -- the type is untagged, the control primitives come from a component
11066 -- that has already been checked.
11068 if Has_PE
11069 and then Is_Controlled (E)
11070 and then Is_Tagged_Type (E)
11071 and then Has_Overriding_Initialize (E)
11072 then
11073 Has_PE := False;
11074 end if;
11076 -- Private types not derived from a type having preelaborable init and
11077 -- that are not marked with pragma Preelaborable_Initialization do not
11078 -- have preelaborable initialization.
11080 elsif Is_Private_Type (E) then
11081 return False;
11083 -- Record type has PI if it is non private and all components have PI
11085 elsif Is_Record_Type (E) then
11086 Has_PE := True;
11087 Check_Components (First_Entity (E));
11089 -- Protected types must not have entries, and components must meet
11090 -- same set of rules as for record components.
11092 elsif Is_Protected_Type (E) then
11093 if Has_Entries (E) then
11094 Has_PE := False;
11095 else
11096 Has_PE := True;
11097 Check_Components (First_Entity (E));
11098 Check_Components (First_Private_Entity (E));
11099 end if;
11101 -- Type System.Address always has preelaborable initialization
11103 elsif Is_RTE (E, RE_Address) then
11104 Has_PE := True;
11106 -- In all other cases, type does not have preelaborable initialization
11108 else
11109 return False;
11110 end if;
11112 -- If type has preelaborable initialization, cache result
11114 if Has_PE then
11115 Set_Known_To_Have_Preelab_Init (E);
11116 end if;
11118 return Has_PE;
11119 end Has_Preelaborable_Initialization;
11121 ---------------------------
11122 -- Has_Private_Component --
11123 ---------------------------
11125 function Has_Private_Component (Type_Id : Entity_Id) return Boolean is
11126 Btype : Entity_Id := Base_Type (Type_Id);
11127 Component : Entity_Id;
11129 begin
11130 if Error_Posted (Type_Id)
11131 or else Error_Posted (Btype)
11132 then
11133 return False;
11134 end if;
11136 if Is_Class_Wide_Type (Btype) then
11137 Btype := Root_Type (Btype);
11138 end if;
11140 if Is_Private_Type (Btype) then
11141 declare
11142 UT : constant Entity_Id := Underlying_Type (Btype);
11143 begin
11144 if No (UT) then
11145 if No (Full_View (Btype)) then
11146 return not Is_Generic_Type (Btype)
11147 and then
11148 not Is_Generic_Type (Root_Type (Btype));
11149 else
11150 return not Is_Generic_Type (Root_Type (Full_View (Btype)));
11151 end if;
11152 else
11153 return not Is_Frozen (UT) and then Has_Private_Component (UT);
11154 end if;
11155 end;
11157 elsif Is_Array_Type (Btype) then
11158 return Has_Private_Component (Component_Type (Btype));
11160 elsif Is_Record_Type (Btype) then
11161 Component := First_Component (Btype);
11162 while Present (Component) loop
11163 if Has_Private_Component (Etype (Component)) then
11164 return True;
11165 end if;
11167 Next_Component (Component);
11168 end loop;
11170 return False;
11172 elsif Is_Protected_Type (Btype)
11173 and then Present (Corresponding_Record_Type (Btype))
11174 then
11175 return Has_Private_Component (Corresponding_Record_Type (Btype));
11177 else
11178 return False;
11179 end if;
11180 end Has_Private_Component;
11182 ----------------------
11183 -- Has_Signed_Zeros --
11184 ----------------------
11186 function Has_Signed_Zeros (E : Entity_Id) return Boolean is
11187 begin
11188 return Is_Floating_Point_Type (E) and then Signed_Zeros_On_Target;
11189 end Has_Signed_Zeros;
11191 ------------------------------
11192 -- Has_Significant_Contract --
11193 ------------------------------
11195 function Has_Significant_Contract (Subp_Id : Entity_Id) return Boolean is
11196 Subp_Nam : constant Name_Id := Chars (Subp_Id);
11198 begin
11199 -- _Finalizer procedure
11201 if Subp_Nam = Name_uFinalizer then
11202 return False;
11204 -- _Postconditions procedure
11206 elsif Subp_Nam = Name_uPostconditions then
11207 return False;
11209 -- Predicate function
11211 elsif Ekind (Subp_Id) = E_Function
11212 and then Is_Predicate_Function (Subp_Id)
11213 then
11214 return False;
11216 -- TSS subprogram
11218 elsif Get_TSS_Name (Subp_Id) /= TSS_Null then
11219 return False;
11221 else
11222 return True;
11223 end if;
11224 end Has_Significant_Contract;
11226 -----------------------------
11227 -- Has_Static_Array_Bounds --
11228 -----------------------------
11230 function Has_Static_Array_Bounds (Typ : Node_Id) return Boolean is
11231 Ndims : constant Nat := Number_Dimensions (Typ);
11233 Index : Node_Id;
11234 Low : Node_Id;
11235 High : Node_Id;
11237 begin
11238 -- Unconstrained types do not have static bounds
11240 if not Is_Constrained (Typ) then
11241 return False;
11242 end if;
11244 -- First treat string literals specially, as the lower bound and length
11245 -- of string literals are not stored like those of arrays.
11247 -- A string literal always has static bounds
11249 if Ekind (Typ) = E_String_Literal_Subtype then
11250 return True;
11251 end if;
11253 -- Treat all dimensions in turn
11255 Index := First_Index (Typ);
11256 for Indx in 1 .. Ndims loop
11258 -- In case of an illegal index which is not a discrete type, return
11259 -- that the type is not static.
11261 if not Is_Discrete_Type (Etype (Index))
11262 or else Etype (Index) = Any_Type
11263 then
11264 return False;
11265 end if;
11267 Get_Index_Bounds (Index, Low, High);
11269 if Error_Posted (Low) or else Error_Posted (High) then
11270 return False;
11271 end if;
11273 if Is_OK_Static_Expression (Low)
11274 and then
11275 Is_OK_Static_Expression (High)
11276 then
11277 null;
11278 else
11279 return False;
11280 end if;
11282 Next (Index);
11283 end loop;
11285 -- If we fall through the loop, all indexes matched
11287 return True;
11288 end Has_Static_Array_Bounds;
11290 ----------------
11291 -- Has_Stream --
11292 ----------------
11294 function Has_Stream (T : Entity_Id) return Boolean is
11295 E : Entity_Id;
11297 begin
11298 if No (T) then
11299 return False;
11301 elsif Is_RTE (Root_Type (T), RE_Root_Stream_Type) then
11302 return True;
11304 elsif Is_Array_Type (T) then
11305 return Has_Stream (Component_Type (T));
11307 elsif Is_Record_Type (T) then
11308 E := First_Component (T);
11309 while Present (E) loop
11310 if Has_Stream (Etype (E)) then
11311 return True;
11312 else
11313 Next_Component (E);
11314 end if;
11315 end loop;
11317 return False;
11319 elsif Is_Private_Type (T) then
11320 return Has_Stream (Underlying_Type (T));
11322 else
11323 return False;
11324 end if;
11325 end Has_Stream;
11327 ----------------
11328 -- Has_Suffix --
11329 ----------------
11331 function Has_Suffix (E : Entity_Id; Suffix : Character) return Boolean is
11332 begin
11333 Get_Name_String (Chars (E));
11334 return Name_Buffer (Name_Len) = Suffix;
11335 end Has_Suffix;
11337 ----------------
11338 -- Add_Suffix --
11339 ----------------
11341 function Add_Suffix (E : Entity_Id; Suffix : Character) return Name_Id is
11342 begin
11343 Get_Name_String (Chars (E));
11344 Add_Char_To_Name_Buffer (Suffix);
11345 return Name_Find;
11346 end Add_Suffix;
11348 -------------------
11349 -- Remove_Suffix --
11350 -------------------
11352 function Remove_Suffix (E : Entity_Id; Suffix : Character) return Name_Id is
11353 begin
11354 pragma Assert (Has_Suffix (E, Suffix));
11355 Get_Name_String (Chars (E));
11356 Name_Len := Name_Len - 1;
11357 return Name_Find;
11358 end Remove_Suffix;
11360 ----------------------------------
11361 -- Replace_Null_By_Null_Address --
11362 ----------------------------------
11364 procedure Replace_Null_By_Null_Address (N : Node_Id) is
11365 procedure Replace_Null_Operand (Op : Node_Id; Other_Op : Node_Id);
11366 -- Replace operand Op with a reference to Null_Address when the operand
11367 -- denotes a null Address. Other_Op denotes the other operand.
11369 --------------------------
11370 -- Replace_Null_Operand --
11371 --------------------------
11373 procedure Replace_Null_Operand (Op : Node_Id; Other_Op : Node_Id) is
11374 begin
11375 -- Check the type of the complementary operand since the N_Null node
11376 -- has not been decorated yet.
11378 if Nkind (Op) = N_Null
11379 and then Is_Descendant_Of_Address (Etype (Other_Op))
11380 then
11381 Rewrite (Op, New_Occurrence_Of (RTE (RE_Null_Address), Sloc (Op)));
11382 end if;
11383 end Replace_Null_Operand;
11385 -- Start of processing for Replace_Null_By_Null_Address
11387 begin
11388 pragma Assert (Relaxed_RM_Semantics);
11389 pragma Assert (Nkind_In (N, N_Null,
11390 N_Op_Eq,
11391 N_Op_Ge,
11392 N_Op_Gt,
11393 N_Op_Le,
11394 N_Op_Lt,
11395 N_Op_Ne));
11397 if Nkind (N) = N_Null then
11398 Rewrite (N, New_Occurrence_Of (RTE (RE_Null_Address), Sloc (N)));
11400 else
11401 declare
11402 L : constant Node_Id := Left_Opnd (N);
11403 R : constant Node_Id := Right_Opnd (N);
11405 begin
11406 Replace_Null_Operand (L, Other_Op => R);
11407 Replace_Null_Operand (R, Other_Op => L);
11408 end;
11409 end if;
11410 end Replace_Null_By_Null_Address;
11412 --------------------------
11413 -- Has_Tagged_Component --
11414 --------------------------
11416 function Has_Tagged_Component (Typ : Entity_Id) return Boolean is
11417 Comp : Entity_Id;
11419 begin
11420 if Is_Private_Type (Typ) and then Present (Underlying_Type (Typ)) then
11421 return Has_Tagged_Component (Underlying_Type (Typ));
11423 elsif Is_Array_Type (Typ) then
11424 return Has_Tagged_Component (Component_Type (Typ));
11426 elsif Is_Tagged_Type (Typ) then
11427 return True;
11429 elsif Is_Record_Type (Typ) then
11430 Comp := First_Component (Typ);
11431 while Present (Comp) loop
11432 if Has_Tagged_Component (Etype (Comp)) then
11433 return True;
11434 end if;
11436 Next_Component (Comp);
11437 end loop;
11439 return False;
11441 else
11442 return False;
11443 end if;
11444 end Has_Tagged_Component;
11446 -----------------------------
11447 -- Has_Undefined_Reference --
11448 -----------------------------
11450 function Has_Undefined_Reference (Expr : Node_Id) return Boolean is
11451 Has_Undef_Ref : Boolean := False;
11452 -- Flag set when expression Expr contains at least one undefined
11453 -- reference.
11455 function Is_Undefined_Reference (N : Node_Id) return Traverse_Result;
11456 -- Determine whether N denotes a reference and if it does, whether it is
11457 -- undefined.
11459 ----------------------------
11460 -- Is_Undefined_Reference --
11461 ----------------------------
11463 function Is_Undefined_Reference (N : Node_Id) return Traverse_Result is
11464 begin
11465 if Is_Entity_Name (N)
11466 and then Present (Entity (N))
11467 and then Entity (N) = Any_Id
11468 then
11469 Has_Undef_Ref := True;
11470 return Abandon;
11471 end if;
11473 return OK;
11474 end Is_Undefined_Reference;
11476 procedure Find_Undefined_References is
11477 new Traverse_Proc (Is_Undefined_Reference);
11479 -- Start of processing for Has_Undefined_Reference
11481 begin
11482 Find_Undefined_References (Expr);
11484 return Has_Undef_Ref;
11485 end Has_Undefined_Reference;
11487 ----------------------------
11488 -- Has_Volatile_Component --
11489 ----------------------------
11491 function Has_Volatile_Component (Typ : Entity_Id) return Boolean is
11492 Comp : Entity_Id;
11494 begin
11495 if Has_Volatile_Components (Typ) then
11496 return True;
11498 elsif Is_Array_Type (Typ) then
11499 return Is_Volatile (Component_Type (Typ));
11501 elsif Is_Record_Type (Typ) then
11502 Comp := First_Component (Typ);
11503 while Present (Comp) loop
11504 if Is_Volatile_Object (Comp) then
11505 return True;
11506 end if;
11508 Comp := Next_Component (Comp);
11509 end loop;
11510 end if;
11512 return False;
11513 end Has_Volatile_Component;
11515 -------------------------
11516 -- Implementation_Kind --
11517 -------------------------
11519 function Implementation_Kind (Subp : Entity_Id) return Name_Id is
11520 Impl_Prag : constant Node_Id := Get_Rep_Pragma (Subp, Name_Implemented);
11521 Arg : Node_Id;
11522 begin
11523 pragma Assert (Present (Impl_Prag));
11524 Arg := Last (Pragma_Argument_Associations (Impl_Prag));
11525 return Chars (Get_Pragma_Arg (Arg));
11526 end Implementation_Kind;
11528 --------------------------
11529 -- Implements_Interface --
11530 --------------------------
11532 function Implements_Interface
11533 (Typ_Ent : Entity_Id;
11534 Iface_Ent : Entity_Id;
11535 Exclude_Parents : Boolean := False) return Boolean
11537 Ifaces_List : Elist_Id;
11538 Elmt : Elmt_Id;
11539 Iface : Entity_Id := Base_Type (Iface_Ent);
11540 Typ : Entity_Id := Base_Type (Typ_Ent);
11542 begin
11543 if Is_Class_Wide_Type (Typ) then
11544 Typ := Root_Type (Typ);
11545 end if;
11547 if not Has_Interfaces (Typ) then
11548 return False;
11549 end if;
11551 if Is_Class_Wide_Type (Iface) then
11552 Iface := Root_Type (Iface);
11553 end if;
11555 Collect_Interfaces (Typ, Ifaces_List);
11557 Elmt := First_Elmt (Ifaces_List);
11558 while Present (Elmt) loop
11559 if Is_Ancestor (Node (Elmt), Typ, Use_Full_View => True)
11560 and then Exclude_Parents
11561 then
11562 null;
11564 elsif Node (Elmt) = Iface then
11565 return True;
11566 end if;
11568 Next_Elmt (Elmt);
11569 end loop;
11571 return False;
11572 end Implements_Interface;
11574 ------------------------------------
11575 -- In_Assertion_Expression_Pragma --
11576 ------------------------------------
11578 function In_Assertion_Expression_Pragma (N : Node_Id) return Boolean is
11579 Par : Node_Id;
11580 Prag : Node_Id := Empty;
11582 begin
11583 -- Climb the parent chain looking for an enclosing pragma
11585 Par := N;
11586 while Present (Par) loop
11587 if Nkind (Par) = N_Pragma then
11588 Prag := Par;
11589 exit;
11591 -- Precondition-like pragmas are expanded into if statements, check
11592 -- the original node instead.
11594 elsif Nkind (Original_Node (Par)) = N_Pragma then
11595 Prag := Original_Node (Par);
11596 exit;
11598 -- The expansion of attribute 'Old generates a constant to capture
11599 -- the result of the prefix. If the parent traversal reaches
11600 -- one of these constants, then the node technically came from a
11601 -- postcondition-like pragma. Note that the Ekind is not tested here
11602 -- because N may be the expression of an object declaration which is
11603 -- currently being analyzed. Such objects carry Ekind of E_Void.
11605 elsif Nkind (Par) = N_Object_Declaration
11606 and then Constant_Present (Par)
11607 and then Stores_Attribute_Old_Prefix (Defining_Entity (Par))
11608 then
11609 return True;
11611 -- Prevent the search from going too far
11613 elsif Is_Body_Or_Package_Declaration (Par) then
11614 return False;
11615 end if;
11617 Par := Parent (Par);
11618 end loop;
11620 return
11621 Present (Prag)
11622 and then Assertion_Expression_Pragma (Get_Pragma_Id (Prag));
11623 end In_Assertion_Expression_Pragma;
11625 ----------------------
11626 -- In_Generic_Scope --
11627 ----------------------
11629 function In_Generic_Scope (E : Entity_Id) return Boolean is
11630 S : Entity_Id;
11632 begin
11633 S := Scope (E);
11634 while Present (S) and then S /= Standard_Standard loop
11635 if Is_Generic_Unit (S) then
11636 return True;
11637 end if;
11639 S := Scope (S);
11640 end loop;
11642 return False;
11643 end In_Generic_Scope;
11645 -----------------
11646 -- In_Instance --
11647 -----------------
11649 function In_Instance return Boolean is
11650 Curr_Unit : constant Entity_Id := Cunit_Entity (Current_Sem_Unit);
11651 S : Entity_Id;
11653 begin
11654 S := Current_Scope;
11655 while Present (S) and then S /= Standard_Standard loop
11656 if Is_Generic_Instance (S) then
11658 -- A child instance is always compiled in the context of a parent
11659 -- instance. Nevertheless, the actuals are not analyzed in an
11660 -- instance context. We detect this case by examining the current
11661 -- compilation unit, which must be a child instance, and checking
11662 -- that it is not currently on the scope stack.
11664 if Is_Child_Unit (Curr_Unit)
11665 and then Nkind (Unit (Cunit (Current_Sem_Unit))) =
11666 N_Package_Instantiation
11667 and then not In_Open_Scopes (Curr_Unit)
11668 then
11669 return False;
11670 else
11671 return True;
11672 end if;
11673 end if;
11675 S := Scope (S);
11676 end loop;
11678 return False;
11679 end In_Instance;
11681 ----------------------
11682 -- In_Instance_Body --
11683 ----------------------
11685 function In_Instance_Body return Boolean is
11686 S : Entity_Id;
11688 begin
11689 S := Current_Scope;
11690 while Present (S) and then S /= Standard_Standard loop
11691 if Ekind_In (S, E_Function, E_Procedure)
11692 and then Is_Generic_Instance (S)
11693 then
11694 return True;
11696 elsif Ekind (S) = E_Package
11697 and then In_Package_Body (S)
11698 and then Is_Generic_Instance (S)
11699 then
11700 return True;
11701 end if;
11703 S := Scope (S);
11704 end loop;
11706 return False;
11707 end In_Instance_Body;
11709 -----------------------------
11710 -- In_Instance_Not_Visible --
11711 -----------------------------
11713 function In_Instance_Not_Visible return Boolean is
11714 S : Entity_Id;
11716 begin
11717 S := Current_Scope;
11718 while Present (S) and then S /= Standard_Standard loop
11719 if Ekind_In (S, E_Function, E_Procedure)
11720 and then Is_Generic_Instance (S)
11721 then
11722 return True;
11724 elsif Ekind (S) = E_Package
11725 and then (In_Package_Body (S) or else In_Private_Part (S))
11726 and then Is_Generic_Instance (S)
11727 then
11728 return True;
11729 end if;
11731 S := Scope (S);
11732 end loop;
11734 return False;
11735 end In_Instance_Not_Visible;
11737 ------------------------------
11738 -- In_Instance_Visible_Part --
11739 ------------------------------
11741 function In_Instance_Visible_Part return Boolean is
11742 S : Entity_Id;
11744 begin
11745 S := Current_Scope;
11746 while Present (S) and then S /= Standard_Standard loop
11747 if Ekind (S) = E_Package
11748 and then Is_Generic_Instance (S)
11749 and then not In_Package_Body (S)
11750 and then not In_Private_Part (S)
11751 then
11752 return True;
11753 end if;
11755 S := Scope (S);
11756 end loop;
11758 return False;
11759 end In_Instance_Visible_Part;
11761 ---------------------
11762 -- In_Package_Body --
11763 ---------------------
11765 function In_Package_Body return Boolean is
11766 S : Entity_Id;
11768 begin
11769 S := Current_Scope;
11770 while Present (S) and then S /= Standard_Standard loop
11771 if Ekind (S) = E_Package and then In_Package_Body (S) then
11772 return True;
11773 else
11774 S := Scope (S);
11775 end if;
11776 end loop;
11778 return False;
11779 end In_Package_Body;
11781 --------------------------
11782 -- In_Pragma_Expression --
11783 --------------------------
11785 function In_Pragma_Expression (N : Node_Id; Nam : Name_Id) return Boolean is
11786 P : Node_Id;
11787 begin
11788 P := Parent (N);
11789 loop
11790 if No (P) then
11791 return False;
11792 elsif Nkind (P) = N_Pragma and then Pragma_Name (P) = Nam then
11793 return True;
11794 else
11795 P := Parent (P);
11796 end if;
11797 end loop;
11798 end In_Pragma_Expression;
11800 ---------------------------
11801 -- In_Pre_Post_Condition --
11802 ---------------------------
11804 function In_Pre_Post_Condition (N : Node_Id) return Boolean is
11805 Par : Node_Id;
11806 Prag : Node_Id := Empty;
11807 Prag_Id : Pragma_Id;
11809 begin
11810 -- Climb the parent chain looking for an enclosing pragma
11812 Par := N;
11813 while Present (Par) loop
11814 if Nkind (Par) = N_Pragma then
11815 Prag := Par;
11816 exit;
11818 -- Prevent the search from going too far
11820 elsif Is_Body_Or_Package_Declaration (Par) then
11821 exit;
11822 end if;
11824 Par := Parent (Par);
11825 end loop;
11827 if Present (Prag) then
11828 Prag_Id := Get_Pragma_Id (Prag);
11830 return
11831 Prag_Id = Pragma_Post
11832 or else Prag_Id = Pragma_Post_Class
11833 or else Prag_Id = Pragma_Postcondition
11834 or else Prag_Id = Pragma_Pre
11835 or else Prag_Id = Pragma_Pre_Class
11836 or else Prag_Id = Pragma_Precondition;
11838 -- Otherwise the node is not enclosed by a pre/postcondition pragma
11840 else
11841 return False;
11842 end if;
11843 end In_Pre_Post_Condition;
11845 -------------------------------------
11846 -- In_Reverse_Storage_Order_Object --
11847 -------------------------------------
11849 function In_Reverse_Storage_Order_Object (N : Node_Id) return Boolean is
11850 Pref : Node_Id;
11851 Btyp : Entity_Id := Empty;
11853 begin
11854 -- Climb up indexed components
11856 Pref := N;
11857 loop
11858 case Nkind (Pref) is
11859 when N_Selected_Component =>
11860 Pref := Prefix (Pref);
11861 exit;
11863 when N_Indexed_Component =>
11864 Pref := Prefix (Pref);
11866 when others =>
11867 Pref := Empty;
11868 exit;
11869 end case;
11870 end loop;
11872 if Present (Pref) then
11873 Btyp := Base_Type (Etype (Pref));
11874 end if;
11876 return Present (Btyp)
11877 and then (Is_Record_Type (Btyp) or else Is_Array_Type (Btyp))
11878 and then Reverse_Storage_Order (Btyp);
11879 end In_Reverse_Storage_Order_Object;
11881 --------------------------------------
11882 -- In_Subprogram_Or_Concurrent_Unit --
11883 --------------------------------------
11885 function In_Subprogram_Or_Concurrent_Unit return Boolean is
11886 E : Entity_Id;
11887 K : Entity_Kind;
11889 begin
11890 -- Use scope chain to check successively outer scopes
11892 E := Current_Scope;
11893 loop
11894 K := Ekind (E);
11896 if K in Subprogram_Kind
11897 or else K in Concurrent_Kind
11898 or else K in Generic_Subprogram_Kind
11899 then
11900 return True;
11902 elsif E = Standard_Standard then
11903 return False;
11904 end if;
11906 E := Scope (E);
11907 end loop;
11908 end In_Subprogram_Or_Concurrent_Unit;
11910 ----------------
11911 -- In_Subtree --
11912 ----------------
11914 function In_Subtree (Root : Node_Id; N : Node_Id) return Boolean is
11915 Curr : Node_Id;
11917 begin
11918 Curr := N;
11919 while Present (Curr) loop
11920 if Curr = Root then
11921 return True;
11922 end if;
11924 Curr := Parent (Curr);
11925 end loop;
11927 return False;
11928 end In_Subtree;
11930 ---------------------
11931 -- In_Visible_Part --
11932 ---------------------
11934 function In_Visible_Part (Scope_Id : Entity_Id) return Boolean is
11935 begin
11936 return Is_Package_Or_Generic_Package (Scope_Id)
11937 and then In_Open_Scopes (Scope_Id)
11938 and then not In_Package_Body (Scope_Id)
11939 and then not In_Private_Part (Scope_Id);
11940 end In_Visible_Part;
11942 --------------------------------
11943 -- Incomplete_Or_Partial_View --
11944 --------------------------------
11946 function Incomplete_Or_Partial_View (Id : Entity_Id) return Entity_Id is
11947 function Inspect_Decls
11948 (Decls : List_Id;
11949 Taft : Boolean := False) return Entity_Id;
11950 -- Check whether a declarative region contains the incomplete or partial
11951 -- view of Id.
11953 -------------------
11954 -- Inspect_Decls --
11955 -------------------
11957 function Inspect_Decls
11958 (Decls : List_Id;
11959 Taft : Boolean := False) return Entity_Id
11961 Decl : Node_Id;
11962 Match : Node_Id;
11964 begin
11965 Decl := First (Decls);
11966 while Present (Decl) loop
11967 Match := Empty;
11969 -- The partial view of a Taft-amendment type is an incomplete
11970 -- type.
11972 if Taft then
11973 if Nkind (Decl) = N_Incomplete_Type_Declaration then
11974 Match := Defining_Identifier (Decl);
11975 end if;
11977 -- Otherwise look for a private type whose full view matches the
11978 -- input type. Note that this checks full_type_declaration nodes
11979 -- to account for derivations from a private type where the type
11980 -- declaration hold the partial view and the full view is an
11981 -- itype.
11983 elsif Nkind_In (Decl, N_Full_Type_Declaration,
11984 N_Private_Extension_Declaration,
11985 N_Private_Type_Declaration)
11986 then
11987 Match := Defining_Identifier (Decl);
11988 end if;
11990 -- Guard against unanalyzed entities
11992 if Present (Match)
11993 and then Is_Type (Match)
11994 and then Present (Full_View (Match))
11995 and then Full_View (Match) = Id
11996 then
11997 return Match;
11998 end if;
12000 Next (Decl);
12001 end loop;
12003 return Empty;
12004 end Inspect_Decls;
12006 -- Local variables
12008 Prev : Entity_Id;
12010 -- Start of processing for Incomplete_Or_Partial_View
12012 begin
12013 -- Deferred constant or incomplete type case
12015 Prev := Current_Entity_In_Scope (Id);
12017 if Present (Prev)
12018 and then (Is_Incomplete_Type (Prev) or else Ekind (Prev) = E_Constant)
12019 and then Present (Full_View (Prev))
12020 and then Full_View (Prev) = Id
12021 then
12022 return Prev;
12023 end if;
12025 -- Private or Taft amendment type case
12027 declare
12028 Pkg : constant Entity_Id := Scope (Id);
12029 Pkg_Decl : Node_Id := Pkg;
12031 begin
12032 if Present (Pkg)
12033 and then Ekind_In (Pkg, E_Generic_Package, E_Package)
12034 then
12035 while Nkind (Pkg_Decl) /= N_Package_Specification loop
12036 Pkg_Decl := Parent (Pkg_Decl);
12037 end loop;
12039 -- It is knows that Typ has a private view, look for it in the
12040 -- visible declarations of the enclosing scope. A special case
12041 -- of this is when the two views have been exchanged - the full
12042 -- appears earlier than the private.
12044 if Has_Private_Declaration (Id) then
12045 Prev := Inspect_Decls (Visible_Declarations (Pkg_Decl));
12047 -- Exchanged view case, look in the private declarations
12049 if No (Prev) then
12050 Prev := Inspect_Decls (Private_Declarations (Pkg_Decl));
12051 end if;
12053 return Prev;
12055 -- Otherwise if this is the package body, then Typ is a potential
12056 -- Taft amendment type. The incomplete view should be located in
12057 -- the private declarations of the enclosing scope.
12059 elsif In_Package_Body (Pkg) then
12060 return Inspect_Decls (Private_Declarations (Pkg_Decl), True);
12061 end if;
12062 end if;
12063 end;
12065 -- The type has no incomplete or private view
12067 return Empty;
12068 end Incomplete_Or_Partial_View;
12070 ----------------------------------
12071 -- Indexed_Component_Bit_Offset --
12072 ----------------------------------
12074 function Indexed_Component_Bit_Offset (N : Node_Id) return Uint is
12075 Exp : constant Node_Id := First (Expressions (N));
12076 Typ : constant Entity_Id := Etype (Prefix (N));
12077 Off : constant Uint := Component_Size (Typ);
12078 Ind : Node_Id;
12080 begin
12081 -- Return early if the component size is not known or variable
12083 if Off = No_Uint or else Off < Uint_0 then
12084 return No_Uint;
12085 end if;
12087 -- Deal with the degenerate case of an empty component
12089 if Off = Uint_0 then
12090 return Off;
12091 end if;
12093 -- Check that both the index value and the low bound are known
12095 if not Compile_Time_Known_Value (Exp) then
12096 return No_Uint;
12097 end if;
12099 Ind := First_Index (Typ);
12100 if No (Ind) then
12101 return No_Uint;
12102 end if;
12104 if Nkind (Ind) = N_Subtype_Indication then
12105 Ind := Constraint (Ind);
12107 if Nkind (Ind) = N_Range_Constraint then
12108 Ind := Range_Expression (Ind);
12109 end if;
12110 end if;
12112 if Nkind (Ind) /= N_Range
12113 or else not Compile_Time_Known_Value (Low_Bound (Ind))
12114 then
12115 return No_Uint;
12116 end if;
12118 -- Return the scaled offset
12120 return Off * (Expr_Value (Exp) - Expr_Value (Low_Bound ((Ind))));
12121 end Indexed_Component_Bit_Offset;
12123 ----------------------------
12124 -- Inherit_Rep_Item_Chain --
12125 ----------------------------
12127 procedure Inherit_Rep_Item_Chain (Typ : Entity_Id; From_Typ : Entity_Id) is
12128 Item : Node_Id;
12129 Next_Item : Node_Id;
12131 begin
12132 -- There are several inheritance scenarios to consider depending on
12133 -- whether both types have rep item chains and whether the destination
12134 -- type already inherits part of the source type's rep item chain.
12136 -- 1) The source type lacks a rep item chain
12137 -- From_Typ ---> Empty
12139 -- Typ --------> Item (or Empty)
12141 -- In this case inheritance cannot take place because there are no items
12142 -- to inherit.
12144 -- 2) The destination type lacks a rep item chain
12145 -- From_Typ ---> Item ---> ...
12147 -- Typ --------> Empty
12149 -- Inheritance takes place by setting the First_Rep_Item of the
12150 -- destination type to the First_Rep_Item of the source type.
12151 -- From_Typ ---> Item ---> ...
12152 -- ^
12153 -- Typ -----------+
12155 -- 3.1) Both source and destination types have at least one rep item.
12156 -- The destination type does NOT inherit a rep item from the source
12157 -- type.
12158 -- From_Typ ---> Item ---> Item
12160 -- Typ --------> Item ---> Item
12162 -- Inheritance takes place by setting the Next_Rep_Item of the last item
12163 -- of the destination type to the First_Rep_Item of the source type.
12164 -- From_Typ -------------------> Item ---> Item
12165 -- ^
12166 -- Typ --------> Item ---> Item --+
12168 -- 3.2) Both source and destination types have at least one rep item.
12169 -- The destination type DOES inherit part of the rep item chain of the
12170 -- source type.
12171 -- From_Typ ---> Item ---> Item ---> Item
12172 -- ^
12173 -- Typ --------> Item ------+
12175 -- This rare case arises when the full view of a private extension must
12176 -- inherit the rep item chain from the full view of its parent type and
12177 -- the full view of the parent type contains extra rep items. Currently
12178 -- only invariants may lead to such form of inheritance.
12180 -- type From_Typ is tagged private
12181 -- with Type_Invariant'Class => Item_2;
12183 -- type Typ is new From_Typ with private
12184 -- with Type_Invariant => Item_4;
12186 -- At this point the rep item chains contain the following items
12188 -- From_Typ -----------> Item_2 ---> Item_3
12189 -- ^
12190 -- Typ --------> Item_4 --+
12192 -- The full views of both types may introduce extra invariants
12194 -- type From_Typ is tagged null record
12195 -- with Type_Invariant => Item_1;
12197 -- type Typ is new From_Typ with null record;
12199 -- The full view of Typ would have to inherit any new rep items added to
12200 -- the full view of From_Typ.
12202 -- From_Typ -----------> Item_1 ---> Item_2 ---> Item_3
12203 -- ^
12204 -- Typ --------> Item_4 --+
12206 -- To achieve this form of inheritance, the destination type must first
12207 -- sever the link between its own rep chain and that of the source type,
12208 -- then inheritance 3.1 takes place.
12210 -- Case 1: The source type lacks a rep item chain
12212 if No (First_Rep_Item (From_Typ)) then
12213 return;
12215 -- Case 2: The destination type lacks a rep item chain
12217 elsif No (First_Rep_Item (Typ)) then
12218 Set_First_Rep_Item (Typ, First_Rep_Item (From_Typ));
12220 -- Case 3: Both the source and destination types have at least one rep
12221 -- item. Traverse the rep item chain of the destination type to find the
12222 -- last rep item.
12224 else
12225 Item := Empty;
12226 Next_Item := First_Rep_Item (Typ);
12227 while Present (Next_Item) loop
12229 -- Detect a link between the destination type's rep chain and that
12230 -- of the source type. There are two possibilities:
12232 -- Variant 1
12233 -- Next_Item
12234 -- V
12235 -- From_Typ ---> Item_1 --->
12236 -- ^
12237 -- Typ -----------+
12239 -- Item is Empty
12241 -- Variant 2
12242 -- Next_Item
12243 -- V
12244 -- From_Typ ---> Item_1 ---> Item_2 --->
12245 -- ^
12246 -- Typ --------> Item_3 ------+
12247 -- ^
12248 -- Item
12250 if Has_Rep_Item (From_Typ, Next_Item) then
12251 exit;
12252 end if;
12254 Item := Next_Item;
12255 Next_Item := Next_Rep_Item (Next_Item);
12256 end loop;
12258 -- Inherit the source type's rep item chain
12260 if Present (Item) then
12261 Set_Next_Rep_Item (Item, First_Rep_Item (From_Typ));
12262 else
12263 Set_First_Rep_Item (Typ, First_Rep_Item (From_Typ));
12264 end if;
12265 end if;
12266 end Inherit_Rep_Item_Chain;
12268 ---------------------------------
12269 -- Insert_Explicit_Dereference --
12270 ---------------------------------
12272 procedure Insert_Explicit_Dereference (N : Node_Id) is
12273 New_Prefix : constant Node_Id := Relocate_Node (N);
12274 Ent : Entity_Id := Empty;
12275 Pref : Node_Id;
12276 I : Interp_Index;
12277 It : Interp;
12278 T : Entity_Id;
12280 begin
12281 Save_Interps (N, New_Prefix);
12283 Rewrite (N,
12284 Make_Explicit_Dereference (Sloc (Parent (N)),
12285 Prefix => New_Prefix));
12287 Set_Etype (N, Designated_Type (Etype (New_Prefix)));
12289 if Is_Overloaded (New_Prefix) then
12291 -- The dereference is also overloaded, and its interpretations are
12292 -- the designated types of the interpretations of the original node.
12294 Set_Etype (N, Any_Type);
12296 Get_First_Interp (New_Prefix, I, It);
12297 while Present (It.Nam) loop
12298 T := It.Typ;
12300 if Is_Access_Type (T) then
12301 Add_One_Interp (N, Designated_Type (T), Designated_Type (T));
12302 end if;
12304 Get_Next_Interp (I, It);
12305 end loop;
12307 End_Interp_List;
12309 else
12310 -- Prefix is unambiguous: mark the original prefix (which might
12311 -- Come_From_Source) as a reference, since the new (relocated) one
12312 -- won't be taken into account.
12314 if Is_Entity_Name (New_Prefix) then
12315 Ent := Entity (New_Prefix);
12316 Pref := New_Prefix;
12318 -- For a retrieval of a subcomponent of some composite object,
12319 -- retrieve the ultimate entity if there is one.
12321 elsif Nkind_In (New_Prefix, N_Selected_Component,
12322 N_Indexed_Component)
12323 then
12324 Pref := Prefix (New_Prefix);
12325 while Present (Pref)
12326 and then Nkind_In (Pref, N_Selected_Component,
12327 N_Indexed_Component)
12328 loop
12329 Pref := Prefix (Pref);
12330 end loop;
12332 if Present (Pref) and then Is_Entity_Name (Pref) then
12333 Ent := Entity (Pref);
12334 end if;
12335 end if;
12337 -- Place the reference on the entity node
12339 if Present (Ent) then
12340 Generate_Reference (Ent, Pref);
12341 end if;
12342 end if;
12343 end Insert_Explicit_Dereference;
12345 ------------------------------------------
12346 -- Inspect_Deferred_Constant_Completion --
12347 ------------------------------------------
12349 procedure Inspect_Deferred_Constant_Completion (Decls : List_Id) is
12350 Decl : Node_Id;
12352 begin
12353 Decl := First (Decls);
12354 while Present (Decl) loop
12356 -- Deferred constant signature
12358 if Nkind (Decl) = N_Object_Declaration
12359 and then Constant_Present (Decl)
12360 and then No (Expression (Decl))
12362 -- No need to check internally generated constants
12364 and then Comes_From_Source (Decl)
12366 -- The constant is not completed. A full object declaration or a
12367 -- pragma Import complete a deferred constant.
12369 and then not Has_Completion (Defining_Identifier (Decl))
12370 then
12371 Error_Msg_N
12372 ("constant declaration requires initialization expression",
12373 Defining_Identifier (Decl));
12374 end if;
12376 Decl := Next (Decl);
12377 end loop;
12378 end Inspect_Deferred_Constant_Completion;
12380 -----------------------------
12381 -- Install_Generic_Formals --
12382 -----------------------------
12384 procedure Install_Generic_Formals (Subp_Id : Entity_Id) is
12385 E : Entity_Id;
12387 begin
12388 pragma Assert (Is_Generic_Subprogram (Subp_Id));
12390 E := First_Entity (Subp_Id);
12391 while Present (E) loop
12392 Install_Entity (E);
12393 Next_Entity (E);
12394 end loop;
12395 end Install_Generic_Formals;
12397 ------------------------
12398 -- Install_SPARK_Mode --
12399 ------------------------
12401 procedure Install_SPARK_Mode (Mode : SPARK_Mode_Type; Prag : Node_Id) is
12402 begin
12403 SPARK_Mode := Mode;
12404 SPARK_Mode_Pragma := Prag;
12405 end Install_SPARK_Mode;
12407 -----------------------------
12408 -- Is_Actual_Out_Parameter --
12409 -----------------------------
12411 function Is_Actual_Out_Parameter (N : Node_Id) return Boolean is
12412 Formal : Entity_Id;
12413 Call : Node_Id;
12414 begin
12415 Find_Actual (N, Formal, Call);
12416 return Present (Formal) and then Ekind (Formal) = E_Out_Parameter;
12417 end Is_Actual_Out_Parameter;
12419 -------------------------
12420 -- Is_Actual_Parameter --
12421 -------------------------
12423 function Is_Actual_Parameter (N : Node_Id) return Boolean is
12424 PK : constant Node_Kind := Nkind (Parent (N));
12426 begin
12427 case PK is
12428 when N_Parameter_Association =>
12429 return N = Explicit_Actual_Parameter (Parent (N));
12431 when N_Subprogram_Call =>
12432 return Is_List_Member (N)
12433 and then
12434 List_Containing (N) = Parameter_Associations (Parent (N));
12436 when others =>
12437 return False;
12438 end case;
12439 end Is_Actual_Parameter;
12441 --------------------------------
12442 -- Is_Actual_Tagged_Parameter --
12443 --------------------------------
12445 function Is_Actual_Tagged_Parameter (N : Node_Id) return Boolean is
12446 Formal : Entity_Id;
12447 Call : Node_Id;
12448 begin
12449 Find_Actual (N, Formal, Call);
12450 return Present (Formal) and then Is_Tagged_Type (Etype (Formal));
12451 end Is_Actual_Tagged_Parameter;
12453 ---------------------
12454 -- Is_Aliased_View --
12455 ---------------------
12457 function Is_Aliased_View (Obj : Node_Id) return Boolean is
12458 E : Entity_Id;
12460 begin
12461 if Is_Entity_Name (Obj) then
12462 E := Entity (Obj);
12464 return
12465 (Is_Object (E)
12466 and then
12467 (Is_Aliased (E)
12468 or else (Present (Renamed_Object (E))
12469 and then Is_Aliased_View (Renamed_Object (E)))))
12471 or else ((Is_Formal (E)
12472 or else Ekind_In (E, E_Generic_In_Out_Parameter,
12473 E_Generic_In_Parameter))
12474 and then Is_Tagged_Type (Etype (E)))
12476 or else (Is_Concurrent_Type (E) and then In_Open_Scopes (E))
12478 -- Current instance of type, either directly or as rewritten
12479 -- reference to the current object.
12481 or else (Is_Entity_Name (Original_Node (Obj))
12482 and then Present (Entity (Original_Node (Obj)))
12483 and then Is_Type (Entity (Original_Node (Obj))))
12485 or else (Is_Type (E) and then E = Current_Scope)
12487 or else (Is_Incomplete_Or_Private_Type (E)
12488 and then Full_View (E) = Current_Scope)
12490 -- Ada 2012 AI05-0053: the return object of an extended return
12491 -- statement is aliased if its type is immutably limited.
12493 or else (Is_Return_Object (E)
12494 and then Is_Limited_View (Etype (E)));
12496 elsif Nkind (Obj) = N_Selected_Component then
12497 return Is_Aliased (Entity (Selector_Name (Obj)));
12499 elsif Nkind (Obj) = N_Indexed_Component then
12500 return Has_Aliased_Components (Etype (Prefix (Obj)))
12501 or else
12502 (Is_Access_Type (Etype (Prefix (Obj)))
12503 and then Has_Aliased_Components
12504 (Designated_Type (Etype (Prefix (Obj)))));
12506 elsif Nkind_In (Obj, N_Unchecked_Type_Conversion, N_Type_Conversion) then
12507 return Is_Tagged_Type (Etype (Obj))
12508 and then Is_Aliased_View (Expression (Obj));
12510 elsif Nkind (Obj) = N_Explicit_Dereference then
12511 return Nkind (Original_Node (Obj)) /= N_Function_Call;
12513 else
12514 return False;
12515 end if;
12516 end Is_Aliased_View;
12518 -------------------------
12519 -- Is_Ancestor_Package --
12520 -------------------------
12522 function Is_Ancestor_Package
12523 (E1 : Entity_Id;
12524 E2 : Entity_Id) return Boolean
12526 Par : Entity_Id;
12528 begin
12529 Par := E2;
12530 while Present (Par) and then Par /= Standard_Standard loop
12531 if Par = E1 then
12532 return True;
12533 end if;
12535 Par := Scope (Par);
12536 end loop;
12538 return False;
12539 end Is_Ancestor_Package;
12541 ----------------------
12542 -- Is_Atomic_Object --
12543 ----------------------
12545 function Is_Atomic_Object (N : Node_Id) return Boolean is
12547 function Object_Has_Atomic_Components (N : Node_Id) return Boolean;
12548 -- Determines if given object has atomic components
12550 function Is_Atomic_Prefix (N : Node_Id) return Boolean;
12551 -- If prefix is an implicit dereference, examine designated type
12553 ----------------------
12554 -- Is_Atomic_Prefix --
12555 ----------------------
12557 function Is_Atomic_Prefix (N : Node_Id) return Boolean is
12558 begin
12559 if Is_Access_Type (Etype (N)) then
12560 return
12561 Has_Atomic_Components (Designated_Type (Etype (N)));
12562 else
12563 return Object_Has_Atomic_Components (N);
12564 end if;
12565 end Is_Atomic_Prefix;
12567 ----------------------------------
12568 -- Object_Has_Atomic_Components --
12569 ----------------------------------
12571 function Object_Has_Atomic_Components (N : Node_Id) return Boolean is
12572 begin
12573 if Has_Atomic_Components (Etype (N))
12574 or else Is_Atomic (Etype (N))
12575 then
12576 return True;
12578 elsif Is_Entity_Name (N)
12579 and then (Has_Atomic_Components (Entity (N))
12580 or else Is_Atomic (Entity (N)))
12581 then
12582 return True;
12584 elsif Nkind (N) = N_Selected_Component
12585 and then Is_Atomic (Entity (Selector_Name (N)))
12586 then
12587 return True;
12589 elsif Nkind (N) = N_Indexed_Component
12590 or else Nkind (N) = N_Selected_Component
12591 then
12592 return Is_Atomic_Prefix (Prefix (N));
12594 else
12595 return False;
12596 end if;
12597 end Object_Has_Atomic_Components;
12599 -- Start of processing for Is_Atomic_Object
12601 begin
12602 -- Predicate is not relevant to subprograms
12604 if Is_Entity_Name (N) and then Is_Overloadable (Entity (N)) then
12605 return False;
12607 elsif Is_Atomic (Etype (N))
12608 or else (Is_Entity_Name (N) and then Is_Atomic (Entity (N)))
12609 then
12610 return True;
12612 elsif Nkind (N) = N_Selected_Component
12613 and then Is_Atomic (Entity (Selector_Name (N)))
12614 then
12615 return True;
12617 elsif Nkind (N) = N_Indexed_Component
12618 or else Nkind (N) = N_Selected_Component
12619 then
12620 return Is_Atomic_Prefix (Prefix (N));
12622 else
12623 return False;
12624 end if;
12625 end Is_Atomic_Object;
12627 -----------------------------
12628 -- Is_Atomic_Or_VFA_Object --
12629 -----------------------------
12631 function Is_Atomic_Or_VFA_Object (N : Node_Id) return Boolean is
12632 begin
12633 return Is_Atomic_Object (N)
12634 or else (Is_Object_Reference (N)
12635 and then Is_Entity_Name (N)
12636 and then (Is_Volatile_Full_Access (Entity (N))
12637 or else
12638 Is_Volatile_Full_Access (Etype (Entity (N)))));
12639 end Is_Atomic_Or_VFA_Object;
12641 -------------------------
12642 -- Is_Attribute_Result --
12643 -------------------------
12645 function Is_Attribute_Result (N : Node_Id) return Boolean is
12646 begin
12647 return Nkind (N) = N_Attribute_Reference
12648 and then Attribute_Name (N) = Name_Result;
12649 end Is_Attribute_Result;
12651 -------------------------
12652 -- Is_Attribute_Update --
12653 -------------------------
12655 function Is_Attribute_Update (N : Node_Id) return Boolean is
12656 begin
12657 return Nkind (N) = N_Attribute_Reference
12658 and then Attribute_Name (N) = Name_Update;
12659 end Is_Attribute_Update;
12661 ------------------------------------
12662 -- Is_Body_Or_Package_Declaration --
12663 ------------------------------------
12665 function Is_Body_Or_Package_Declaration (N : Node_Id) return Boolean is
12666 begin
12667 return Nkind_In (N, N_Entry_Body,
12668 N_Package_Body,
12669 N_Package_Declaration,
12670 N_Protected_Body,
12671 N_Subprogram_Body,
12672 N_Task_Body);
12673 end Is_Body_Or_Package_Declaration;
12675 -----------------------
12676 -- Is_Bounded_String --
12677 -----------------------
12679 function Is_Bounded_String (T : Entity_Id) return Boolean is
12680 Under : constant Entity_Id := Underlying_Type (Root_Type (T));
12682 begin
12683 -- Check whether T is ultimately derived from Ada.Strings.Superbounded.
12684 -- Super_String, or one of the [Wide_]Wide_ versions. This will
12685 -- be True for all the Bounded_String types in instances of the
12686 -- Generic_Bounded_Length generics, and for types derived from those.
12688 return Present (Under)
12689 and then (Is_RTE (Root_Type (Under), RO_SU_Super_String) or else
12690 Is_RTE (Root_Type (Under), RO_WI_Super_String) or else
12691 Is_RTE (Root_Type (Under), RO_WW_Super_String));
12692 end Is_Bounded_String;
12694 ---------------------
12695 -- Is_CCT_Instance --
12696 ---------------------
12698 function Is_CCT_Instance
12699 (Ref_Id : Entity_Id;
12700 Context_Id : Entity_Id) return Boolean
12702 begin
12703 pragma Assert (Ekind_In (Ref_Id, E_Protected_Type, E_Task_Type));
12705 if Is_Single_Task_Object (Context_Id) then
12706 return Scope_Within_Or_Same (Etype (Context_Id), Ref_Id);
12708 else
12709 pragma Assert (Ekind_In (Context_Id, E_Entry,
12710 E_Entry_Family,
12711 E_Function,
12712 E_Package,
12713 E_Procedure,
12714 E_Protected_Type,
12715 E_Task_Type));
12717 return Scope_Within_Or_Same (Context_Id, Ref_Id);
12718 end if;
12719 end Is_CCT_Instance;
12721 -------------------------
12722 -- Is_Child_Or_Sibling --
12723 -------------------------
12725 function Is_Child_Or_Sibling
12726 (Pack_1 : Entity_Id;
12727 Pack_2 : Entity_Id) return Boolean
12729 function Distance_From_Standard (Pack : Entity_Id) return Nat;
12730 -- Given an arbitrary package, return the number of "climbs" necessary
12731 -- to reach scope Standard_Standard.
12733 procedure Equalize_Depths
12734 (Pack : in out Entity_Id;
12735 Depth : in out Nat;
12736 Depth_To_Reach : Nat);
12737 -- Given an arbitrary package, its depth and a target depth to reach,
12738 -- climb the scope chain until the said depth is reached. The pointer
12739 -- to the package and its depth a modified during the climb.
12741 ----------------------------
12742 -- Distance_From_Standard --
12743 ----------------------------
12745 function Distance_From_Standard (Pack : Entity_Id) return Nat is
12746 Dist : Nat;
12747 Scop : Entity_Id;
12749 begin
12750 Dist := 0;
12751 Scop := Pack;
12752 while Present (Scop) and then Scop /= Standard_Standard loop
12753 Dist := Dist + 1;
12754 Scop := Scope (Scop);
12755 end loop;
12757 return Dist;
12758 end Distance_From_Standard;
12760 ---------------------
12761 -- Equalize_Depths --
12762 ---------------------
12764 procedure Equalize_Depths
12765 (Pack : in out Entity_Id;
12766 Depth : in out Nat;
12767 Depth_To_Reach : Nat)
12769 begin
12770 -- The package must be at a greater or equal depth
12772 if Depth < Depth_To_Reach then
12773 raise Program_Error;
12774 end if;
12776 -- Climb the scope chain until the desired depth is reached
12778 while Present (Pack) and then Depth /= Depth_To_Reach loop
12779 Pack := Scope (Pack);
12780 Depth := Depth - 1;
12781 end loop;
12782 end Equalize_Depths;
12784 -- Local variables
12786 P_1 : Entity_Id := Pack_1;
12787 P_1_Child : Boolean := False;
12788 P_1_Depth : Nat := Distance_From_Standard (P_1);
12789 P_2 : Entity_Id := Pack_2;
12790 P_2_Child : Boolean := False;
12791 P_2_Depth : Nat := Distance_From_Standard (P_2);
12793 -- Start of processing for Is_Child_Or_Sibling
12795 begin
12796 pragma Assert
12797 (Ekind (Pack_1) = E_Package and then Ekind (Pack_2) = E_Package);
12799 -- Both packages denote the same entity, therefore they cannot be
12800 -- children or siblings.
12802 if P_1 = P_2 then
12803 return False;
12805 -- One of the packages is at a deeper level than the other. Note that
12806 -- both may still come from different hierarchies.
12808 -- (root) P_2
12809 -- / \ :
12810 -- X P_2 or X
12811 -- : :
12812 -- P_1 P_1
12814 elsif P_1_Depth > P_2_Depth then
12815 Equalize_Depths
12816 (Pack => P_1,
12817 Depth => P_1_Depth,
12818 Depth_To_Reach => P_2_Depth);
12819 P_1_Child := True;
12821 -- (root) P_1
12822 -- / \ :
12823 -- P_1 X or X
12824 -- : :
12825 -- P_2 P_2
12827 elsif P_2_Depth > P_1_Depth then
12828 Equalize_Depths
12829 (Pack => P_2,
12830 Depth => P_2_Depth,
12831 Depth_To_Reach => P_1_Depth);
12832 P_2_Child := True;
12833 end if;
12835 -- At this stage the package pointers have been elevated to the same
12836 -- depth. If the related entities are the same, then one package is a
12837 -- potential child of the other:
12839 -- P_1
12840 -- :
12841 -- X became P_1 P_2 or vice versa
12842 -- :
12843 -- P_2
12845 if P_1 = P_2 then
12846 if P_1_Child then
12847 return Is_Child_Unit (Pack_1);
12849 else pragma Assert (P_2_Child);
12850 return Is_Child_Unit (Pack_2);
12851 end if;
12853 -- The packages may come from the same package chain or from entirely
12854 -- different hierarcies. To determine this, climb the scope stack until
12855 -- a common root is found.
12857 -- (root) (root 1) (root 2)
12858 -- / \ | |
12859 -- P_1 P_2 P_1 P_2
12861 else
12862 while Present (P_1) and then Present (P_2) loop
12864 -- The two packages may be siblings
12866 if P_1 = P_2 then
12867 return Is_Child_Unit (Pack_1) and then Is_Child_Unit (Pack_2);
12868 end if;
12870 P_1 := Scope (P_1);
12871 P_2 := Scope (P_2);
12872 end loop;
12873 end if;
12875 return False;
12876 end Is_Child_Or_Sibling;
12878 -----------------------------
12879 -- Is_Concurrent_Interface --
12880 -----------------------------
12882 function Is_Concurrent_Interface (T : Entity_Id) return Boolean is
12883 begin
12884 return Is_Interface (T)
12885 and then
12886 (Is_Protected_Interface (T)
12887 or else Is_Synchronized_Interface (T)
12888 or else Is_Task_Interface (T));
12889 end Is_Concurrent_Interface;
12891 -----------------------
12892 -- Is_Constant_Bound --
12893 -----------------------
12895 function Is_Constant_Bound (Exp : Node_Id) return Boolean is
12896 begin
12897 if Compile_Time_Known_Value (Exp) then
12898 return True;
12900 elsif Is_Entity_Name (Exp) and then Present (Entity (Exp)) then
12901 return Is_Constant_Object (Entity (Exp))
12902 or else Ekind (Entity (Exp)) = E_Enumeration_Literal;
12904 elsif Nkind (Exp) in N_Binary_Op then
12905 return Is_Constant_Bound (Left_Opnd (Exp))
12906 and then Is_Constant_Bound (Right_Opnd (Exp))
12907 and then Scope (Entity (Exp)) = Standard_Standard;
12909 else
12910 return False;
12911 end if;
12912 end Is_Constant_Bound;
12914 ---------------------------
12915 -- Is_Container_Element --
12916 ---------------------------
12918 function Is_Container_Element (Exp : Node_Id) return Boolean is
12919 Loc : constant Source_Ptr := Sloc (Exp);
12920 Pref : constant Node_Id := Prefix (Exp);
12922 Call : Node_Id;
12923 -- Call to an indexing aspect
12925 Cont_Typ : Entity_Id;
12926 -- The type of the container being accessed
12928 Elem_Typ : Entity_Id;
12929 -- Its element type
12931 Indexing : Entity_Id;
12932 Is_Const : Boolean;
12933 -- Indicates that constant indexing is used, and the element is thus
12934 -- a constant.
12936 Ref_Typ : Entity_Id;
12937 -- The reference type returned by the indexing operation
12939 begin
12940 -- If C is a container, in a context that imposes the element type of
12941 -- that container, the indexing notation C (X) is rewritten as:
12943 -- Indexing (C, X).Discr.all
12945 -- where Indexing is one of the indexing aspects of the container.
12946 -- If the context does not require a reference, the construct can be
12947 -- rewritten as
12949 -- Element (C, X)
12951 -- First, verify that the construct has the proper form
12953 if not Expander_Active then
12954 return False;
12956 elsif Nkind (Pref) /= N_Selected_Component then
12957 return False;
12959 elsif Nkind (Prefix (Pref)) /= N_Function_Call then
12960 return False;
12962 else
12963 Call := Prefix (Pref);
12964 Ref_Typ := Etype (Call);
12965 end if;
12967 if not Has_Implicit_Dereference (Ref_Typ)
12968 or else No (First (Parameter_Associations (Call)))
12969 or else not Is_Entity_Name (Name (Call))
12970 then
12971 return False;
12972 end if;
12974 -- Retrieve type of container object, and its iterator aspects
12976 Cont_Typ := Etype (First (Parameter_Associations (Call)));
12977 Indexing := Find_Value_Of_Aspect (Cont_Typ, Aspect_Constant_Indexing);
12978 Is_Const := False;
12980 if No (Indexing) then
12982 -- Container should have at least one indexing operation
12984 return False;
12986 elsif Entity (Name (Call)) /= Entity (Indexing) then
12988 -- This may be a variable indexing operation
12990 Indexing := Find_Value_Of_Aspect (Cont_Typ, Aspect_Variable_Indexing);
12992 if No (Indexing)
12993 or else Entity (Name (Call)) /= Entity (Indexing)
12994 then
12995 return False;
12996 end if;
12998 else
12999 Is_Const := True;
13000 end if;
13002 Elem_Typ := Find_Value_Of_Aspect (Cont_Typ, Aspect_Iterator_Element);
13004 if No (Elem_Typ) or else Entity (Elem_Typ) /= Etype (Exp) then
13005 return False;
13006 end if;
13008 -- Check that the expression is not the target of an assignment, in
13009 -- which case the rewriting is not possible.
13011 if not Is_Const then
13012 declare
13013 Par : Node_Id;
13015 begin
13016 Par := Exp;
13017 while Present (Par)
13018 loop
13019 if Nkind (Parent (Par)) = N_Assignment_Statement
13020 and then Par = Name (Parent (Par))
13021 then
13022 return False;
13024 -- A renaming produces a reference, and the transformation
13025 -- does not apply.
13027 elsif Nkind (Parent (Par)) = N_Object_Renaming_Declaration then
13028 return False;
13030 elsif Nkind_In
13031 (Nkind (Parent (Par)), N_Function_Call,
13032 N_Procedure_Call_Statement,
13033 N_Entry_Call_Statement)
13034 then
13035 -- Check that the element is not part of an actual for an
13036 -- in-out parameter.
13038 declare
13039 F : Entity_Id;
13040 A : Node_Id;
13042 begin
13043 F := First_Formal (Entity (Name (Parent (Par))));
13044 A := First (Parameter_Associations (Parent (Par)));
13045 while Present (F) loop
13046 if A = Par and then Ekind (F) /= E_In_Parameter then
13047 return False;
13048 end if;
13050 Next_Formal (F);
13051 Next (A);
13052 end loop;
13053 end;
13055 -- E_In_Parameter in a call: element is not modified.
13057 exit;
13058 end if;
13060 Par := Parent (Par);
13061 end loop;
13062 end;
13063 end if;
13065 -- The expression has the proper form and the context requires the
13066 -- element type. Retrieve the Element function of the container and
13067 -- rewrite the construct as a call to it.
13069 declare
13070 Op : Elmt_Id;
13072 begin
13073 Op := First_Elmt (Primitive_Operations (Cont_Typ));
13074 while Present (Op) loop
13075 exit when Chars (Node (Op)) = Name_Element;
13076 Next_Elmt (Op);
13077 end loop;
13079 if No (Op) then
13080 return False;
13082 else
13083 Rewrite (Exp,
13084 Make_Function_Call (Loc,
13085 Name => New_Occurrence_Of (Node (Op), Loc),
13086 Parameter_Associations => Parameter_Associations (Call)));
13087 Analyze_And_Resolve (Exp, Entity (Elem_Typ));
13088 return True;
13089 end if;
13090 end;
13091 end Is_Container_Element;
13093 ----------------------------
13094 -- Is_Contract_Annotation --
13095 ----------------------------
13097 function Is_Contract_Annotation (Item : Node_Id) return Boolean is
13098 begin
13099 return Is_Package_Contract_Annotation (Item)
13100 or else
13101 Is_Subprogram_Contract_Annotation (Item);
13102 end Is_Contract_Annotation;
13104 --------------------------------------
13105 -- Is_Controlling_Limited_Procedure --
13106 --------------------------------------
13108 function Is_Controlling_Limited_Procedure
13109 (Proc_Nam : Entity_Id) return Boolean
13111 Param_Typ : Entity_Id := Empty;
13113 begin
13114 if Ekind (Proc_Nam) = E_Procedure
13115 and then Present (Parameter_Specifications (Parent (Proc_Nam)))
13116 then
13117 Param_Typ := Etype (Parameter_Type (First (
13118 Parameter_Specifications (Parent (Proc_Nam)))));
13120 -- In this case where an Itype was created, the procedure call has been
13121 -- rewritten.
13123 elsif Present (Associated_Node_For_Itype (Proc_Nam))
13124 and then Present (Original_Node (Associated_Node_For_Itype (Proc_Nam)))
13125 and then
13126 Present (Parameter_Associations
13127 (Associated_Node_For_Itype (Proc_Nam)))
13128 then
13129 Param_Typ :=
13130 Etype (First (Parameter_Associations
13131 (Associated_Node_For_Itype (Proc_Nam))));
13132 end if;
13134 if Present (Param_Typ) then
13135 return
13136 Is_Interface (Param_Typ)
13137 and then Is_Limited_Record (Param_Typ);
13138 end if;
13140 return False;
13141 end Is_Controlling_Limited_Procedure;
13143 -----------------------------
13144 -- Is_CPP_Constructor_Call --
13145 -----------------------------
13147 function Is_CPP_Constructor_Call (N : Node_Id) return Boolean is
13148 begin
13149 return Nkind (N) = N_Function_Call
13150 and then Is_CPP_Class (Etype (Etype (N)))
13151 and then Is_Constructor (Entity (Name (N)))
13152 and then Is_Imported (Entity (Name (N)));
13153 end Is_CPP_Constructor_Call;
13155 -------------------------
13156 -- Is_Current_Instance --
13157 -------------------------
13159 function Is_Current_Instance (N : Node_Id) return Boolean is
13160 Typ : constant Entity_Id := Entity (N);
13161 P : Node_Id;
13163 begin
13164 -- Simplest case: entity is a concurrent type and we are currently
13165 -- inside the body. This will eventually be expanded into a
13166 -- call to Self (for tasks) or _object (for protected objects).
13168 if Is_Concurrent_Type (Typ) and then In_Open_Scopes (Typ) then
13169 return True;
13171 else
13172 -- Check whether the context is a (sub)type declaration for the
13173 -- type entity.
13175 P := Parent (N);
13176 while Present (P) loop
13177 if Nkind_In (P, N_Full_Type_Declaration,
13178 N_Private_Type_Declaration,
13179 N_Subtype_Declaration)
13180 and then Comes_From_Source (P)
13181 and then Defining_Entity (P) = Typ
13182 then
13183 return True;
13185 -- A subtype name may appear in an aspect specification for a
13186 -- Predicate_Failure aspect, for which we do not construct a
13187 -- wrapper procedure. The subtype will be replaced by the
13188 -- expression being tested when the corresponding predicate
13189 -- check is expanded.
13191 elsif Nkind (P) = N_Aspect_Specification
13192 and then Nkind (Parent (P)) = N_Subtype_Declaration
13193 then
13194 return True;
13196 elsif Nkind (P) = N_Pragma
13197 and then
13198 Get_Pragma_Id (P) = Pragma_Predicate_Failure
13199 then
13200 return True;
13201 end if;
13203 P := Parent (P);
13204 end loop;
13205 end if;
13207 -- In any other context this is not a current occurrence
13209 return False;
13210 end Is_Current_Instance;
13212 --------------------
13213 -- Is_Declaration --
13214 --------------------
13216 function Is_Declaration (N : Node_Id) return Boolean is
13217 begin
13218 return
13219 Is_Declaration_Other_Than_Renaming (N)
13220 or else Is_Renaming_Declaration (N);
13221 end Is_Declaration;
13223 ----------------------------------------
13224 -- Is_Declaration_Other_Than_Renaming --
13225 ----------------------------------------
13227 function Is_Declaration_Other_Than_Renaming (N : Node_Id) return Boolean is
13228 begin
13229 case Nkind (N) is
13230 when N_Abstract_Subprogram_Declaration
13231 | N_Exception_Declaration
13232 | N_Expression_Function
13233 | N_Full_Type_Declaration
13234 | N_Generic_Package_Declaration
13235 | N_Generic_Subprogram_Declaration
13236 | N_Number_Declaration
13237 | N_Object_Declaration
13238 | N_Package_Declaration
13239 | N_Private_Extension_Declaration
13240 | N_Private_Type_Declaration
13241 | N_Subprogram_Declaration
13242 | N_Subtype_Declaration
13244 return True;
13246 when others =>
13247 return False;
13248 end case;
13249 end Is_Declaration_Other_Than_Renaming;
13251 --------------------------------
13252 -- Is_Declared_Within_Variant --
13253 --------------------------------
13255 function Is_Declared_Within_Variant (Comp : Entity_Id) return Boolean is
13256 Comp_Decl : constant Node_Id := Parent (Comp);
13257 Comp_List : constant Node_Id := Parent (Comp_Decl);
13258 begin
13259 return Nkind (Parent (Comp_List)) = N_Variant;
13260 end Is_Declared_Within_Variant;
13262 ----------------------------------------------
13263 -- Is_Dependent_Component_Of_Mutable_Object --
13264 ----------------------------------------------
13266 function Is_Dependent_Component_Of_Mutable_Object
13267 (Object : Node_Id) return Boolean
13269 P : Node_Id;
13270 Prefix_Type : Entity_Id;
13271 P_Aliased : Boolean := False;
13272 Comp : Entity_Id;
13274 Deref : Node_Id := Object;
13275 -- Dereference node, in something like X.all.Y(2)
13277 -- Start of processing for Is_Dependent_Component_Of_Mutable_Object
13279 begin
13280 -- Find the dereference node if any
13282 while Nkind_In (Deref, N_Indexed_Component,
13283 N_Selected_Component,
13284 N_Slice)
13285 loop
13286 Deref := Prefix (Deref);
13287 end loop;
13289 -- Ada 2005: If we have a component or slice of a dereference,
13290 -- something like X.all.Y (2), and the type of X is access-to-constant,
13291 -- Is_Variable will return False, because it is indeed a constant
13292 -- view. But it might be a view of a variable object, so we want the
13293 -- following condition to be True in that case.
13295 if Is_Variable (Object)
13296 or else (Ada_Version >= Ada_2005
13297 and then Nkind (Deref) = N_Explicit_Dereference)
13298 then
13299 if Nkind (Object) = N_Selected_Component then
13300 P := Prefix (Object);
13301 Prefix_Type := Etype (P);
13303 if Is_Entity_Name (P) then
13304 if Ekind (Entity (P)) = E_Generic_In_Out_Parameter then
13305 Prefix_Type := Base_Type (Prefix_Type);
13306 end if;
13308 if Is_Aliased (Entity (P)) then
13309 P_Aliased := True;
13310 end if;
13312 -- A discriminant check on a selected component may be expanded
13313 -- into a dereference when removing side-effects. Recover the
13314 -- original node and its type, which may be unconstrained.
13316 elsif Nkind (P) = N_Explicit_Dereference
13317 and then not (Comes_From_Source (P))
13318 then
13319 P := Original_Node (P);
13320 Prefix_Type := Etype (P);
13322 else
13323 -- Check for prefix being an aliased component???
13325 null;
13327 end if;
13329 -- A heap object is constrained by its initial value
13331 -- Ada 2005 (AI-363): Always assume the object could be mutable in
13332 -- the dereferenced case, since the access value might denote an
13333 -- unconstrained aliased object, whereas in Ada 95 the designated
13334 -- object is guaranteed to be constrained. A worst-case assumption
13335 -- has to apply in Ada 2005 because we can't tell at compile
13336 -- time whether the object is "constrained by its initial value",
13337 -- despite the fact that 3.10.2(26/2) and 8.5.1(5/2) are semantic
13338 -- rules (these rules are acknowledged to need fixing). We don't
13339 -- impose this more stringent checking for earlier Ada versions or
13340 -- when Relaxed_RM_Semantics applies (the latter for CodePeer's
13341 -- benefit, though it's unclear on why using -gnat95 would not be
13342 -- sufficient???).
13344 if Ada_Version < Ada_2005 or else Relaxed_RM_Semantics then
13345 if Is_Access_Type (Prefix_Type)
13346 or else Nkind (P) = N_Explicit_Dereference
13347 then
13348 return False;
13349 end if;
13351 else pragma Assert (Ada_Version >= Ada_2005);
13352 if Is_Access_Type (Prefix_Type) then
13354 -- If the access type is pool-specific, and there is no
13355 -- constrained partial view of the designated type, then the
13356 -- designated object is known to be constrained.
13358 if Ekind (Prefix_Type) = E_Access_Type
13359 and then not Object_Type_Has_Constrained_Partial_View
13360 (Typ => Designated_Type (Prefix_Type),
13361 Scop => Current_Scope)
13362 then
13363 return False;
13365 -- Otherwise (general access type, or there is a constrained
13366 -- partial view of the designated type), we need to check
13367 -- based on the designated type.
13369 else
13370 Prefix_Type := Designated_Type (Prefix_Type);
13371 end if;
13372 end if;
13373 end if;
13375 Comp :=
13376 Original_Record_Component (Entity (Selector_Name (Object)));
13378 -- As per AI-0017, the renaming is illegal in a generic body, even
13379 -- if the subtype is indefinite.
13381 -- Ada 2005 (AI-363): In Ada 2005 an aliased object can be mutable
13383 if not Is_Constrained (Prefix_Type)
13384 and then (Is_Definite_Subtype (Prefix_Type)
13385 or else
13386 (Is_Generic_Type (Prefix_Type)
13387 and then Ekind (Current_Scope) = E_Generic_Package
13388 and then In_Package_Body (Current_Scope)))
13390 and then (Is_Declared_Within_Variant (Comp)
13391 or else Has_Discriminant_Dependent_Constraint (Comp))
13392 and then (not P_Aliased or else Ada_Version >= Ada_2005)
13393 then
13394 return True;
13396 -- If the prefix is of an access type at this point, then we want
13397 -- to return False, rather than calling this function recursively
13398 -- on the access object (which itself might be a discriminant-
13399 -- dependent component of some other object, but that isn't
13400 -- relevant to checking the object passed to us). This avoids
13401 -- issuing wrong errors when compiling with -gnatc, where there
13402 -- can be implicit dereferences that have not been expanded.
13404 elsif Is_Access_Type (Etype (Prefix (Object))) then
13405 return False;
13407 else
13408 return
13409 Is_Dependent_Component_Of_Mutable_Object (Prefix (Object));
13410 end if;
13412 elsif Nkind (Object) = N_Indexed_Component
13413 or else Nkind (Object) = N_Slice
13414 then
13415 return Is_Dependent_Component_Of_Mutable_Object (Prefix (Object));
13417 -- A type conversion that Is_Variable is a view conversion:
13418 -- go back to the denoted object.
13420 elsif Nkind (Object) = N_Type_Conversion then
13421 return
13422 Is_Dependent_Component_Of_Mutable_Object (Expression (Object));
13423 end if;
13424 end if;
13426 return False;
13427 end Is_Dependent_Component_Of_Mutable_Object;
13429 ---------------------
13430 -- Is_Dereferenced --
13431 ---------------------
13433 function Is_Dereferenced (N : Node_Id) return Boolean is
13434 P : constant Node_Id := Parent (N);
13435 begin
13436 return Nkind_In (P, N_Selected_Component,
13437 N_Explicit_Dereference,
13438 N_Indexed_Component,
13439 N_Slice)
13440 and then Prefix (P) = N;
13441 end Is_Dereferenced;
13443 ----------------------
13444 -- Is_Descendant_Of --
13445 ----------------------
13447 function Is_Descendant_Of (T1 : Entity_Id; T2 : Entity_Id) return Boolean is
13448 T : Entity_Id;
13449 Etyp : Entity_Id;
13451 begin
13452 pragma Assert (Nkind (T1) in N_Entity);
13453 pragma Assert (Nkind (T2) in N_Entity);
13455 T := Base_Type (T1);
13457 -- Immediate return if the types match
13459 if T = T2 then
13460 return True;
13462 -- Comment needed here ???
13464 elsif Ekind (T) = E_Class_Wide_Type then
13465 return Etype (T) = T2;
13467 -- All other cases
13469 else
13470 loop
13471 Etyp := Etype (T);
13473 -- Done if we found the type we are looking for
13475 if Etyp = T2 then
13476 return True;
13478 -- Done if no more derivations to check
13480 elsif T = T1
13481 or else T = Etyp
13482 then
13483 return False;
13485 -- Following test catches error cases resulting from prev errors
13487 elsif No (Etyp) then
13488 return False;
13490 elsif Is_Private_Type (T) and then Etyp = Full_View (T) then
13491 return False;
13493 elsif Is_Private_Type (Etyp) and then Full_View (Etyp) = T then
13494 return False;
13495 end if;
13497 T := Base_Type (Etyp);
13498 end loop;
13499 end if;
13500 end Is_Descendant_Of;
13502 ----------------------------------------
13503 -- Is_Descendant_Of_Suspension_Object --
13504 ----------------------------------------
13506 function Is_Descendant_Of_Suspension_Object
13507 (Typ : Entity_Id) return Boolean
13509 Cur_Typ : Entity_Id;
13510 Par_Typ : Entity_Id;
13512 begin
13513 -- Climb the type derivation chain checking each parent type against
13514 -- Suspension_Object.
13516 Cur_Typ := Base_Type (Typ);
13517 while Present (Cur_Typ) loop
13518 Par_Typ := Etype (Cur_Typ);
13520 -- The current type is a match
13522 if Is_Suspension_Object (Cur_Typ) then
13523 return True;
13525 -- Stop the traversal once the root of the derivation chain has been
13526 -- reached. In that case the current type is its own base type.
13528 elsif Cur_Typ = Par_Typ then
13529 exit;
13530 end if;
13532 Cur_Typ := Base_Type (Par_Typ);
13533 end loop;
13535 return False;
13536 end Is_Descendant_Of_Suspension_Object;
13538 ---------------------------------------------
13539 -- Is_Double_Precision_Floating_Point_Type --
13540 ---------------------------------------------
13542 function Is_Double_Precision_Floating_Point_Type
13543 (E : Entity_Id) return Boolean is
13544 begin
13545 return Is_Floating_Point_Type (E)
13546 and then Machine_Radix_Value (E) = Uint_2
13547 and then Machine_Mantissa_Value (E) = UI_From_Int (53)
13548 and then Machine_Emax_Value (E) = Uint_2 ** Uint_10
13549 and then Machine_Emin_Value (E) = Uint_3 - (Uint_2 ** Uint_10);
13550 end Is_Double_Precision_Floating_Point_Type;
13552 -----------------------------
13553 -- Is_Effectively_Volatile --
13554 -----------------------------
13556 function Is_Effectively_Volatile (Id : Entity_Id) return Boolean is
13557 begin
13558 if Is_Type (Id) then
13560 -- An arbitrary type is effectively volatile when it is subject to
13561 -- pragma Atomic or Volatile.
13563 if Is_Volatile (Id) then
13564 return True;
13566 -- An array type is effectively volatile when it is subject to pragma
13567 -- Atomic_Components or Volatile_Components or its component type is
13568 -- effectively volatile.
13570 elsif Is_Array_Type (Id) then
13571 declare
13572 Anc : Entity_Id := Base_Type (Id);
13573 begin
13574 if Is_Private_Type (Anc) then
13575 Anc := Full_View (Anc);
13576 end if;
13578 -- Test for presence of ancestor, as the full view of a private
13579 -- type may be missing in case of error.
13581 return
13582 Has_Volatile_Components (Id)
13583 or else
13584 (Present (Anc)
13585 and then Is_Effectively_Volatile (Component_Type (Anc)));
13586 end;
13588 -- A protected type is always volatile
13590 elsif Is_Protected_Type (Id) then
13591 return True;
13593 -- A descendant of Ada.Synchronous_Task_Control.Suspension_Object is
13594 -- automatically volatile.
13596 elsif Is_Descendant_Of_Suspension_Object (Id) then
13597 return True;
13599 -- Otherwise the type is not effectively volatile
13601 else
13602 return False;
13603 end if;
13605 -- Otherwise Id denotes an object
13607 else
13608 return
13609 Is_Volatile (Id)
13610 or else Has_Volatile_Components (Id)
13611 or else Is_Effectively_Volatile (Etype (Id));
13612 end if;
13613 end Is_Effectively_Volatile;
13615 ------------------------------------
13616 -- Is_Effectively_Volatile_Object --
13617 ------------------------------------
13619 function Is_Effectively_Volatile_Object (N : Node_Id) return Boolean is
13620 begin
13621 if Is_Entity_Name (N) then
13622 return Is_Effectively_Volatile (Entity (N));
13624 elsif Nkind (N) = N_Indexed_Component then
13625 return Is_Effectively_Volatile_Object (Prefix (N));
13627 elsif Nkind (N) = N_Selected_Component then
13628 return
13629 Is_Effectively_Volatile_Object (Prefix (N))
13630 or else
13631 Is_Effectively_Volatile_Object (Selector_Name (N));
13633 else
13634 return False;
13635 end if;
13636 end Is_Effectively_Volatile_Object;
13638 -------------------
13639 -- Is_Entry_Body --
13640 -------------------
13642 function Is_Entry_Body (Id : Entity_Id) return Boolean is
13643 begin
13644 return
13645 Ekind_In (Id, E_Entry, E_Entry_Family)
13646 and then Nkind (Unit_Declaration_Node (Id)) = N_Entry_Body;
13647 end Is_Entry_Body;
13649 --------------------------
13650 -- Is_Entry_Declaration --
13651 --------------------------
13653 function Is_Entry_Declaration (Id : Entity_Id) return Boolean is
13654 begin
13655 return
13656 Ekind_In (Id, E_Entry, E_Entry_Family)
13657 and then Nkind (Unit_Declaration_Node (Id)) = N_Entry_Declaration;
13658 end Is_Entry_Declaration;
13660 ------------------------------------
13661 -- Is_Expanded_Priority_Attribute --
13662 ------------------------------------
13664 function Is_Expanded_Priority_Attribute (E : Entity_Id) return Boolean is
13665 begin
13666 return
13667 Nkind (E) = N_Function_Call
13668 and then not Configurable_Run_Time_Mode
13669 and then (Entity (Name (E)) = RTE (RE_Get_Ceiling)
13670 or else Entity (Name (E)) = RTE (RO_PE_Get_Ceiling));
13671 end Is_Expanded_Priority_Attribute;
13673 ----------------------------
13674 -- Is_Expression_Function --
13675 ----------------------------
13677 function Is_Expression_Function (Subp : Entity_Id) return Boolean is
13678 begin
13679 if Ekind_In (Subp, E_Function, E_Subprogram_Body) then
13680 return
13681 Nkind (Original_Node (Unit_Declaration_Node (Subp))) =
13682 N_Expression_Function;
13683 else
13684 return False;
13685 end if;
13686 end Is_Expression_Function;
13688 ------------------------------------------
13689 -- Is_Expression_Function_Or_Completion --
13690 ------------------------------------------
13692 function Is_Expression_Function_Or_Completion
13693 (Subp : Entity_Id) return Boolean
13695 Subp_Decl : Node_Id;
13697 begin
13698 if Ekind (Subp) = E_Function then
13699 Subp_Decl := Unit_Declaration_Node (Subp);
13701 -- The function declaration is either an expression function or is
13702 -- completed by an expression function body.
13704 return
13705 Is_Expression_Function (Subp)
13706 or else (Nkind (Subp_Decl) = N_Subprogram_Declaration
13707 and then Present (Corresponding_Body (Subp_Decl))
13708 and then Is_Expression_Function
13709 (Corresponding_Body (Subp_Decl)));
13711 elsif Ekind (Subp) = E_Subprogram_Body then
13712 return Is_Expression_Function (Subp);
13714 else
13715 return False;
13716 end if;
13717 end Is_Expression_Function_Or_Completion;
13719 -----------------------
13720 -- Is_EVF_Expression --
13721 -----------------------
13723 function Is_EVF_Expression (N : Node_Id) return Boolean is
13724 Orig_N : constant Node_Id := Original_Node (N);
13725 Alt : Node_Id;
13726 Expr : Node_Id;
13727 Id : Entity_Id;
13729 begin
13730 -- Detect a reference to a formal parameter of a specific tagged type
13731 -- whose related subprogram is subject to pragma Expresions_Visible with
13732 -- value "False".
13734 if Is_Entity_Name (N) and then Present (Entity (N)) then
13735 Id := Entity (N);
13737 return
13738 Is_Formal (Id)
13739 and then Is_Specific_Tagged_Type (Etype (Id))
13740 and then Extensions_Visible_Status (Id) =
13741 Extensions_Visible_False;
13743 -- A case expression is an EVF expression when it contains at least one
13744 -- EVF dependent_expression. Note that a case expression may have been
13745 -- expanded, hence the use of Original_Node.
13747 elsif Nkind (Orig_N) = N_Case_Expression then
13748 Alt := First (Alternatives (Orig_N));
13749 while Present (Alt) loop
13750 if Is_EVF_Expression (Expression (Alt)) then
13751 return True;
13752 end if;
13754 Next (Alt);
13755 end loop;
13757 -- An if expression is an EVF expression when it contains at least one
13758 -- EVF dependent_expression. Note that an if expression may have been
13759 -- expanded, hence the use of Original_Node.
13761 elsif Nkind (Orig_N) = N_If_Expression then
13762 Expr := Next (First (Expressions (Orig_N)));
13763 while Present (Expr) loop
13764 if Is_EVF_Expression (Expr) then
13765 return True;
13766 end if;
13768 Next (Expr);
13769 end loop;
13771 -- A qualified expression or a type conversion is an EVF expression when
13772 -- its operand is an EVF expression.
13774 elsif Nkind_In (N, N_Qualified_Expression,
13775 N_Unchecked_Type_Conversion,
13776 N_Type_Conversion)
13777 then
13778 return Is_EVF_Expression (Expression (N));
13780 -- Attributes 'Loop_Entry, 'Old, and 'Update are EVF expressions when
13781 -- their prefix denotes an EVF expression.
13783 elsif Nkind (N) = N_Attribute_Reference
13784 and then Nam_In (Attribute_Name (N), Name_Loop_Entry,
13785 Name_Old,
13786 Name_Update)
13787 then
13788 return Is_EVF_Expression (Prefix (N));
13789 end if;
13791 return False;
13792 end Is_EVF_Expression;
13794 --------------
13795 -- Is_False --
13796 --------------
13798 function Is_False (U : Uint) return Boolean is
13799 begin
13800 return (U = 0);
13801 end Is_False;
13803 ---------------------------
13804 -- Is_Fixed_Model_Number --
13805 ---------------------------
13807 function Is_Fixed_Model_Number (U : Ureal; T : Entity_Id) return Boolean is
13808 S : constant Ureal := Small_Value (T);
13809 M : Urealp.Save_Mark;
13810 R : Boolean;
13812 begin
13813 M := Urealp.Mark;
13814 R := (U = UR_Trunc (U / S) * S);
13815 Urealp.Release (M);
13816 return R;
13817 end Is_Fixed_Model_Number;
13819 -------------------------------
13820 -- Is_Fully_Initialized_Type --
13821 -------------------------------
13823 function Is_Fully_Initialized_Type (Typ : Entity_Id) return Boolean is
13824 begin
13825 -- Scalar types
13827 if Is_Scalar_Type (Typ) then
13829 -- A scalar type with an aspect Default_Value is fully initialized
13831 -- Note: Iniitalize/Normalize_Scalars also ensure full initialization
13832 -- of a scalar type, but we don't take that into account here, since
13833 -- we don't want these to affect warnings.
13835 return Has_Default_Aspect (Typ);
13837 elsif Is_Access_Type (Typ) then
13838 return True;
13840 elsif Is_Array_Type (Typ) then
13841 if Is_Fully_Initialized_Type (Component_Type (Typ))
13842 or else (Ada_Version >= Ada_2012 and then Has_Default_Aspect (Typ))
13843 then
13844 return True;
13845 end if;
13847 -- An interesting case, if we have a constrained type one of whose
13848 -- bounds is known to be null, then there are no elements to be
13849 -- initialized, so all the elements are initialized.
13851 if Is_Constrained (Typ) then
13852 declare
13853 Indx : Node_Id;
13854 Indx_Typ : Entity_Id;
13855 Lbd, Hbd : Node_Id;
13857 begin
13858 Indx := First_Index (Typ);
13859 while Present (Indx) loop
13860 if Etype (Indx) = Any_Type then
13861 return False;
13863 -- If index is a range, use directly
13865 elsif Nkind (Indx) = N_Range then
13866 Lbd := Low_Bound (Indx);
13867 Hbd := High_Bound (Indx);
13869 else
13870 Indx_Typ := Etype (Indx);
13872 if Is_Private_Type (Indx_Typ) then
13873 Indx_Typ := Full_View (Indx_Typ);
13874 end if;
13876 if No (Indx_Typ) or else Etype (Indx_Typ) = Any_Type then
13877 return False;
13878 else
13879 Lbd := Type_Low_Bound (Indx_Typ);
13880 Hbd := Type_High_Bound (Indx_Typ);
13881 end if;
13882 end if;
13884 if Compile_Time_Known_Value (Lbd)
13885 and then
13886 Compile_Time_Known_Value (Hbd)
13887 then
13888 if Expr_Value (Hbd) < Expr_Value (Lbd) then
13889 return True;
13890 end if;
13891 end if;
13893 Next_Index (Indx);
13894 end loop;
13895 end;
13896 end if;
13898 -- If no null indexes, then type is not fully initialized
13900 return False;
13902 -- Record types
13904 elsif Is_Record_Type (Typ) then
13905 if Has_Discriminants (Typ)
13906 and then
13907 Present (Discriminant_Default_Value (First_Discriminant (Typ)))
13908 and then Is_Fully_Initialized_Variant (Typ)
13909 then
13910 return True;
13911 end if;
13913 -- We consider bounded string types to be fully initialized, because
13914 -- otherwise we get false alarms when the Data component is not
13915 -- default-initialized.
13917 if Is_Bounded_String (Typ) then
13918 return True;
13919 end if;
13921 -- Controlled records are considered to be fully initialized if
13922 -- there is a user defined Initialize routine. This may not be
13923 -- entirely correct, but as the spec notes, we are guessing here
13924 -- what is best from the point of view of issuing warnings.
13926 if Is_Controlled (Typ) then
13927 declare
13928 Utyp : constant Entity_Id := Underlying_Type (Typ);
13930 begin
13931 if Present (Utyp) then
13932 declare
13933 Init : constant Entity_Id :=
13934 (Find_Optional_Prim_Op
13935 (Underlying_Type (Typ), Name_Initialize));
13937 begin
13938 if Present (Init)
13939 and then Comes_From_Source (Init)
13940 and then not In_Predefined_Unit (Init)
13941 then
13942 return True;
13944 elsif Has_Null_Extension (Typ)
13945 and then
13946 Is_Fully_Initialized_Type
13947 (Etype (Base_Type (Typ)))
13948 then
13949 return True;
13950 end if;
13951 end;
13952 end if;
13953 end;
13954 end if;
13956 -- Otherwise see if all record components are initialized
13958 declare
13959 Ent : Entity_Id;
13961 begin
13962 Ent := First_Entity (Typ);
13963 while Present (Ent) loop
13964 if Ekind (Ent) = E_Component
13965 and then (No (Parent (Ent))
13966 or else No (Expression (Parent (Ent))))
13967 and then not Is_Fully_Initialized_Type (Etype (Ent))
13969 -- Special VM case for tag components, which need to be
13970 -- defined in this case, but are never initialized as VMs
13971 -- are using other dispatching mechanisms. Ignore this
13972 -- uninitialized case. Note that this applies both to the
13973 -- uTag entry and the main vtable pointer (CPP_Class case).
13975 and then (Tagged_Type_Expansion or else not Is_Tag (Ent))
13976 then
13977 return False;
13978 end if;
13980 Next_Entity (Ent);
13981 end loop;
13982 end;
13984 -- No uninitialized components, so type is fully initialized.
13985 -- Note that this catches the case of no components as well.
13987 return True;
13989 elsif Is_Concurrent_Type (Typ) then
13990 return True;
13992 elsif Is_Private_Type (Typ) then
13993 declare
13994 U : constant Entity_Id := Underlying_Type (Typ);
13996 begin
13997 if No (U) then
13998 return False;
13999 else
14000 return Is_Fully_Initialized_Type (U);
14001 end if;
14002 end;
14004 else
14005 return False;
14006 end if;
14007 end Is_Fully_Initialized_Type;
14009 ----------------------------------
14010 -- Is_Fully_Initialized_Variant --
14011 ----------------------------------
14013 function Is_Fully_Initialized_Variant (Typ : Entity_Id) return Boolean is
14014 Loc : constant Source_Ptr := Sloc (Typ);
14015 Constraints : constant List_Id := New_List;
14016 Components : constant Elist_Id := New_Elmt_List;
14017 Comp_Elmt : Elmt_Id;
14018 Comp_Id : Node_Id;
14019 Comp_List : Node_Id;
14020 Discr : Entity_Id;
14021 Discr_Val : Node_Id;
14023 Report_Errors : Boolean;
14024 pragma Warnings (Off, Report_Errors);
14026 begin
14027 if Serious_Errors_Detected > 0 then
14028 return False;
14029 end if;
14031 if Is_Record_Type (Typ)
14032 and then Nkind (Parent (Typ)) = N_Full_Type_Declaration
14033 and then Nkind (Type_Definition (Parent (Typ))) = N_Record_Definition
14034 then
14035 Comp_List := Component_List (Type_Definition (Parent (Typ)));
14037 Discr := First_Discriminant (Typ);
14038 while Present (Discr) loop
14039 if Nkind (Parent (Discr)) = N_Discriminant_Specification then
14040 Discr_Val := Expression (Parent (Discr));
14042 if Present (Discr_Val)
14043 and then Is_OK_Static_Expression (Discr_Val)
14044 then
14045 Append_To (Constraints,
14046 Make_Component_Association (Loc,
14047 Choices => New_List (New_Occurrence_Of (Discr, Loc)),
14048 Expression => New_Copy (Discr_Val)));
14049 else
14050 return False;
14051 end if;
14052 else
14053 return False;
14054 end if;
14056 Next_Discriminant (Discr);
14057 end loop;
14059 Gather_Components
14060 (Typ => Typ,
14061 Comp_List => Comp_List,
14062 Governed_By => Constraints,
14063 Into => Components,
14064 Report_Errors => Report_Errors);
14066 -- Check that each component present is fully initialized
14068 Comp_Elmt := First_Elmt (Components);
14069 while Present (Comp_Elmt) loop
14070 Comp_Id := Node (Comp_Elmt);
14072 if Ekind (Comp_Id) = E_Component
14073 and then (No (Parent (Comp_Id))
14074 or else No (Expression (Parent (Comp_Id))))
14075 and then not Is_Fully_Initialized_Type (Etype (Comp_Id))
14076 then
14077 return False;
14078 end if;
14080 Next_Elmt (Comp_Elmt);
14081 end loop;
14083 return True;
14085 elsif Is_Private_Type (Typ) then
14086 declare
14087 U : constant Entity_Id := Underlying_Type (Typ);
14089 begin
14090 if No (U) then
14091 return False;
14092 else
14093 return Is_Fully_Initialized_Variant (U);
14094 end if;
14095 end;
14097 else
14098 return False;
14099 end if;
14100 end Is_Fully_Initialized_Variant;
14102 ------------------------------------
14103 -- Is_Generic_Declaration_Or_Body --
14104 ------------------------------------
14106 function Is_Generic_Declaration_Or_Body (Decl : Node_Id) return Boolean is
14107 Spec_Decl : Node_Id;
14109 begin
14110 -- Package/subprogram body
14112 if Nkind_In (Decl, N_Package_Body, N_Subprogram_Body)
14113 and then Present (Corresponding_Spec (Decl))
14114 then
14115 Spec_Decl := Unit_Declaration_Node (Corresponding_Spec (Decl));
14117 -- Package/subprogram body stub
14119 elsif Nkind_In (Decl, N_Package_Body_Stub, N_Subprogram_Body_Stub)
14120 and then Present (Corresponding_Spec_Of_Stub (Decl))
14121 then
14122 Spec_Decl :=
14123 Unit_Declaration_Node (Corresponding_Spec_Of_Stub (Decl));
14125 -- All other cases
14127 else
14128 Spec_Decl := Decl;
14129 end if;
14131 -- Rather than inspecting the defining entity of the spec declaration,
14132 -- look at its Nkind. This takes care of the case where the analysis of
14133 -- a generic body modifies the Ekind of its spec to allow for recursive
14134 -- calls.
14136 return
14137 Nkind_In (Spec_Decl, N_Generic_Package_Declaration,
14138 N_Generic_Subprogram_Declaration);
14139 end Is_Generic_Declaration_Or_Body;
14141 ----------------------------
14142 -- Is_Inherited_Operation --
14143 ----------------------------
14145 function Is_Inherited_Operation (E : Entity_Id) return Boolean is
14146 pragma Assert (Is_Overloadable (E));
14147 Kind : constant Node_Kind := Nkind (Parent (E));
14148 begin
14149 return Kind = N_Full_Type_Declaration
14150 or else Kind = N_Private_Extension_Declaration
14151 or else Kind = N_Subtype_Declaration
14152 or else (Ekind (E) = E_Enumeration_Literal
14153 and then Is_Derived_Type (Etype (E)));
14154 end Is_Inherited_Operation;
14156 -------------------------------------
14157 -- Is_Inherited_Operation_For_Type --
14158 -------------------------------------
14160 function Is_Inherited_Operation_For_Type
14161 (E : Entity_Id;
14162 Typ : Entity_Id) return Boolean
14164 begin
14165 -- Check that the operation has been created by the type declaration
14167 return Is_Inherited_Operation (E)
14168 and then Defining_Identifier (Parent (E)) = Typ;
14169 end Is_Inherited_Operation_For_Type;
14171 --------------------------------------
14172 -- Is_Inlinable_Expression_Function --
14173 --------------------------------------
14175 function Is_Inlinable_Expression_Function
14176 (Subp : Entity_Id) return Boolean
14178 Return_Expr : Node_Id;
14180 begin
14181 if Is_Expression_Function_Or_Completion (Subp)
14182 and then Has_Pragma_Inline_Always (Subp)
14183 and then Needs_No_Actuals (Subp)
14184 and then No (Contract (Subp))
14185 and then not Is_Dispatching_Operation (Subp)
14186 and then Needs_Finalization (Etype (Subp))
14187 and then not Is_Class_Wide_Type (Etype (Subp))
14188 and then not (Has_Invariants (Etype (Subp)))
14189 and then Present (Subprogram_Body (Subp))
14190 and then Was_Expression_Function (Subprogram_Body (Subp))
14191 then
14192 Return_Expr := Expression_Of_Expression_Function (Subp);
14194 -- The returned object must not have a qualified expression and its
14195 -- nominal subtype must be statically compatible with the result
14196 -- subtype of the expression function.
14198 return
14199 Nkind (Return_Expr) = N_Identifier
14200 and then Etype (Return_Expr) = Etype (Subp);
14201 end if;
14203 return False;
14204 end Is_Inlinable_Expression_Function;
14206 -----------------
14207 -- Is_Iterator --
14208 -----------------
14210 function Is_Iterator (Typ : Entity_Id) return Boolean is
14211 function Denotes_Iterator (Iter_Typ : Entity_Id) return Boolean;
14212 -- Determine whether type Iter_Typ is a predefined forward or reversible
14213 -- iterator.
14215 ----------------------
14216 -- Denotes_Iterator --
14217 ----------------------
14219 function Denotes_Iterator (Iter_Typ : Entity_Id) return Boolean is
14220 begin
14221 -- Check that the name matches, and that the ultimate ancestor is in
14222 -- a predefined unit, i.e the one that declares iterator interfaces.
14224 return
14225 Nam_In (Chars (Iter_Typ), Name_Forward_Iterator,
14226 Name_Reversible_Iterator)
14227 and then In_Predefined_Unit (Root_Type (Iter_Typ));
14228 end Denotes_Iterator;
14230 -- Local variables
14232 Iface_Elmt : Elmt_Id;
14233 Ifaces : Elist_Id;
14235 -- Start of processing for Is_Iterator
14237 begin
14238 -- The type may be a subtype of a descendant of the proper instance of
14239 -- the predefined interface type, so we must use the root type of the
14240 -- given type. The same is done for Is_Reversible_Iterator.
14242 if Is_Class_Wide_Type (Typ)
14243 and then Denotes_Iterator (Root_Type (Typ))
14244 then
14245 return True;
14247 elsif not Is_Tagged_Type (Typ) or else not Is_Derived_Type (Typ) then
14248 return False;
14250 elsif Present (Find_Value_Of_Aspect (Typ, Aspect_Iterable)) then
14251 return True;
14253 else
14254 Collect_Interfaces (Typ, Ifaces);
14256 Iface_Elmt := First_Elmt (Ifaces);
14257 while Present (Iface_Elmt) loop
14258 if Denotes_Iterator (Node (Iface_Elmt)) then
14259 return True;
14260 end if;
14262 Next_Elmt (Iface_Elmt);
14263 end loop;
14265 return False;
14266 end if;
14267 end Is_Iterator;
14269 ----------------------------
14270 -- Is_Iterator_Over_Array --
14271 ----------------------------
14273 function Is_Iterator_Over_Array (N : Node_Id) return Boolean is
14274 Container : constant Node_Id := Name (N);
14275 Container_Typ : constant Entity_Id := Base_Type (Etype (Container));
14276 begin
14277 return Is_Array_Type (Container_Typ);
14278 end Is_Iterator_Over_Array;
14280 ------------
14281 -- Is_LHS --
14282 ------------
14284 -- We seem to have a lot of overlapping functions that do similar things
14285 -- (testing for left hand sides or lvalues???).
14287 function Is_LHS (N : Node_Id) return Is_LHS_Result is
14288 P : constant Node_Id := Parent (N);
14290 begin
14291 -- Return True if we are the left hand side of an assignment statement
14293 if Nkind (P) = N_Assignment_Statement then
14294 if Name (P) = N then
14295 return Yes;
14296 else
14297 return No;
14298 end if;
14300 -- Case of prefix of indexed or selected component or slice
14302 elsif Nkind_In (P, N_Indexed_Component, N_Selected_Component, N_Slice)
14303 and then N = Prefix (P)
14304 then
14305 -- Here we have the case where the parent P is N.Q or N(Q .. R).
14306 -- If P is an LHS, then N is also effectively an LHS, but there
14307 -- is an important exception. If N is of an access type, then
14308 -- what we really have is N.all.Q (or N.all(Q .. R)). In either
14309 -- case this makes N.all a left hand side but not N itself.
14311 -- If we don't know the type yet, this is the case where we return
14312 -- Unknown, since the answer depends on the type which is unknown.
14314 if No (Etype (N)) then
14315 return Unknown;
14317 -- We have an Etype set, so we can check it
14319 elsif Is_Access_Type (Etype (N)) then
14320 return No;
14322 -- OK, not access type case, so just test whole expression
14324 else
14325 return Is_LHS (P);
14326 end if;
14328 -- All other cases are not left hand sides
14330 else
14331 return No;
14332 end if;
14333 end Is_LHS;
14335 -----------------------------
14336 -- Is_Library_Level_Entity --
14337 -----------------------------
14339 function Is_Library_Level_Entity (E : Entity_Id) return Boolean is
14340 begin
14341 -- The following is a small optimization, and it also properly handles
14342 -- discriminals, which in task bodies might appear in expressions before
14343 -- the corresponding procedure has been created, and which therefore do
14344 -- not have an assigned scope.
14346 if Is_Formal (E) then
14347 return False;
14348 end if;
14350 -- Normal test is simply that the enclosing dynamic scope is Standard
14352 return Enclosing_Dynamic_Scope (E) = Standard_Standard;
14353 end Is_Library_Level_Entity;
14355 --------------------------------
14356 -- Is_Limited_Class_Wide_Type --
14357 --------------------------------
14359 function Is_Limited_Class_Wide_Type (Typ : Entity_Id) return Boolean is
14360 begin
14361 return
14362 Is_Class_Wide_Type (Typ)
14363 and then (Is_Limited_Type (Typ) or else From_Limited_With (Typ));
14364 end Is_Limited_Class_Wide_Type;
14366 ---------------------------------
14367 -- Is_Local_Variable_Reference --
14368 ---------------------------------
14370 function Is_Local_Variable_Reference (Expr : Node_Id) return Boolean is
14371 begin
14372 if not Is_Entity_Name (Expr) then
14373 return False;
14375 else
14376 declare
14377 Ent : constant Entity_Id := Entity (Expr);
14378 Sub : constant Entity_Id := Enclosing_Subprogram (Ent);
14379 begin
14380 if not Ekind_In (Ent, E_Variable, E_In_Out_Parameter) then
14381 return False;
14382 else
14383 return Present (Sub) and then Sub = Current_Subprogram;
14384 end if;
14385 end;
14386 end if;
14387 end Is_Local_Variable_Reference;
14389 -----------------------
14390 -- Is_Name_Reference --
14391 -----------------------
14393 function Is_Name_Reference (N : Node_Id) return Boolean is
14394 begin
14395 if Is_Entity_Name (N) then
14396 return Present (Entity (N)) and then Is_Object (Entity (N));
14397 end if;
14399 case Nkind (N) is
14400 when N_Indexed_Component
14401 | N_Slice
14403 return
14404 Is_Name_Reference (Prefix (N))
14405 or else Is_Access_Type (Etype (Prefix (N)));
14407 -- Attributes 'Input, 'Old and 'Result produce objects
14409 when N_Attribute_Reference =>
14410 return
14411 Nam_In (Attribute_Name (N), Name_Input, Name_Old, Name_Result);
14413 when N_Selected_Component =>
14414 return
14415 Is_Name_Reference (Selector_Name (N))
14416 and then
14417 (Is_Name_Reference (Prefix (N))
14418 or else Is_Access_Type (Etype (Prefix (N))));
14420 when N_Explicit_Dereference =>
14421 return True;
14423 -- A view conversion of a tagged name is a name reference
14425 when N_Type_Conversion =>
14426 return
14427 Is_Tagged_Type (Etype (Subtype_Mark (N)))
14428 and then Is_Tagged_Type (Etype (Expression (N)))
14429 and then Is_Name_Reference (Expression (N));
14431 -- An unchecked type conversion is considered to be a name if the
14432 -- operand is a name (this construction arises only as a result of
14433 -- expansion activities).
14435 when N_Unchecked_Type_Conversion =>
14436 return Is_Name_Reference (Expression (N));
14438 when others =>
14439 return False;
14440 end case;
14441 end Is_Name_Reference;
14443 ---------------------------------
14444 -- Is_Nontrivial_DIC_Procedure --
14445 ---------------------------------
14447 function Is_Nontrivial_DIC_Procedure (Id : Entity_Id) return Boolean is
14448 Body_Decl : Node_Id;
14449 Stmt : Node_Id;
14451 begin
14452 if Ekind (Id) = E_Procedure and then Is_DIC_Procedure (Id) then
14453 Body_Decl :=
14454 Unit_Declaration_Node
14455 (Corresponding_Body (Unit_Declaration_Node (Id)));
14457 -- The body of the Default_Initial_Condition procedure must contain
14458 -- at least one statement, otherwise the generation of the subprogram
14459 -- body failed.
14461 pragma Assert (Present (Handled_Statement_Sequence (Body_Decl)));
14463 -- To qualify as nontrivial, the first statement of the procedure
14464 -- must be a check in the form of an if statement. If the original
14465 -- Default_Initial_Condition expression was folded, then the first
14466 -- statement is not a check.
14468 Stmt := First (Statements (Handled_Statement_Sequence (Body_Decl)));
14470 return
14471 Nkind (Stmt) = N_If_Statement
14472 and then Nkind (Original_Node (Stmt)) = N_Pragma;
14473 end if;
14475 return False;
14476 end Is_Nontrivial_DIC_Procedure;
14478 -------------------------
14479 -- Is_Null_Record_Type --
14480 -------------------------
14482 function Is_Null_Record_Type (T : Entity_Id) return Boolean is
14483 Decl : constant Node_Id := Parent (T);
14484 begin
14485 return Nkind (Decl) = N_Full_Type_Declaration
14486 and then Nkind (Type_Definition (Decl)) = N_Record_Definition
14487 and then
14488 (No (Component_List (Type_Definition (Decl)))
14489 or else Null_Present (Component_List (Type_Definition (Decl))));
14490 end Is_Null_Record_Type;
14492 ---------------------
14493 -- Is_Object_Image --
14494 ---------------------
14496 function Is_Object_Image (Prefix : Node_Id) return Boolean is
14497 begin
14498 -- When the type of the prefix is not scalar, then the prefix is not
14499 -- valid in any scenario.
14501 if not Is_Scalar_Type (Etype (Prefix)) then
14502 return False;
14503 end if;
14505 -- Here we test for the case that the prefix is not a type and assume
14506 -- if it is not then it must be a named value or an object reference.
14507 -- This is because the parser always checks that prefixes of attributes
14508 -- are named.
14510 return not (Is_Entity_Name (Prefix) and then Is_Type (Entity (Prefix)));
14511 end Is_Object_Image;
14513 -------------------------
14514 -- Is_Object_Reference --
14515 -------------------------
14517 function Is_Object_Reference (N : Node_Id) return Boolean is
14518 function Is_Internally_Generated_Renaming (N : Node_Id) return Boolean;
14519 -- Determine whether N is the name of an internally-generated renaming
14521 --------------------------------------
14522 -- Is_Internally_Generated_Renaming --
14523 --------------------------------------
14525 function Is_Internally_Generated_Renaming (N : Node_Id) return Boolean is
14526 P : Node_Id;
14528 begin
14529 P := N;
14530 while Present (P) loop
14531 if Nkind (P) = N_Object_Renaming_Declaration then
14532 return not Comes_From_Source (P);
14533 elsif Is_List_Member (P) then
14534 return False;
14535 end if;
14537 P := Parent (P);
14538 end loop;
14540 return False;
14541 end Is_Internally_Generated_Renaming;
14543 -- Start of processing for Is_Object_Reference
14545 begin
14546 if Is_Entity_Name (N) then
14547 return Present (Entity (N)) and then Is_Object (Entity (N));
14549 else
14550 case Nkind (N) is
14551 when N_Indexed_Component
14552 | N_Slice
14554 return
14555 Is_Object_Reference (Prefix (N))
14556 or else Is_Access_Type (Etype (Prefix (N)));
14558 -- In Ada 95, a function call is a constant object; a procedure
14559 -- call is not.
14561 -- Note that predefined operators are functions as well, and so
14562 -- are attributes that are (can be renamed as) functions.
14564 when N_Binary_Op
14565 | N_Function_Call
14566 | N_Unary_Op
14568 return Etype (N) /= Standard_Void_Type;
14570 -- Attributes references 'Loop_Entry, 'Old, and 'Result yield
14571 -- objects, even though they are not functions.
14573 when N_Attribute_Reference =>
14574 return
14575 Nam_In (Attribute_Name (N), Name_Loop_Entry,
14576 Name_Old,
14577 Name_Result)
14578 or else Is_Function_Attribute_Name (Attribute_Name (N));
14580 when N_Selected_Component =>
14581 return
14582 Is_Object_Reference (Selector_Name (N))
14583 and then
14584 (Is_Object_Reference (Prefix (N))
14585 or else Is_Access_Type (Etype (Prefix (N))));
14587 -- An explicit dereference denotes an object, except that a
14588 -- conditional expression gets turned into an explicit dereference
14589 -- in some cases, and conditional expressions are not object
14590 -- names.
14592 when N_Explicit_Dereference =>
14593 return not Nkind_In (Original_Node (N), N_Case_Expression,
14594 N_If_Expression);
14596 -- A view conversion of a tagged object is an object reference
14598 when N_Type_Conversion =>
14599 return Is_Tagged_Type (Etype (Subtype_Mark (N)))
14600 and then Is_Tagged_Type (Etype (Expression (N)))
14601 and then Is_Object_Reference (Expression (N));
14603 -- An unchecked type conversion is considered to be an object if
14604 -- the operand is an object (this construction arises only as a
14605 -- result of expansion activities).
14607 when N_Unchecked_Type_Conversion =>
14608 return True;
14610 -- Allow string literals to act as objects as long as they appear
14611 -- in internally-generated renamings. The expansion of iterators
14612 -- may generate such renamings when the range involves a string
14613 -- literal.
14615 when N_String_Literal =>
14616 return Is_Internally_Generated_Renaming (Parent (N));
14618 -- AI05-0003: In Ada 2012 a qualified expression is a name.
14619 -- This allows disambiguation of function calls and the use
14620 -- of aggregates in more contexts.
14622 when N_Qualified_Expression =>
14623 if Ada_Version < Ada_2012 then
14624 return False;
14625 else
14626 return Is_Object_Reference (Expression (N))
14627 or else Nkind (Expression (N)) = N_Aggregate;
14628 end if;
14630 when others =>
14631 return False;
14632 end case;
14633 end if;
14634 end Is_Object_Reference;
14636 -----------------------------------
14637 -- Is_OK_Variable_For_Out_Formal --
14638 -----------------------------------
14640 function Is_OK_Variable_For_Out_Formal (AV : Node_Id) return Boolean is
14641 begin
14642 Note_Possible_Modification (AV, Sure => True);
14644 -- We must reject parenthesized variable names. Comes_From_Source is
14645 -- checked because there are currently cases where the compiler violates
14646 -- this rule (e.g. passing a task object to its controlled Initialize
14647 -- routine). This should be properly documented in sinfo???
14649 if Paren_Count (AV) > 0 and then Comes_From_Source (AV) then
14650 return False;
14652 -- A variable is always allowed
14654 elsif Is_Variable (AV) then
14655 return True;
14657 -- Generalized indexing operations are rewritten as explicit
14658 -- dereferences, and it is only during resolution that we can
14659 -- check whether the context requires an access_to_variable type.
14661 elsif Nkind (AV) = N_Explicit_Dereference
14662 and then Ada_Version >= Ada_2012
14663 and then Nkind (Original_Node (AV)) = N_Indexed_Component
14664 and then Present (Etype (Original_Node (AV)))
14665 and then Has_Implicit_Dereference (Etype (Original_Node (AV)))
14666 then
14667 return not Is_Access_Constant (Etype (Prefix (AV)));
14669 -- Unchecked conversions are allowed only if they come from the
14670 -- generated code, which sometimes uses unchecked conversions for out
14671 -- parameters in cases where code generation is unaffected. We tell
14672 -- source unchecked conversions by seeing if they are rewrites of
14673 -- an original Unchecked_Conversion function call, or of an explicit
14674 -- conversion of a function call or an aggregate (as may happen in the
14675 -- expansion of a packed array aggregate).
14677 elsif Nkind (AV) = N_Unchecked_Type_Conversion then
14678 if Nkind_In (Original_Node (AV), N_Function_Call, N_Aggregate) then
14679 return False;
14681 elsif Comes_From_Source (AV)
14682 and then Nkind (Original_Node (Expression (AV))) = N_Function_Call
14683 then
14684 return False;
14686 elsif Nkind (Original_Node (AV)) = N_Type_Conversion then
14687 return Is_OK_Variable_For_Out_Formal (Expression (AV));
14689 else
14690 return True;
14691 end if;
14693 -- Normal type conversions are allowed if argument is a variable
14695 elsif Nkind (AV) = N_Type_Conversion then
14696 if Is_Variable (Expression (AV))
14697 and then Paren_Count (Expression (AV)) = 0
14698 then
14699 Note_Possible_Modification (Expression (AV), Sure => True);
14700 return True;
14702 -- We also allow a non-parenthesized expression that raises
14703 -- constraint error if it rewrites what used to be a variable
14705 elsif Raises_Constraint_Error (Expression (AV))
14706 and then Paren_Count (Expression (AV)) = 0
14707 and then Is_Variable (Original_Node (Expression (AV)))
14708 then
14709 return True;
14711 -- Type conversion of something other than a variable
14713 else
14714 return False;
14715 end if;
14717 -- If this node is rewritten, then test the original form, if that is
14718 -- OK, then we consider the rewritten node OK (for example, if the
14719 -- original node is a conversion, then Is_Variable will not be true
14720 -- but we still want to allow the conversion if it converts a variable).
14722 elsif Original_Node (AV) /= AV then
14724 -- In Ada 2012, the explicit dereference may be a rewritten call to a
14725 -- Reference function.
14727 if Ada_Version >= Ada_2012
14728 and then Nkind (Original_Node (AV)) = N_Function_Call
14729 and then
14730 Has_Implicit_Dereference (Etype (Name (Original_Node (AV))))
14731 then
14733 -- Check that this is not a constant reference.
14735 return not Is_Access_Constant (Etype (Prefix (AV)));
14737 elsif Has_Implicit_Dereference (Etype (Original_Node (AV))) then
14738 return
14739 not Is_Access_Constant (Etype
14740 (Get_Reference_Discriminant (Etype (Original_Node (AV)))));
14742 else
14743 return Is_OK_Variable_For_Out_Formal (Original_Node (AV));
14744 end if;
14746 -- All other non-variables are rejected
14748 else
14749 return False;
14750 end if;
14751 end Is_OK_Variable_For_Out_Formal;
14753 ----------------------------
14754 -- Is_OK_Volatile_Context --
14755 ----------------------------
14757 function Is_OK_Volatile_Context
14758 (Context : Node_Id;
14759 Obj_Ref : Node_Id) return Boolean
14761 function Is_Protected_Operation_Call (Nod : Node_Id) return Boolean;
14762 -- Determine whether an arbitrary node denotes a call to a protected
14763 -- entry, function, or procedure in prefixed form where the prefix is
14764 -- Obj_Ref.
14766 function Within_Check (Nod : Node_Id) return Boolean;
14767 -- Determine whether an arbitrary node appears in a check node
14769 function Within_Subprogram_Call (Nod : Node_Id) return Boolean;
14770 -- Determine whether an arbitrary node appears in an entry, function, or
14771 -- procedure call.
14773 function Within_Volatile_Function (Id : Entity_Id) return Boolean;
14774 -- Determine whether an arbitrary entity appears in a volatile function
14776 ---------------------------------
14777 -- Is_Protected_Operation_Call --
14778 ---------------------------------
14780 function Is_Protected_Operation_Call (Nod : Node_Id) return Boolean is
14781 Pref : Node_Id;
14782 Subp : Node_Id;
14784 begin
14785 -- A call to a protected operations retains its selected component
14786 -- form as opposed to other prefixed calls that are transformed in
14787 -- expanded names.
14789 if Nkind (Nod) = N_Selected_Component then
14790 Pref := Prefix (Nod);
14791 Subp := Selector_Name (Nod);
14793 return
14794 Pref = Obj_Ref
14795 and then Present (Etype (Pref))
14796 and then Is_Protected_Type (Etype (Pref))
14797 and then Is_Entity_Name (Subp)
14798 and then Present (Entity (Subp))
14799 and then Ekind_In (Entity (Subp), E_Entry,
14800 E_Entry_Family,
14801 E_Function,
14802 E_Procedure);
14803 else
14804 return False;
14805 end if;
14806 end Is_Protected_Operation_Call;
14808 ------------------
14809 -- Within_Check --
14810 ------------------
14812 function Within_Check (Nod : Node_Id) return Boolean is
14813 Par : Node_Id;
14815 begin
14816 -- Climb the parent chain looking for a check node
14818 Par := Nod;
14819 while Present (Par) loop
14820 if Nkind (Par) in N_Raise_xxx_Error then
14821 return True;
14823 -- Prevent the search from going too far
14825 elsif Is_Body_Or_Package_Declaration (Par) then
14826 exit;
14827 end if;
14829 Par := Parent (Par);
14830 end loop;
14832 return False;
14833 end Within_Check;
14835 ----------------------------
14836 -- Within_Subprogram_Call --
14837 ----------------------------
14839 function Within_Subprogram_Call (Nod : Node_Id) return Boolean is
14840 Par : Node_Id;
14842 begin
14843 -- Climb the parent chain looking for a function or procedure call
14845 Par := Nod;
14846 while Present (Par) loop
14847 if Nkind_In (Par, N_Entry_Call_Statement,
14848 N_Function_Call,
14849 N_Procedure_Call_Statement)
14850 then
14851 return True;
14853 -- Prevent the search from going too far
14855 elsif Is_Body_Or_Package_Declaration (Par) then
14856 exit;
14857 end if;
14859 Par := Parent (Par);
14860 end loop;
14862 return False;
14863 end Within_Subprogram_Call;
14865 ------------------------------
14866 -- Within_Volatile_Function --
14867 ------------------------------
14869 function Within_Volatile_Function (Id : Entity_Id) return Boolean is
14870 Func_Id : Entity_Id;
14872 begin
14873 -- Traverse the scope stack looking for a [generic] function
14875 Func_Id := Id;
14876 while Present (Func_Id) and then Func_Id /= Standard_Standard loop
14877 if Ekind_In (Func_Id, E_Function, E_Generic_Function) then
14878 return Is_Volatile_Function (Func_Id);
14879 end if;
14881 Func_Id := Scope (Func_Id);
14882 end loop;
14884 return False;
14885 end Within_Volatile_Function;
14887 -- Local variables
14889 Obj_Id : Entity_Id;
14891 -- Start of processing for Is_OK_Volatile_Context
14893 begin
14894 -- The volatile object appears on either side of an assignment
14896 if Nkind (Context) = N_Assignment_Statement then
14897 return True;
14899 -- The volatile object is part of the initialization expression of
14900 -- another object.
14902 elsif Nkind (Context) = N_Object_Declaration
14903 and then Present (Expression (Context))
14904 and then Expression (Context) = Obj_Ref
14905 then
14906 Obj_Id := Defining_Entity (Context);
14908 -- The volatile object acts as the initialization expression of an
14909 -- extended return statement. This is valid context as long as the
14910 -- function is volatile.
14912 if Is_Return_Object (Obj_Id) then
14913 return Within_Volatile_Function (Obj_Id);
14915 -- Otherwise this is a normal object initialization
14917 else
14918 return True;
14919 end if;
14921 -- The volatile object acts as the name of a renaming declaration
14923 elsif Nkind (Context) = N_Object_Renaming_Declaration
14924 and then Name (Context) = Obj_Ref
14925 then
14926 return True;
14928 -- The volatile object appears as an actual parameter in a call to an
14929 -- instance of Unchecked_Conversion whose result is renamed.
14931 elsif Nkind (Context) = N_Function_Call
14932 and then Is_Entity_Name (Name (Context))
14933 and then Is_Unchecked_Conversion_Instance (Entity (Name (Context)))
14934 and then Nkind (Parent (Context)) = N_Object_Renaming_Declaration
14935 then
14936 return True;
14938 -- The volatile object is actually the prefix in a protected entry,
14939 -- function, or procedure call.
14941 elsif Is_Protected_Operation_Call (Context) then
14942 return True;
14944 -- The volatile object appears as the expression of a simple return
14945 -- statement that applies to a volatile function.
14947 elsif Nkind (Context) = N_Simple_Return_Statement
14948 and then Expression (Context) = Obj_Ref
14949 then
14950 return
14951 Within_Volatile_Function (Return_Statement_Entity (Context));
14953 -- The volatile object appears as the prefix of a name occurring in a
14954 -- non-interfering context.
14956 elsif Nkind_In (Context, N_Attribute_Reference,
14957 N_Explicit_Dereference,
14958 N_Indexed_Component,
14959 N_Selected_Component,
14960 N_Slice)
14961 and then Prefix (Context) = Obj_Ref
14962 and then Is_OK_Volatile_Context
14963 (Context => Parent (Context),
14964 Obj_Ref => Context)
14965 then
14966 return True;
14968 -- The volatile object appears as the prefix of attributes Address,
14969 -- Alignment, Component_Size, First_Bit, Last_Bit, Position, Size,
14970 -- Storage_Size.
14972 elsif Nkind (Context) = N_Attribute_Reference
14973 and then Prefix (Context) = Obj_Ref
14974 and then Nam_In (Attribute_Name (Context), Name_Address,
14975 Name_Alignment,
14976 Name_Component_Size,
14977 Name_First_Bit,
14978 Name_Last_Bit,
14979 Name_Position,
14980 Name_Size,
14981 Name_Storage_Size)
14982 then
14983 return True;
14985 -- The volatile object appears as the expression of a type conversion
14986 -- occurring in a non-interfering context.
14988 elsif Nkind_In (Context, N_Type_Conversion,
14989 N_Unchecked_Type_Conversion)
14990 and then Expression (Context) = Obj_Ref
14991 and then Is_OK_Volatile_Context
14992 (Context => Parent (Context),
14993 Obj_Ref => Context)
14994 then
14995 return True;
14997 -- The volatile object appears as the expression in a delay statement
14999 elsif Nkind (Context) in N_Delay_Statement then
15000 return True;
15002 -- Allow references to volatile objects in various checks. This is not a
15003 -- direct SPARK 2014 requirement.
15005 elsif Within_Check (Context) then
15006 return True;
15008 -- Assume that references to effectively volatile objects that appear
15009 -- as actual parameters in a subprogram call are always legal. A full
15010 -- legality check is done when the actuals are resolved (see routine
15011 -- Resolve_Actuals).
15013 elsif Within_Subprogram_Call (Context) then
15014 return True;
15016 -- Otherwise the context is not suitable for an effectively volatile
15017 -- object.
15019 else
15020 return False;
15021 end if;
15022 end Is_OK_Volatile_Context;
15024 ------------------------------------
15025 -- Is_Package_Contract_Annotation --
15026 ------------------------------------
15028 function Is_Package_Contract_Annotation (Item : Node_Id) return Boolean is
15029 Nam : Name_Id;
15031 begin
15032 if Nkind (Item) = N_Aspect_Specification then
15033 Nam := Chars (Identifier (Item));
15035 else pragma Assert (Nkind (Item) = N_Pragma);
15036 Nam := Pragma_Name (Item);
15037 end if;
15039 return Nam = Name_Abstract_State
15040 or else Nam = Name_Initial_Condition
15041 or else Nam = Name_Initializes
15042 or else Nam = Name_Refined_State;
15043 end Is_Package_Contract_Annotation;
15045 -----------------------------------
15046 -- Is_Partially_Initialized_Type --
15047 -----------------------------------
15049 function Is_Partially_Initialized_Type
15050 (Typ : Entity_Id;
15051 Include_Implicit : Boolean := True) return Boolean
15053 begin
15054 if Is_Scalar_Type (Typ) then
15055 return False;
15057 elsif Is_Access_Type (Typ) then
15058 return Include_Implicit;
15060 elsif Is_Array_Type (Typ) then
15062 -- If component type is partially initialized, so is array type
15064 if Is_Partially_Initialized_Type
15065 (Component_Type (Typ), Include_Implicit)
15066 then
15067 return True;
15069 -- Otherwise we are only partially initialized if we are fully
15070 -- initialized (this is the empty array case, no point in us
15071 -- duplicating that code here).
15073 else
15074 return Is_Fully_Initialized_Type (Typ);
15075 end if;
15077 elsif Is_Record_Type (Typ) then
15079 -- A discriminated type is always partially initialized if in
15080 -- all mode
15082 if Has_Discriminants (Typ) and then Include_Implicit then
15083 return True;
15085 -- A tagged type is always partially initialized
15087 elsif Is_Tagged_Type (Typ) then
15088 return True;
15090 -- Case of non-discriminated record
15092 else
15093 declare
15094 Ent : Entity_Id;
15096 Component_Present : Boolean := False;
15097 -- Set True if at least one component is present. If no
15098 -- components are present, then record type is fully
15099 -- initialized (another odd case, like the null array).
15101 begin
15102 -- Loop through components
15104 Ent := First_Entity (Typ);
15105 while Present (Ent) loop
15106 if Ekind (Ent) = E_Component then
15107 Component_Present := True;
15109 -- If a component has an initialization expression then
15110 -- the enclosing record type is partially initialized
15112 if Present (Parent (Ent))
15113 and then Present (Expression (Parent (Ent)))
15114 then
15115 return True;
15117 -- If a component is of a type which is itself partially
15118 -- initialized, then the enclosing record type is also.
15120 elsif Is_Partially_Initialized_Type
15121 (Etype (Ent), Include_Implicit)
15122 then
15123 return True;
15124 end if;
15125 end if;
15127 Next_Entity (Ent);
15128 end loop;
15130 -- No initialized components found. If we found any components
15131 -- they were all uninitialized so the result is false.
15133 if Component_Present then
15134 return False;
15136 -- But if we found no components, then all the components are
15137 -- initialized so we consider the type to be initialized.
15139 else
15140 return True;
15141 end if;
15142 end;
15143 end if;
15145 -- Concurrent types are always fully initialized
15147 elsif Is_Concurrent_Type (Typ) then
15148 return True;
15150 -- For a private type, go to underlying type. If there is no underlying
15151 -- type then just assume this partially initialized. Not clear if this
15152 -- can happen in a non-error case, but no harm in testing for this.
15154 elsif Is_Private_Type (Typ) then
15155 declare
15156 U : constant Entity_Id := Underlying_Type (Typ);
15157 begin
15158 if No (U) then
15159 return True;
15160 else
15161 return Is_Partially_Initialized_Type (U, Include_Implicit);
15162 end if;
15163 end;
15165 -- For any other type (are there any?) assume partially initialized
15167 else
15168 return True;
15169 end if;
15170 end Is_Partially_Initialized_Type;
15172 ------------------------------------
15173 -- Is_Potentially_Persistent_Type --
15174 ------------------------------------
15176 function Is_Potentially_Persistent_Type (T : Entity_Id) return Boolean is
15177 Comp : Entity_Id;
15178 Indx : Node_Id;
15180 begin
15181 -- For private type, test corresponding full type
15183 if Is_Private_Type (T) then
15184 return Is_Potentially_Persistent_Type (Full_View (T));
15186 -- Scalar types are potentially persistent
15188 elsif Is_Scalar_Type (T) then
15189 return True;
15191 -- Record type is potentially persistent if not tagged and the types of
15192 -- all it components are potentially persistent, and no component has
15193 -- an initialization expression.
15195 elsif Is_Record_Type (T)
15196 and then not Is_Tagged_Type (T)
15197 and then not Is_Partially_Initialized_Type (T)
15198 then
15199 Comp := First_Component (T);
15200 while Present (Comp) loop
15201 if not Is_Potentially_Persistent_Type (Etype (Comp)) then
15202 return False;
15203 else
15204 Next_Entity (Comp);
15205 end if;
15206 end loop;
15208 return True;
15210 -- Array type is potentially persistent if its component type is
15211 -- potentially persistent and if all its constraints are static.
15213 elsif Is_Array_Type (T) then
15214 if not Is_Potentially_Persistent_Type (Component_Type (T)) then
15215 return False;
15216 end if;
15218 Indx := First_Index (T);
15219 while Present (Indx) loop
15220 if not Is_OK_Static_Subtype (Etype (Indx)) then
15221 return False;
15222 else
15223 Next_Index (Indx);
15224 end if;
15225 end loop;
15227 return True;
15229 -- All other types are not potentially persistent
15231 else
15232 return False;
15233 end if;
15234 end Is_Potentially_Persistent_Type;
15236 --------------------------------
15237 -- Is_Potentially_Unevaluated --
15238 --------------------------------
15240 function Is_Potentially_Unevaluated (N : Node_Id) return Boolean is
15241 Par : Node_Id;
15242 Expr : Node_Id;
15244 begin
15245 Expr := N;
15246 Par := Parent (N);
15248 -- A postcondition whose expression is a short-circuit is broken down
15249 -- into individual aspects for better exception reporting. The original
15250 -- short-circuit expression is rewritten as the second operand, and an
15251 -- occurrence of 'Old in that operand is potentially unevaluated.
15252 -- See Sem_ch13.adb for details of this transformation.
15254 if Nkind (Original_Node (Par)) = N_And_Then then
15255 return True;
15256 end if;
15258 while not Nkind_In (Par, N_If_Expression,
15259 N_Case_Expression,
15260 N_And_Then,
15261 N_Or_Else,
15262 N_In,
15263 N_Not_In,
15264 N_Quantified_Expression)
15265 loop
15266 Expr := Par;
15267 Par := Parent (Par);
15269 -- If the context is not an expression, or if is the result of
15270 -- expansion of an enclosing construct (such as another attribute)
15271 -- the predicate does not apply.
15273 if Nkind (Par) = N_Case_Expression_Alternative then
15274 null;
15276 elsif Nkind (Par) not in N_Subexpr
15277 or else not Comes_From_Source (Par)
15278 then
15279 return False;
15280 end if;
15281 end loop;
15283 if Nkind (Par) = N_If_Expression then
15284 return Is_Elsif (Par) or else Expr /= First (Expressions (Par));
15286 elsif Nkind (Par) = N_Case_Expression then
15287 return Expr /= Expression (Par);
15289 elsif Nkind_In (Par, N_And_Then, N_Or_Else) then
15290 return Expr = Right_Opnd (Par);
15292 elsif Nkind_In (Par, N_In, N_Not_In) then
15294 -- If the membership includes several alternatives, only the first is
15295 -- definitely evaluated.
15297 if Present (Alternatives (Par)) then
15298 return Expr /= First (Alternatives (Par));
15300 -- If this is a range membership both bounds are evaluated
15302 else
15303 return False;
15304 end if;
15306 elsif Nkind (Par) = N_Quantified_Expression then
15307 return Expr = Condition (Par);
15309 else
15310 return False;
15311 end if;
15312 end Is_Potentially_Unevaluated;
15314 ---------------------------------
15315 -- Is_Protected_Self_Reference --
15316 ---------------------------------
15318 function Is_Protected_Self_Reference (N : Node_Id) return Boolean is
15320 function In_Access_Definition (N : Node_Id) return Boolean;
15321 -- Returns true if N belongs to an access definition
15323 --------------------------
15324 -- In_Access_Definition --
15325 --------------------------
15327 function In_Access_Definition (N : Node_Id) return Boolean is
15328 P : Node_Id;
15330 begin
15331 P := Parent (N);
15332 while Present (P) loop
15333 if Nkind (P) = N_Access_Definition then
15334 return True;
15335 end if;
15337 P := Parent (P);
15338 end loop;
15340 return False;
15341 end In_Access_Definition;
15343 -- Start of processing for Is_Protected_Self_Reference
15345 begin
15346 -- Verify that prefix is analyzed and has the proper form. Note that
15347 -- the attributes Elab_Spec, Elab_Body, and Elab_Subp_Body, which also
15348 -- produce the address of an entity, do not analyze their prefix
15349 -- because they denote entities that are not necessarily visible.
15350 -- Neither of them can apply to a protected type.
15352 return Ada_Version >= Ada_2005
15353 and then Is_Entity_Name (N)
15354 and then Present (Entity (N))
15355 and then Is_Protected_Type (Entity (N))
15356 and then In_Open_Scopes (Entity (N))
15357 and then not In_Access_Definition (N);
15358 end Is_Protected_Self_Reference;
15360 -----------------------------
15361 -- Is_RCI_Pkg_Spec_Or_Body --
15362 -----------------------------
15364 function Is_RCI_Pkg_Spec_Or_Body (Cunit : Node_Id) return Boolean is
15366 function Is_RCI_Pkg_Decl_Cunit (Cunit : Node_Id) return Boolean;
15367 -- Return True if the unit of Cunit is an RCI package declaration
15369 ---------------------------
15370 -- Is_RCI_Pkg_Decl_Cunit --
15371 ---------------------------
15373 function Is_RCI_Pkg_Decl_Cunit (Cunit : Node_Id) return Boolean is
15374 The_Unit : constant Node_Id := Unit (Cunit);
15376 begin
15377 if Nkind (The_Unit) /= N_Package_Declaration then
15378 return False;
15379 end if;
15381 return Is_Remote_Call_Interface (Defining_Entity (The_Unit));
15382 end Is_RCI_Pkg_Decl_Cunit;
15384 -- Start of processing for Is_RCI_Pkg_Spec_Or_Body
15386 begin
15387 return Is_RCI_Pkg_Decl_Cunit (Cunit)
15388 or else
15389 (Nkind (Unit (Cunit)) = N_Package_Body
15390 and then Is_RCI_Pkg_Decl_Cunit (Library_Unit (Cunit)));
15391 end Is_RCI_Pkg_Spec_Or_Body;
15393 -----------------------------------------
15394 -- Is_Remote_Access_To_Class_Wide_Type --
15395 -----------------------------------------
15397 function Is_Remote_Access_To_Class_Wide_Type
15398 (E : Entity_Id) return Boolean
15400 begin
15401 -- A remote access to class-wide type is a general access to object type
15402 -- declared in the visible part of a Remote_Types or Remote_Call_
15403 -- Interface unit.
15405 return Ekind (E) = E_General_Access_Type
15406 and then (Is_Remote_Call_Interface (E) or else Is_Remote_Types (E));
15407 end Is_Remote_Access_To_Class_Wide_Type;
15409 -----------------------------------------
15410 -- Is_Remote_Access_To_Subprogram_Type --
15411 -----------------------------------------
15413 function Is_Remote_Access_To_Subprogram_Type
15414 (E : Entity_Id) return Boolean
15416 begin
15417 return (Ekind (E) = E_Access_Subprogram_Type
15418 or else (Ekind (E) = E_Record_Type
15419 and then Present (Corresponding_Remote_Type (E))))
15420 and then (Is_Remote_Call_Interface (E) or else Is_Remote_Types (E));
15421 end Is_Remote_Access_To_Subprogram_Type;
15423 --------------------
15424 -- Is_Remote_Call --
15425 --------------------
15427 function Is_Remote_Call (N : Node_Id) return Boolean is
15428 begin
15429 if Nkind (N) not in N_Subprogram_Call then
15431 -- An entry call cannot be remote
15433 return False;
15435 elsif Nkind (Name (N)) in N_Has_Entity
15436 and then Is_Remote_Call_Interface (Entity (Name (N)))
15437 then
15438 -- A subprogram declared in the spec of a RCI package is remote
15440 return True;
15442 elsif Nkind (Name (N)) = N_Explicit_Dereference
15443 and then Is_Remote_Access_To_Subprogram_Type
15444 (Etype (Prefix (Name (N))))
15445 then
15446 -- The dereference of a RAS is a remote call
15448 return True;
15450 elsif Present (Controlling_Argument (N))
15451 and then Is_Remote_Access_To_Class_Wide_Type
15452 (Etype (Controlling_Argument (N)))
15453 then
15454 -- Any primitive operation call with a controlling argument of
15455 -- a RACW type is a remote call.
15457 return True;
15458 end if;
15460 -- All other calls are local calls
15462 return False;
15463 end Is_Remote_Call;
15465 ----------------------
15466 -- Is_Renamed_Entry --
15467 ----------------------
15469 function Is_Renamed_Entry (Proc_Nam : Entity_Id) return Boolean is
15470 Orig_Node : Node_Id := Empty;
15471 Subp_Decl : Node_Id := Parent (Parent (Proc_Nam));
15473 function Is_Entry (Nam : Node_Id) return Boolean;
15474 -- Determine whether Nam is an entry. Traverse selectors if there are
15475 -- nested selected components.
15477 --------------
15478 -- Is_Entry --
15479 --------------
15481 function Is_Entry (Nam : Node_Id) return Boolean is
15482 begin
15483 if Nkind (Nam) = N_Selected_Component then
15484 return Is_Entry (Selector_Name (Nam));
15485 end if;
15487 return Ekind (Entity (Nam)) = E_Entry;
15488 end Is_Entry;
15490 -- Start of processing for Is_Renamed_Entry
15492 begin
15493 if Present (Alias (Proc_Nam)) then
15494 Subp_Decl := Parent (Parent (Alias (Proc_Nam)));
15495 end if;
15497 -- Look for a rewritten subprogram renaming declaration
15499 if Nkind (Subp_Decl) = N_Subprogram_Declaration
15500 and then Present (Original_Node (Subp_Decl))
15501 then
15502 Orig_Node := Original_Node (Subp_Decl);
15503 end if;
15505 -- The rewritten subprogram is actually an entry
15507 if Present (Orig_Node)
15508 and then Nkind (Orig_Node) = N_Subprogram_Renaming_Declaration
15509 and then Is_Entry (Name (Orig_Node))
15510 then
15511 return True;
15512 end if;
15514 return False;
15515 end Is_Renamed_Entry;
15517 -----------------------------
15518 -- Is_Renaming_Declaration --
15519 -----------------------------
15521 function Is_Renaming_Declaration (N : Node_Id) return Boolean is
15522 begin
15523 case Nkind (N) is
15524 when N_Exception_Renaming_Declaration
15525 | N_Generic_Function_Renaming_Declaration
15526 | N_Generic_Package_Renaming_Declaration
15527 | N_Generic_Procedure_Renaming_Declaration
15528 | N_Object_Renaming_Declaration
15529 | N_Package_Renaming_Declaration
15530 | N_Subprogram_Renaming_Declaration
15532 return True;
15534 when others =>
15535 return False;
15536 end case;
15537 end Is_Renaming_Declaration;
15539 ----------------------------
15540 -- Is_Reversible_Iterator --
15541 ----------------------------
15543 function Is_Reversible_Iterator (Typ : Entity_Id) return Boolean is
15544 Ifaces_List : Elist_Id;
15545 Iface_Elmt : Elmt_Id;
15546 Iface : Entity_Id;
15548 begin
15549 if Is_Class_Wide_Type (Typ)
15550 and then Chars (Root_Type (Typ)) = Name_Reversible_Iterator
15551 and then In_Predefined_Unit (Root_Type (Typ))
15552 then
15553 return True;
15555 elsif not Is_Tagged_Type (Typ) or else not Is_Derived_Type (Typ) then
15556 return False;
15558 else
15559 Collect_Interfaces (Typ, Ifaces_List);
15561 Iface_Elmt := First_Elmt (Ifaces_List);
15562 while Present (Iface_Elmt) loop
15563 Iface := Node (Iface_Elmt);
15564 if Chars (Iface) = Name_Reversible_Iterator
15565 and then In_Predefined_Unit (Iface)
15566 then
15567 return True;
15568 end if;
15570 Next_Elmt (Iface_Elmt);
15571 end loop;
15572 end if;
15574 return False;
15575 end Is_Reversible_Iterator;
15577 ----------------------
15578 -- Is_Selector_Name --
15579 ----------------------
15581 function Is_Selector_Name (N : Node_Id) return Boolean is
15582 begin
15583 if not Is_List_Member (N) then
15584 declare
15585 P : constant Node_Id := Parent (N);
15586 begin
15587 return Nkind_In (P, N_Expanded_Name,
15588 N_Generic_Association,
15589 N_Parameter_Association,
15590 N_Selected_Component)
15591 and then Selector_Name (P) = N;
15592 end;
15594 else
15595 declare
15596 L : constant List_Id := List_Containing (N);
15597 P : constant Node_Id := Parent (L);
15598 begin
15599 return (Nkind (P) = N_Discriminant_Association
15600 and then Selector_Names (P) = L)
15601 or else
15602 (Nkind (P) = N_Component_Association
15603 and then Choices (P) = L);
15604 end;
15605 end if;
15606 end Is_Selector_Name;
15608 ---------------------------------
15609 -- Is_Single_Concurrent_Object --
15610 ---------------------------------
15612 function Is_Single_Concurrent_Object (Id : Entity_Id) return Boolean is
15613 begin
15614 return
15615 Is_Single_Protected_Object (Id) or else Is_Single_Task_Object (Id);
15616 end Is_Single_Concurrent_Object;
15618 -------------------------------
15619 -- Is_Single_Concurrent_Type --
15620 -------------------------------
15622 function Is_Single_Concurrent_Type (Id : Entity_Id) return Boolean is
15623 begin
15624 return
15625 Ekind_In (Id, E_Protected_Type, E_Task_Type)
15626 and then Is_Single_Concurrent_Type_Declaration
15627 (Declaration_Node (Id));
15628 end Is_Single_Concurrent_Type;
15630 -------------------------------------------
15631 -- Is_Single_Concurrent_Type_Declaration --
15632 -------------------------------------------
15634 function Is_Single_Concurrent_Type_Declaration
15635 (N : Node_Id) return Boolean
15637 begin
15638 return Nkind_In (Original_Node (N), N_Single_Protected_Declaration,
15639 N_Single_Task_Declaration);
15640 end Is_Single_Concurrent_Type_Declaration;
15642 ---------------------------------------------
15643 -- Is_Single_Precision_Floating_Point_Type --
15644 ---------------------------------------------
15646 function Is_Single_Precision_Floating_Point_Type
15647 (E : Entity_Id) return Boolean is
15648 begin
15649 return Is_Floating_Point_Type (E)
15650 and then Machine_Radix_Value (E) = Uint_2
15651 and then Machine_Mantissa_Value (E) = Uint_24
15652 and then Machine_Emax_Value (E) = Uint_2 ** Uint_7
15653 and then Machine_Emin_Value (E) = Uint_3 - (Uint_2 ** Uint_7);
15654 end Is_Single_Precision_Floating_Point_Type;
15656 --------------------------------
15657 -- Is_Single_Protected_Object --
15658 --------------------------------
15660 function Is_Single_Protected_Object (Id : Entity_Id) return Boolean is
15661 begin
15662 return
15663 Ekind (Id) = E_Variable
15664 and then Ekind (Etype (Id)) = E_Protected_Type
15665 and then Is_Single_Concurrent_Type (Etype (Id));
15666 end Is_Single_Protected_Object;
15668 ---------------------------
15669 -- Is_Single_Task_Object --
15670 ---------------------------
15672 function Is_Single_Task_Object (Id : Entity_Id) return Boolean is
15673 begin
15674 return
15675 Ekind (Id) = E_Variable
15676 and then Ekind (Etype (Id)) = E_Task_Type
15677 and then Is_Single_Concurrent_Type (Etype (Id));
15678 end Is_Single_Task_Object;
15680 -------------------------------------
15681 -- Is_SPARK_05_Initialization_Expr --
15682 -------------------------------------
15684 function Is_SPARK_05_Initialization_Expr (N : Node_Id) return Boolean is
15685 Is_Ok : Boolean;
15686 Expr : Node_Id;
15687 Comp_Assn : Node_Id;
15688 Orig_N : constant Node_Id := Original_Node (N);
15690 begin
15691 Is_Ok := True;
15693 if not Comes_From_Source (Orig_N) then
15694 goto Done;
15695 end if;
15697 pragma Assert (Nkind (Orig_N) in N_Subexpr);
15699 case Nkind (Orig_N) is
15700 when N_Character_Literal
15701 | N_Integer_Literal
15702 | N_Real_Literal
15703 | N_String_Literal
15705 null;
15707 when N_Expanded_Name
15708 | N_Identifier
15710 if Is_Entity_Name (Orig_N)
15711 and then Present (Entity (Orig_N)) -- needed in some cases
15712 then
15713 case Ekind (Entity (Orig_N)) is
15714 when E_Constant
15715 | E_Enumeration_Literal
15716 | E_Named_Integer
15717 | E_Named_Real
15719 null;
15721 when others =>
15722 if Is_Type (Entity (Orig_N)) then
15723 null;
15724 else
15725 Is_Ok := False;
15726 end if;
15727 end case;
15728 end if;
15730 when N_Qualified_Expression
15731 | N_Type_Conversion
15733 Is_Ok := Is_SPARK_05_Initialization_Expr (Expression (Orig_N));
15735 when N_Unary_Op =>
15736 Is_Ok := Is_SPARK_05_Initialization_Expr (Right_Opnd (Orig_N));
15738 when N_Binary_Op
15739 | N_Membership_Test
15740 | N_Short_Circuit
15742 Is_Ok := Is_SPARK_05_Initialization_Expr (Left_Opnd (Orig_N))
15743 and then
15744 Is_SPARK_05_Initialization_Expr (Right_Opnd (Orig_N));
15746 when N_Aggregate
15747 | N_Extension_Aggregate
15749 if Nkind (Orig_N) = N_Extension_Aggregate then
15750 Is_Ok :=
15751 Is_SPARK_05_Initialization_Expr (Ancestor_Part (Orig_N));
15752 end if;
15754 Expr := First (Expressions (Orig_N));
15755 while Present (Expr) loop
15756 if not Is_SPARK_05_Initialization_Expr (Expr) then
15757 Is_Ok := False;
15758 goto Done;
15759 end if;
15761 Next (Expr);
15762 end loop;
15764 Comp_Assn := First (Component_Associations (Orig_N));
15765 while Present (Comp_Assn) loop
15766 Expr := Expression (Comp_Assn);
15768 -- Note: test for Present here needed for box assocation
15770 if Present (Expr)
15771 and then not Is_SPARK_05_Initialization_Expr (Expr)
15772 then
15773 Is_Ok := False;
15774 goto Done;
15775 end if;
15777 Next (Comp_Assn);
15778 end loop;
15780 when N_Attribute_Reference =>
15781 if Nkind (Prefix (Orig_N)) in N_Subexpr then
15782 Is_Ok := Is_SPARK_05_Initialization_Expr (Prefix (Orig_N));
15783 end if;
15785 Expr := First (Expressions (Orig_N));
15786 while Present (Expr) loop
15787 if not Is_SPARK_05_Initialization_Expr (Expr) then
15788 Is_Ok := False;
15789 goto Done;
15790 end if;
15792 Next (Expr);
15793 end loop;
15795 -- Selected components might be expanded named not yet resolved, so
15796 -- default on the safe side. (Eg on sparklex.ads)
15798 when N_Selected_Component =>
15799 null;
15801 when others =>
15802 Is_Ok := False;
15803 end case;
15805 <<Done>>
15806 return Is_Ok;
15807 end Is_SPARK_05_Initialization_Expr;
15809 ----------------------------------
15810 -- Is_SPARK_05_Object_Reference --
15811 ----------------------------------
15813 function Is_SPARK_05_Object_Reference (N : Node_Id) return Boolean is
15814 begin
15815 if Is_Entity_Name (N) then
15816 return Present (Entity (N))
15817 and then
15818 (Ekind_In (Entity (N), E_Constant, E_Variable)
15819 or else Ekind (Entity (N)) in Formal_Kind);
15821 else
15822 case Nkind (N) is
15823 when N_Selected_Component =>
15824 return Is_SPARK_05_Object_Reference (Prefix (N));
15826 when others =>
15827 return False;
15828 end case;
15829 end if;
15830 end Is_SPARK_05_Object_Reference;
15832 -----------------------------
15833 -- Is_Specific_Tagged_Type --
15834 -----------------------------
15836 function Is_Specific_Tagged_Type (Typ : Entity_Id) return Boolean is
15837 Full_Typ : Entity_Id;
15839 begin
15840 -- Handle private types
15842 if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
15843 Full_Typ := Full_View (Typ);
15844 else
15845 Full_Typ := Typ;
15846 end if;
15848 -- A specific tagged type is a non-class-wide tagged type
15850 return Is_Tagged_Type (Full_Typ) and not Is_Class_Wide_Type (Full_Typ);
15851 end Is_Specific_Tagged_Type;
15853 ------------------
15854 -- Is_Statement --
15855 ------------------
15857 function Is_Statement (N : Node_Id) return Boolean is
15858 begin
15859 return
15860 Nkind (N) in N_Statement_Other_Than_Procedure_Call
15861 or else Nkind (N) = N_Procedure_Call_Statement;
15862 end Is_Statement;
15864 ---------------------------------------
15865 -- Is_Subprogram_Contract_Annotation --
15866 ---------------------------------------
15868 function Is_Subprogram_Contract_Annotation
15869 (Item : Node_Id) return Boolean
15871 Nam : Name_Id;
15873 begin
15874 if Nkind (Item) = N_Aspect_Specification then
15875 Nam := Chars (Identifier (Item));
15877 else pragma Assert (Nkind (Item) = N_Pragma);
15878 Nam := Pragma_Name (Item);
15879 end if;
15881 return Nam = Name_Contract_Cases
15882 or else Nam = Name_Depends
15883 or else Nam = Name_Extensions_Visible
15884 or else Nam = Name_Global
15885 or else Nam = Name_Post
15886 or else Nam = Name_Post_Class
15887 or else Nam = Name_Postcondition
15888 or else Nam = Name_Pre
15889 or else Nam = Name_Pre_Class
15890 or else Nam = Name_Precondition
15891 or else Nam = Name_Refined_Depends
15892 or else Nam = Name_Refined_Global
15893 or else Nam = Name_Refined_Post
15894 or else Nam = Name_Test_Case;
15895 end Is_Subprogram_Contract_Annotation;
15897 --------------------------------------------------
15898 -- Is_Subprogram_Stub_Without_Prior_Declaration --
15899 --------------------------------------------------
15901 function Is_Subprogram_Stub_Without_Prior_Declaration
15902 (N : Node_Id) return Boolean
15904 begin
15905 -- A subprogram stub without prior declaration serves as declaration for
15906 -- the actual subprogram body. As such, it has an attached defining
15907 -- entity of E_[Generic_]Function or E_[Generic_]Procedure.
15909 return Nkind (N) = N_Subprogram_Body_Stub
15910 and then Ekind (Defining_Entity (N)) /= E_Subprogram_Body;
15911 end Is_Subprogram_Stub_Without_Prior_Declaration;
15913 --------------------------
15914 -- Is_Suspension_Object --
15915 --------------------------
15917 function Is_Suspension_Object (Id : Entity_Id) return Boolean is
15918 begin
15919 -- This approach does an exact name match rather than to rely on
15920 -- RTSfind. Routine Is_Effectively_Volatile is used by clients of the
15921 -- front end at point where all auxiliary tables are locked and any
15922 -- modifications to them are treated as violations. Do not tamper with
15923 -- the tables, instead examine the Chars fields of all the scopes of Id.
15925 return
15926 Chars (Id) = Name_Suspension_Object
15927 and then Present (Scope (Id))
15928 and then Chars (Scope (Id)) = Name_Synchronous_Task_Control
15929 and then Present (Scope (Scope (Id)))
15930 and then Chars (Scope (Scope (Id))) = Name_Ada
15931 and then Present (Scope (Scope (Scope (Id))))
15932 and then Scope (Scope (Scope (Id))) = Standard_Standard;
15933 end Is_Suspension_Object;
15935 ----------------------------
15936 -- Is_Synchronized_Object --
15937 ----------------------------
15939 function Is_Synchronized_Object (Id : Entity_Id) return Boolean is
15940 Prag : Node_Id;
15942 begin
15943 if Is_Object (Id) then
15945 -- The object is synchronized if it is of a type that yields a
15946 -- synchronized object.
15948 if Yields_Synchronized_Object (Etype (Id)) then
15949 return True;
15951 -- The object is synchronized if it is atomic and Async_Writers is
15952 -- enabled.
15954 elsif Is_Atomic (Id) and then Async_Writers_Enabled (Id) then
15955 return True;
15957 -- A constant is a synchronized object by default
15959 elsif Ekind (Id) = E_Constant then
15960 return True;
15962 -- A variable is a synchronized object if it is subject to pragma
15963 -- Constant_After_Elaboration.
15965 elsif Ekind (Id) = E_Variable then
15966 Prag := Get_Pragma (Id, Pragma_Constant_After_Elaboration);
15968 return Present (Prag) and then Is_Enabled_Pragma (Prag);
15969 end if;
15970 end if;
15972 -- Otherwise the input is not an object or it does not qualify as a
15973 -- synchronized object.
15975 return False;
15976 end Is_Synchronized_Object;
15978 ---------------------------------
15979 -- Is_Synchronized_Tagged_Type --
15980 ---------------------------------
15982 function Is_Synchronized_Tagged_Type (E : Entity_Id) return Boolean is
15983 Kind : constant Entity_Kind := Ekind (Base_Type (E));
15985 begin
15986 -- A task or protected type derived from an interface is a tagged type.
15987 -- Such a tagged type is called a synchronized tagged type, as are
15988 -- synchronized interfaces and private extensions whose declaration
15989 -- includes the reserved word synchronized.
15991 return (Is_Tagged_Type (E)
15992 and then (Kind = E_Task_Type
15993 or else
15994 Kind = E_Protected_Type))
15995 or else
15996 (Is_Interface (E)
15997 and then Is_Synchronized_Interface (E))
15998 or else
15999 (Ekind (E) = E_Record_Type_With_Private
16000 and then Nkind (Parent (E)) = N_Private_Extension_Declaration
16001 and then (Synchronized_Present (Parent (E))
16002 or else Is_Synchronized_Interface (Etype (E))));
16003 end Is_Synchronized_Tagged_Type;
16005 -----------------
16006 -- Is_Transfer --
16007 -----------------
16009 function Is_Transfer (N : Node_Id) return Boolean is
16010 Kind : constant Node_Kind := Nkind (N);
16012 begin
16013 if Kind = N_Simple_Return_Statement
16014 or else
16015 Kind = N_Extended_Return_Statement
16016 or else
16017 Kind = N_Goto_Statement
16018 or else
16019 Kind = N_Raise_Statement
16020 or else
16021 Kind = N_Requeue_Statement
16022 then
16023 return True;
16025 elsif (Kind = N_Exit_Statement or else Kind in N_Raise_xxx_Error)
16026 and then No (Condition (N))
16027 then
16028 return True;
16030 elsif Kind = N_Procedure_Call_Statement
16031 and then Is_Entity_Name (Name (N))
16032 and then Present (Entity (Name (N)))
16033 and then No_Return (Entity (Name (N)))
16034 then
16035 return True;
16037 elsif Nkind (Original_Node (N)) = N_Raise_Statement then
16038 return True;
16040 else
16041 return False;
16042 end if;
16043 end Is_Transfer;
16045 -------------
16046 -- Is_True --
16047 -------------
16049 function Is_True (U : Uint) return Boolean is
16050 begin
16051 return (U /= 0);
16052 end Is_True;
16054 --------------------------------------
16055 -- Is_Unchecked_Conversion_Instance --
16056 --------------------------------------
16058 function Is_Unchecked_Conversion_Instance (Id : Entity_Id) return Boolean is
16059 Par : Node_Id;
16061 begin
16062 -- Look for a function whose generic parent is the predefined intrinsic
16063 -- function Unchecked_Conversion, or for one that renames such an
16064 -- instance.
16066 if Ekind (Id) = E_Function then
16067 Par := Parent (Id);
16069 if Nkind (Par) = N_Function_Specification then
16070 Par := Generic_Parent (Par);
16072 if Present (Par) then
16073 return
16074 Chars (Par) = Name_Unchecked_Conversion
16075 and then Is_Intrinsic_Subprogram (Par)
16076 and then In_Predefined_Unit (Par);
16077 else
16078 return
16079 Present (Alias (Id))
16080 and then Is_Unchecked_Conversion_Instance (Alias (Id));
16081 end if;
16082 end if;
16083 end if;
16085 return False;
16086 end Is_Unchecked_Conversion_Instance;
16088 -------------------------------
16089 -- Is_Universal_Numeric_Type --
16090 -------------------------------
16092 function Is_Universal_Numeric_Type (T : Entity_Id) return Boolean is
16093 begin
16094 return T = Universal_Integer or else T = Universal_Real;
16095 end Is_Universal_Numeric_Type;
16097 ------------------------------
16098 -- Is_User_Defined_Equality --
16099 ------------------------------
16101 function Is_User_Defined_Equality (Id : Entity_Id) return Boolean is
16102 begin
16103 return Ekind (Id) = E_Function
16104 and then Chars (Id) = Name_Op_Eq
16105 and then Comes_From_Source (Id)
16107 -- Internally generated equalities have a full type declaration
16108 -- as their parent.
16110 and then Nkind (Parent (Id)) = N_Function_Specification;
16111 end Is_User_Defined_Equality;
16113 --------------------------------------
16114 -- Is_Validation_Variable_Reference --
16115 --------------------------------------
16117 function Is_Validation_Variable_Reference (N : Node_Id) return Boolean is
16118 Var : constant Node_Id := Unqual_Conv (N);
16119 Var_Id : Entity_Id;
16121 begin
16122 Var_Id := Empty;
16124 if Is_Entity_Name (Var) then
16125 Var_Id := Entity (Var);
16126 end if;
16128 return
16129 Present (Var_Id)
16130 and then Ekind (Var_Id) = E_Variable
16131 and then Present (Validated_Object (Var_Id));
16132 end Is_Validation_Variable_Reference;
16134 ----------------------------
16135 -- Is_Variable_Size_Array --
16136 ----------------------------
16138 function Is_Variable_Size_Array (E : Entity_Id) return Boolean is
16139 Idx : Node_Id;
16141 begin
16142 pragma Assert (Is_Array_Type (E));
16144 -- Check if some index is initialized with a non-constant value
16146 Idx := First_Index (E);
16147 while Present (Idx) loop
16148 if Nkind (Idx) = N_Range then
16149 if not Is_Constant_Bound (Low_Bound (Idx))
16150 or else not Is_Constant_Bound (High_Bound (Idx))
16151 then
16152 return True;
16153 end if;
16154 end if;
16156 Idx := Next_Index (Idx);
16157 end loop;
16159 return False;
16160 end Is_Variable_Size_Array;
16162 -----------------------------
16163 -- Is_Variable_Size_Record --
16164 -----------------------------
16166 function Is_Variable_Size_Record (E : Entity_Id) return Boolean is
16167 Comp : Entity_Id;
16168 Comp_Typ : Entity_Id;
16170 begin
16171 pragma Assert (Is_Record_Type (E));
16173 Comp := First_Entity (E);
16174 while Present (Comp) loop
16175 Comp_Typ := Etype (Comp);
16177 -- Recursive call if the record type has discriminants
16179 if Is_Record_Type (Comp_Typ)
16180 and then Has_Discriminants (Comp_Typ)
16181 and then Is_Variable_Size_Record (Comp_Typ)
16182 then
16183 return True;
16185 elsif Is_Array_Type (Comp_Typ)
16186 and then Is_Variable_Size_Array (Comp_Typ)
16187 then
16188 return True;
16189 end if;
16191 Next_Entity (Comp);
16192 end loop;
16194 return False;
16195 end Is_Variable_Size_Record;
16197 -----------------
16198 -- Is_Variable --
16199 -----------------
16201 function Is_Variable
16202 (N : Node_Id;
16203 Use_Original_Node : Boolean := True) return Boolean
16205 Orig_Node : Node_Id;
16207 function In_Protected_Function (E : Entity_Id) return Boolean;
16208 -- Within a protected function, the private components of the enclosing
16209 -- protected type are constants. A function nested within a (protected)
16210 -- procedure is not itself protected. Within the body of a protected
16211 -- function the current instance of the protected type is a constant.
16213 function Is_Variable_Prefix (P : Node_Id) return Boolean;
16214 -- Prefixes can involve implicit dereferences, in which case we must
16215 -- test for the case of a reference of a constant access type, which can
16216 -- can never be a variable.
16218 ---------------------------
16219 -- In_Protected_Function --
16220 ---------------------------
16222 function In_Protected_Function (E : Entity_Id) return Boolean is
16223 Prot : Entity_Id;
16224 S : Entity_Id;
16226 begin
16227 -- E is the current instance of a type
16229 if Is_Type (E) then
16230 Prot := E;
16232 -- E is an object
16234 else
16235 Prot := Scope (E);
16236 end if;
16238 if not Is_Protected_Type (Prot) then
16239 return False;
16241 else
16242 S := Current_Scope;
16243 while Present (S) and then S /= Prot loop
16244 if Ekind (S) = E_Function and then Scope (S) = Prot then
16245 return True;
16246 end if;
16248 S := Scope (S);
16249 end loop;
16251 return False;
16252 end if;
16253 end In_Protected_Function;
16255 ------------------------
16256 -- Is_Variable_Prefix --
16257 ------------------------
16259 function Is_Variable_Prefix (P : Node_Id) return Boolean is
16260 begin
16261 if Is_Access_Type (Etype (P)) then
16262 return not Is_Access_Constant (Root_Type (Etype (P)));
16264 -- For the case of an indexed component whose prefix has a packed
16265 -- array type, the prefix has been rewritten into a type conversion.
16266 -- Determine variable-ness from the converted expression.
16268 elsif Nkind (P) = N_Type_Conversion
16269 and then not Comes_From_Source (P)
16270 and then Is_Array_Type (Etype (P))
16271 and then Is_Packed (Etype (P))
16272 then
16273 return Is_Variable (Expression (P));
16275 else
16276 return Is_Variable (P);
16277 end if;
16278 end Is_Variable_Prefix;
16280 -- Start of processing for Is_Variable
16282 begin
16283 -- Special check, allow x'Deref(expr) as a variable
16285 if Nkind (N) = N_Attribute_Reference
16286 and then Attribute_Name (N) = Name_Deref
16287 then
16288 return True;
16289 end if;
16291 -- Check if we perform the test on the original node since this may be a
16292 -- test of syntactic categories which must not be disturbed by whatever
16293 -- rewriting might have occurred. For example, an aggregate, which is
16294 -- certainly NOT a variable, could be turned into a variable by
16295 -- expansion.
16297 if Use_Original_Node then
16298 Orig_Node := Original_Node (N);
16299 else
16300 Orig_Node := N;
16301 end if;
16303 -- Definitely OK if Assignment_OK is set. Since this is something that
16304 -- only gets set for expanded nodes, the test is on N, not Orig_Node.
16306 if Nkind (N) in N_Subexpr and then Assignment_OK (N) then
16307 return True;
16309 -- Normally we go to the original node, but there is one exception where
16310 -- we use the rewritten node, namely when it is an explicit dereference.
16311 -- The generated code may rewrite a prefix which is an access type with
16312 -- an explicit dereference. The dereference is a variable, even though
16313 -- the original node may not be (since it could be a constant of the
16314 -- access type).
16316 -- In Ada 2005 we have a further case to consider: the prefix may be a
16317 -- function call given in prefix notation. The original node appears to
16318 -- be a selected component, but we need to examine the call.
16320 elsif Nkind (N) = N_Explicit_Dereference
16321 and then Nkind (Orig_Node) /= N_Explicit_Dereference
16322 and then Present (Etype (Orig_Node))
16323 and then Is_Access_Type (Etype (Orig_Node))
16324 then
16325 -- Note that if the prefix is an explicit dereference that does not
16326 -- come from source, we must check for a rewritten function call in
16327 -- prefixed notation before other forms of rewriting, to prevent a
16328 -- compiler crash.
16330 return
16331 (Nkind (Orig_Node) = N_Function_Call
16332 and then not Is_Access_Constant (Etype (Prefix (N))))
16333 or else
16334 Is_Variable_Prefix (Original_Node (Prefix (N)));
16336 -- in Ada 2012, the dereference may have been added for a type with
16337 -- a declared implicit dereference aspect. Check that it is not an
16338 -- access to constant.
16340 elsif Nkind (N) = N_Explicit_Dereference
16341 and then Present (Etype (Orig_Node))
16342 and then Ada_Version >= Ada_2012
16343 and then Has_Implicit_Dereference (Etype (Orig_Node))
16344 then
16345 return not Is_Access_Constant (Etype (Prefix (N)));
16347 -- A function call is never a variable
16349 elsif Nkind (N) = N_Function_Call then
16350 return False;
16352 -- All remaining checks use the original node
16354 elsif Is_Entity_Name (Orig_Node)
16355 and then Present (Entity (Orig_Node))
16356 then
16357 declare
16358 E : constant Entity_Id := Entity (Orig_Node);
16359 K : constant Entity_Kind := Ekind (E);
16361 begin
16362 return (K = E_Variable
16363 and then Nkind (Parent (E)) /= N_Exception_Handler)
16364 or else (K = E_Component
16365 and then not In_Protected_Function (E))
16366 or else K = E_Out_Parameter
16367 or else K = E_In_Out_Parameter
16368 or else K = E_Generic_In_Out_Parameter
16370 -- Current instance of type. If this is a protected type, check
16371 -- we are not within the body of one of its protected functions.
16373 or else (Is_Type (E)
16374 and then In_Open_Scopes (E)
16375 and then not In_Protected_Function (E))
16377 or else (Is_Incomplete_Or_Private_Type (E)
16378 and then In_Open_Scopes (Full_View (E)));
16379 end;
16381 else
16382 case Nkind (Orig_Node) is
16383 when N_Indexed_Component
16384 | N_Slice
16386 return Is_Variable_Prefix (Prefix (Orig_Node));
16388 when N_Selected_Component =>
16389 return (Is_Variable (Selector_Name (Orig_Node))
16390 and then Is_Variable_Prefix (Prefix (Orig_Node)))
16391 or else
16392 (Nkind (N) = N_Expanded_Name
16393 and then Scope (Entity (N)) = Entity (Prefix (N)));
16395 -- For an explicit dereference, the type of the prefix cannot
16396 -- be an access to constant or an access to subprogram.
16398 when N_Explicit_Dereference =>
16399 declare
16400 Typ : constant Entity_Id := Etype (Prefix (Orig_Node));
16401 begin
16402 return Is_Access_Type (Typ)
16403 and then not Is_Access_Constant (Root_Type (Typ))
16404 and then Ekind (Typ) /= E_Access_Subprogram_Type;
16405 end;
16407 -- The type conversion is the case where we do not deal with the
16408 -- context dependent special case of an actual parameter. Thus
16409 -- the type conversion is only considered a variable for the
16410 -- purposes of this routine if the target type is tagged. However,
16411 -- a type conversion is considered to be a variable if it does not
16412 -- come from source (this deals for example with the conversions
16413 -- of expressions to their actual subtypes).
16415 when N_Type_Conversion =>
16416 return Is_Variable (Expression (Orig_Node))
16417 and then
16418 (not Comes_From_Source (Orig_Node)
16419 or else
16420 (Is_Tagged_Type (Etype (Subtype_Mark (Orig_Node)))
16421 and then
16422 Is_Tagged_Type (Etype (Expression (Orig_Node)))));
16424 -- GNAT allows an unchecked type conversion as a variable. This
16425 -- only affects the generation of internal expanded code, since
16426 -- calls to instantiations of Unchecked_Conversion are never
16427 -- considered variables (since they are function calls).
16429 when N_Unchecked_Type_Conversion =>
16430 return Is_Variable (Expression (Orig_Node));
16432 when others =>
16433 return False;
16434 end case;
16435 end if;
16436 end Is_Variable;
16438 ------------------------------
16439 -- Is_Verifiable_DIC_Pragma --
16440 ------------------------------
16442 function Is_Verifiable_DIC_Pragma (Prag : Node_Id) return Boolean is
16443 Args : constant List_Id := Pragma_Argument_Associations (Prag);
16445 begin
16446 -- To qualify as verifiable, a DIC pragma must have a non-null argument
16448 return
16449 Present (Args)
16450 and then Nkind (Get_Pragma_Arg (First (Args))) /= N_Null;
16451 end Is_Verifiable_DIC_Pragma;
16453 ---------------------------
16454 -- Is_Visibly_Controlled --
16455 ---------------------------
16457 function Is_Visibly_Controlled (T : Entity_Id) return Boolean is
16458 Root : constant Entity_Id := Root_Type (T);
16459 begin
16460 return Chars (Scope (Root)) = Name_Finalization
16461 and then Chars (Scope (Scope (Root))) = Name_Ada
16462 and then Scope (Scope (Scope (Root))) = Standard_Standard;
16463 end Is_Visibly_Controlled;
16465 --------------------------
16466 -- Is_Volatile_Function --
16467 --------------------------
16469 function Is_Volatile_Function (Func_Id : Entity_Id) return Boolean is
16470 begin
16471 pragma Assert (Ekind_In (Func_Id, E_Function, E_Generic_Function));
16473 -- A function declared within a protected type is volatile
16475 if Is_Protected_Type (Scope (Func_Id)) then
16476 return True;
16478 -- An instance of Ada.Unchecked_Conversion is a volatile function if
16479 -- either the source or the target are effectively volatile.
16481 elsif Is_Unchecked_Conversion_Instance (Func_Id)
16482 and then Has_Effectively_Volatile_Profile (Func_Id)
16483 then
16484 return True;
16486 -- Otherwise the function is treated as volatile if it is subject to
16487 -- enabled pragma Volatile_Function.
16489 else
16490 return
16491 Is_Enabled_Pragma (Get_Pragma (Func_Id, Pragma_Volatile_Function));
16492 end if;
16493 end Is_Volatile_Function;
16495 ------------------------
16496 -- Is_Volatile_Object --
16497 ------------------------
16499 function Is_Volatile_Object (N : Node_Id) return Boolean is
16500 function Is_Volatile_Prefix (N : Node_Id) return Boolean;
16501 -- If prefix is an implicit dereference, examine designated type
16503 function Object_Has_Volatile_Components (N : Node_Id) return Boolean;
16504 -- Determines if given object has volatile components
16506 ------------------------
16507 -- Is_Volatile_Prefix --
16508 ------------------------
16510 function Is_Volatile_Prefix (N : Node_Id) return Boolean is
16511 Typ : constant Entity_Id := Etype (N);
16513 begin
16514 if Is_Access_Type (Typ) then
16515 declare
16516 Dtyp : constant Entity_Id := Designated_Type (Typ);
16518 begin
16519 return Is_Volatile (Dtyp)
16520 or else Has_Volatile_Components (Dtyp);
16521 end;
16523 else
16524 return Object_Has_Volatile_Components (N);
16525 end if;
16526 end Is_Volatile_Prefix;
16528 ------------------------------------
16529 -- Object_Has_Volatile_Components --
16530 ------------------------------------
16532 function Object_Has_Volatile_Components (N : Node_Id) return Boolean is
16533 Typ : constant Entity_Id := Etype (N);
16535 begin
16536 if Is_Volatile (Typ)
16537 or else Has_Volatile_Components (Typ)
16538 then
16539 return True;
16541 elsif Is_Entity_Name (N)
16542 and then (Has_Volatile_Components (Entity (N))
16543 or else Is_Volatile (Entity (N)))
16544 then
16545 return True;
16547 elsif Nkind (N) = N_Indexed_Component
16548 or else Nkind (N) = N_Selected_Component
16549 then
16550 return Is_Volatile_Prefix (Prefix (N));
16552 else
16553 return False;
16554 end if;
16555 end Object_Has_Volatile_Components;
16557 -- Start of processing for Is_Volatile_Object
16559 begin
16560 if Nkind (N) = N_Defining_Identifier then
16561 return Is_Volatile (N) or else Is_Volatile (Etype (N));
16563 elsif Nkind (N) = N_Expanded_Name then
16564 return Is_Volatile_Object (Entity (N));
16566 elsif Is_Volatile (Etype (N))
16567 or else (Is_Entity_Name (N) and then Is_Volatile (Entity (N)))
16568 then
16569 return True;
16571 elsif Nkind_In (N, N_Indexed_Component, N_Selected_Component)
16572 and then Is_Volatile_Prefix (Prefix (N))
16573 then
16574 return True;
16576 elsif Nkind (N) = N_Selected_Component
16577 and then Is_Volatile (Entity (Selector_Name (N)))
16578 then
16579 return True;
16581 else
16582 return False;
16583 end if;
16584 end Is_Volatile_Object;
16586 -----------------------------
16587 -- Iterate_Call_Parameters --
16588 -----------------------------
16590 procedure Iterate_Call_Parameters (Call : Node_Id) is
16591 Formal : Entity_Id := First_Formal (Get_Called_Entity (Call));
16592 Actual : Node_Id := First_Actual (Call);
16594 begin
16595 while Present (Formal) and then Present (Actual) loop
16596 Handle_Parameter (Formal, Actual);
16597 Formal := Next_Formal (Formal);
16598 Actual := Next_Actual (Actual);
16599 end loop;
16600 end Iterate_Call_Parameters;
16602 ---------------------------
16603 -- Itype_Has_Declaration --
16604 ---------------------------
16606 function Itype_Has_Declaration (Id : Entity_Id) return Boolean is
16607 begin
16608 pragma Assert (Is_Itype (Id));
16609 return Present (Parent (Id))
16610 and then Nkind_In (Parent (Id), N_Full_Type_Declaration,
16611 N_Subtype_Declaration)
16612 and then Defining_Entity (Parent (Id)) = Id;
16613 end Itype_Has_Declaration;
16615 -------------------------
16616 -- Kill_Current_Values --
16617 -------------------------
16619 procedure Kill_Current_Values
16620 (Ent : Entity_Id;
16621 Last_Assignment_Only : Boolean := False)
16623 begin
16624 if Is_Assignable (Ent) then
16625 Set_Last_Assignment (Ent, Empty);
16626 end if;
16628 if Is_Object (Ent) then
16629 if not Last_Assignment_Only then
16630 Kill_Checks (Ent);
16631 Set_Current_Value (Ent, Empty);
16633 -- Do not reset the Is_Known_[Non_]Null and Is_Known_Valid flags
16634 -- for a constant. Once the constant is elaborated, its value is
16635 -- not changed, therefore the associated flags that describe the
16636 -- value should not be modified either.
16638 if Ekind (Ent) = E_Constant then
16639 null;
16641 -- Non-constant entities
16643 else
16644 if not Can_Never_Be_Null (Ent) then
16645 Set_Is_Known_Non_Null (Ent, False);
16646 end if;
16648 Set_Is_Known_Null (Ent, False);
16650 -- Reset the Is_Known_Valid flag unless the type is always
16651 -- valid. This does not apply to a loop parameter because its
16652 -- bounds are defined by the loop header and therefore always
16653 -- valid.
16655 if not Is_Known_Valid (Etype (Ent))
16656 and then Ekind (Ent) /= E_Loop_Parameter
16657 then
16658 Set_Is_Known_Valid (Ent, False);
16659 end if;
16660 end if;
16661 end if;
16662 end if;
16663 end Kill_Current_Values;
16665 procedure Kill_Current_Values (Last_Assignment_Only : Boolean := False) is
16666 S : Entity_Id;
16668 procedure Kill_Current_Values_For_Entity_Chain (E : Entity_Id);
16669 -- Clear current value for entity E and all entities chained to E
16671 ------------------------------------------
16672 -- Kill_Current_Values_For_Entity_Chain --
16673 ------------------------------------------
16675 procedure Kill_Current_Values_For_Entity_Chain (E : Entity_Id) is
16676 Ent : Entity_Id;
16677 begin
16678 Ent := E;
16679 while Present (Ent) loop
16680 Kill_Current_Values (Ent, Last_Assignment_Only);
16681 Next_Entity (Ent);
16682 end loop;
16683 end Kill_Current_Values_For_Entity_Chain;
16685 -- Start of processing for Kill_Current_Values
16687 begin
16688 -- Kill all saved checks, a special case of killing saved values
16690 if not Last_Assignment_Only then
16691 Kill_All_Checks;
16692 end if;
16694 -- Loop through relevant scopes, which includes the current scope and
16695 -- any parent scopes if the current scope is a block or a package.
16697 S := Current_Scope;
16698 Scope_Loop : loop
16700 -- Clear current values of all entities in current scope
16702 Kill_Current_Values_For_Entity_Chain (First_Entity (S));
16704 -- If scope is a package, also clear current values of all private
16705 -- entities in the scope.
16707 if Is_Package_Or_Generic_Package (S)
16708 or else Is_Concurrent_Type (S)
16709 then
16710 Kill_Current_Values_For_Entity_Chain (First_Private_Entity (S));
16711 end if;
16713 -- If this is a not a subprogram, deal with parents
16715 if not Is_Subprogram (S) then
16716 S := Scope (S);
16717 exit Scope_Loop when S = Standard_Standard;
16718 else
16719 exit Scope_Loop;
16720 end if;
16721 end loop Scope_Loop;
16722 end Kill_Current_Values;
16724 --------------------------
16725 -- Kill_Size_Check_Code --
16726 --------------------------
16728 procedure Kill_Size_Check_Code (E : Entity_Id) is
16729 begin
16730 if (Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
16731 and then Present (Size_Check_Code (E))
16732 then
16733 Remove (Size_Check_Code (E));
16734 Set_Size_Check_Code (E, Empty);
16735 end if;
16736 end Kill_Size_Check_Code;
16738 --------------------
16739 -- Known_Non_Null --
16740 --------------------
16742 function Known_Non_Null (N : Node_Id) return Boolean is
16743 Status : constant Null_Status_Kind := Null_Status (N);
16745 Id : Entity_Id;
16746 Op : Node_Kind;
16747 Val : Node_Id;
16749 begin
16750 -- The expression yields a non-null value ignoring simple flow analysis
16752 if Status = Is_Non_Null then
16753 return True;
16755 -- Otherwise check whether N is a reference to an entity that appears
16756 -- within a conditional construct.
16758 elsif Is_Entity_Name (N) and then Present (Entity (N)) then
16760 -- First check if we are in decisive conditional
16762 Get_Current_Value_Condition (N, Op, Val);
16764 if Known_Null (Val) then
16765 if Op = N_Op_Eq then
16766 return False;
16767 elsif Op = N_Op_Ne then
16768 return True;
16769 end if;
16770 end if;
16772 -- If OK to do replacement, test Is_Known_Non_Null flag
16774 Id := Entity (N);
16776 if OK_To_Do_Constant_Replacement (Id) then
16777 return Is_Known_Non_Null (Id);
16778 end if;
16779 end if;
16781 -- Otherwise it is not possible to determine whether N yields a non-null
16782 -- value.
16784 return False;
16785 end Known_Non_Null;
16787 ----------------
16788 -- Known_Null --
16789 ----------------
16791 function Known_Null (N : Node_Id) return Boolean is
16792 Status : constant Null_Status_Kind := Null_Status (N);
16794 Id : Entity_Id;
16795 Op : Node_Kind;
16796 Val : Node_Id;
16798 begin
16799 -- The expression yields a null value ignoring simple flow analysis
16801 if Status = Is_Null then
16802 return True;
16804 -- Otherwise check whether N is a reference to an entity that appears
16805 -- within a conditional construct.
16807 elsif Is_Entity_Name (N) and then Present (Entity (N)) then
16809 -- First check if we are in decisive conditional
16811 Get_Current_Value_Condition (N, Op, Val);
16813 if Known_Null (Val) then
16814 if Op = N_Op_Eq then
16815 return True;
16816 elsif Op = N_Op_Ne then
16817 return False;
16818 end if;
16819 end if;
16821 -- If OK to do replacement, test Is_Known_Null flag
16823 Id := Entity (N);
16825 if OK_To_Do_Constant_Replacement (Id) then
16826 return Is_Known_Null (Id);
16827 end if;
16828 end if;
16830 -- Otherwise it is not possible to determine whether N yields a null
16831 -- value.
16833 return False;
16834 end Known_Null;
16836 --------------------------
16837 -- Known_To_Be_Assigned --
16838 --------------------------
16840 function Known_To_Be_Assigned (N : Node_Id) return Boolean is
16841 P : constant Node_Id := Parent (N);
16843 begin
16844 case Nkind (P) is
16846 -- Test left side of assignment
16848 when N_Assignment_Statement =>
16849 return N = Name (P);
16851 -- Function call arguments are never lvalues
16853 when N_Function_Call =>
16854 return False;
16856 -- Positional parameter for procedure or accept call
16858 when N_Accept_Statement
16859 | N_Procedure_Call_Statement
16861 declare
16862 Proc : Entity_Id;
16863 Form : Entity_Id;
16864 Act : Node_Id;
16866 begin
16867 Proc := Get_Subprogram_Entity (P);
16869 if No (Proc) then
16870 return False;
16871 end if;
16873 -- If we are not a list member, something is strange, so
16874 -- be conservative and return False.
16876 if not Is_List_Member (N) then
16877 return False;
16878 end if;
16880 -- We are going to find the right formal by stepping forward
16881 -- through the formals, as we step backwards in the actuals.
16883 Form := First_Formal (Proc);
16884 Act := N;
16885 loop
16886 -- If no formal, something is weird, so be conservative
16887 -- and return False.
16889 if No (Form) then
16890 return False;
16891 end if;
16893 Prev (Act);
16894 exit when No (Act);
16895 Next_Formal (Form);
16896 end loop;
16898 return Ekind (Form) /= E_In_Parameter;
16899 end;
16901 -- Named parameter for procedure or accept call
16903 when N_Parameter_Association =>
16904 declare
16905 Proc : Entity_Id;
16906 Form : Entity_Id;
16908 begin
16909 Proc := Get_Subprogram_Entity (Parent (P));
16911 if No (Proc) then
16912 return False;
16913 end if;
16915 -- Loop through formals to find the one that matches
16917 Form := First_Formal (Proc);
16918 loop
16919 -- If no matching formal, that's peculiar, some kind of
16920 -- previous error, so return False to be conservative.
16921 -- Actually this also happens in legal code in the case
16922 -- where P is a parameter association for an Extra_Formal???
16924 if No (Form) then
16925 return False;
16926 end if;
16928 -- Else test for match
16930 if Chars (Form) = Chars (Selector_Name (P)) then
16931 return Ekind (Form) /= E_In_Parameter;
16932 end if;
16934 Next_Formal (Form);
16935 end loop;
16936 end;
16938 -- Test for appearing in a conversion that itself appears
16939 -- in an lvalue context, since this should be an lvalue.
16941 when N_Type_Conversion =>
16942 return Known_To_Be_Assigned (P);
16944 -- All other references are definitely not known to be modifications
16946 when others =>
16947 return False;
16948 end case;
16949 end Known_To_Be_Assigned;
16951 ---------------------------
16952 -- Last_Source_Statement --
16953 ---------------------------
16955 function Last_Source_Statement (HSS : Node_Id) return Node_Id is
16956 N : Node_Id;
16958 begin
16959 N := Last (Statements (HSS));
16960 while Present (N) loop
16961 exit when Comes_From_Source (N);
16962 Prev (N);
16963 end loop;
16965 return N;
16966 end Last_Source_Statement;
16968 ----------------------------------
16969 -- Matching_Static_Array_Bounds --
16970 ----------------------------------
16972 function Matching_Static_Array_Bounds
16973 (L_Typ : Node_Id;
16974 R_Typ : Node_Id) return Boolean
16976 L_Ndims : constant Nat := Number_Dimensions (L_Typ);
16977 R_Ndims : constant Nat := Number_Dimensions (R_Typ);
16979 L_Index : Node_Id;
16980 R_Index : Node_Id;
16981 L_Low : Node_Id;
16982 L_High : Node_Id;
16983 L_Len : Uint;
16984 R_Low : Node_Id;
16985 R_High : Node_Id;
16986 R_Len : Uint;
16988 begin
16989 if L_Ndims /= R_Ndims then
16990 return False;
16991 end if;
16993 -- Unconstrained types do not have static bounds
16995 if not Is_Constrained (L_Typ) or else not Is_Constrained (R_Typ) then
16996 return False;
16997 end if;
16999 -- First treat specially the first dimension, as the lower bound and
17000 -- length of string literals are not stored like those of arrays.
17002 if Ekind (L_Typ) = E_String_Literal_Subtype then
17003 L_Low := String_Literal_Low_Bound (L_Typ);
17004 L_Len := String_Literal_Length (L_Typ);
17005 else
17006 L_Index := First_Index (L_Typ);
17007 Get_Index_Bounds (L_Index, L_Low, L_High);
17009 if Is_OK_Static_Expression (L_Low)
17010 and then
17011 Is_OK_Static_Expression (L_High)
17012 then
17013 if Expr_Value (L_High) < Expr_Value (L_Low) then
17014 L_Len := Uint_0;
17015 else
17016 L_Len := (Expr_Value (L_High) - Expr_Value (L_Low)) + 1;
17017 end if;
17018 else
17019 return False;
17020 end if;
17021 end if;
17023 if Ekind (R_Typ) = E_String_Literal_Subtype then
17024 R_Low := String_Literal_Low_Bound (R_Typ);
17025 R_Len := String_Literal_Length (R_Typ);
17026 else
17027 R_Index := First_Index (R_Typ);
17028 Get_Index_Bounds (R_Index, R_Low, R_High);
17030 if Is_OK_Static_Expression (R_Low)
17031 and then
17032 Is_OK_Static_Expression (R_High)
17033 then
17034 if Expr_Value (R_High) < Expr_Value (R_Low) then
17035 R_Len := Uint_0;
17036 else
17037 R_Len := (Expr_Value (R_High) - Expr_Value (R_Low)) + 1;
17038 end if;
17039 else
17040 return False;
17041 end if;
17042 end if;
17044 if (Is_OK_Static_Expression (L_Low)
17045 and then
17046 Is_OK_Static_Expression (R_Low))
17047 and then Expr_Value (L_Low) = Expr_Value (R_Low)
17048 and then L_Len = R_Len
17049 then
17050 null;
17051 else
17052 return False;
17053 end if;
17055 -- Then treat all other dimensions
17057 for Indx in 2 .. L_Ndims loop
17058 Next (L_Index);
17059 Next (R_Index);
17061 Get_Index_Bounds (L_Index, L_Low, L_High);
17062 Get_Index_Bounds (R_Index, R_Low, R_High);
17064 if (Is_OK_Static_Expression (L_Low) and then
17065 Is_OK_Static_Expression (L_High) and then
17066 Is_OK_Static_Expression (R_Low) and then
17067 Is_OK_Static_Expression (R_High))
17068 and then (Expr_Value (L_Low) = Expr_Value (R_Low)
17069 and then
17070 Expr_Value (L_High) = Expr_Value (R_High))
17071 then
17072 null;
17073 else
17074 return False;
17075 end if;
17076 end loop;
17078 -- If we fall through the loop, all indexes matched
17080 return True;
17081 end Matching_Static_Array_Bounds;
17083 -------------------
17084 -- May_Be_Lvalue --
17085 -------------------
17087 function May_Be_Lvalue (N : Node_Id) return Boolean is
17088 P : constant Node_Id := Parent (N);
17090 begin
17091 case Nkind (P) is
17093 -- Test left side of assignment
17095 when N_Assignment_Statement =>
17096 return N = Name (P);
17098 -- Test prefix of component or attribute. Note that the prefix of an
17099 -- explicit or implicit dereference cannot be an l-value. In the case
17100 -- of a 'Read attribute, the reference can be an actual in the
17101 -- argument list of the attribute.
17103 when N_Attribute_Reference =>
17104 return (N = Prefix (P)
17105 and then Name_Implies_Lvalue_Prefix (Attribute_Name (P)))
17106 or else
17107 Attribute_Name (P) = Name_Read;
17109 -- For an expanded name, the name is an lvalue if the expanded name
17110 -- is an lvalue, but the prefix is never an lvalue, since it is just
17111 -- the scope where the name is found.
17113 when N_Expanded_Name =>
17114 if N = Prefix (P) then
17115 return May_Be_Lvalue (P);
17116 else
17117 return False;
17118 end if;
17120 -- For a selected component A.B, A is certainly an lvalue if A.B is.
17121 -- B is a little interesting, if we have A.B := 3, there is some
17122 -- discussion as to whether B is an lvalue or not, we choose to say
17123 -- it is. Note however that A is not an lvalue if it is of an access
17124 -- type since this is an implicit dereference.
17126 when N_Selected_Component =>
17127 if N = Prefix (P)
17128 and then Present (Etype (N))
17129 and then Is_Access_Type (Etype (N))
17130 then
17131 return False;
17132 else
17133 return May_Be_Lvalue (P);
17134 end if;
17136 -- For an indexed component or slice, the index or slice bounds is
17137 -- never an lvalue. The prefix is an lvalue if the indexed component
17138 -- or slice is an lvalue, except if it is an access type, where we
17139 -- have an implicit dereference.
17141 when N_Indexed_Component
17142 | N_Slice
17144 if N /= Prefix (P)
17145 or else (Present (Etype (N)) and then Is_Access_Type (Etype (N)))
17146 then
17147 return False;
17148 else
17149 return May_Be_Lvalue (P);
17150 end if;
17152 -- Prefix of a reference is an lvalue if the reference is an lvalue
17154 when N_Reference =>
17155 return May_Be_Lvalue (P);
17157 -- Prefix of explicit dereference is never an lvalue
17159 when N_Explicit_Dereference =>
17160 return False;
17162 -- Positional parameter for subprogram, entry, or accept call.
17163 -- In older versions of Ada function call arguments are never
17164 -- lvalues. In Ada 2012 functions can have in-out parameters.
17166 when N_Accept_Statement
17167 | N_Entry_Call_Statement
17168 | N_Subprogram_Call
17170 if Nkind (P) = N_Function_Call and then Ada_Version < Ada_2012 then
17171 return False;
17172 end if;
17174 -- The following mechanism is clumsy and fragile. A single flag
17175 -- set in Resolve_Actuals would be preferable ???
17177 declare
17178 Proc : Entity_Id;
17179 Form : Entity_Id;
17180 Act : Node_Id;
17182 begin
17183 Proc := Get_Subprogram_Entity (P);
17185 if No (Proc) then
17186 return True;
17187 end if;
17189 -- If we are not a list member, something is strange, so be
17190 -- conservative and return True.
17192 if not Is_List_Member (N) then
17193 return True;
17194 end if;
17196 -- We are going to find the right formal by stepping forward
17197 -- through the formals, as we step backwards in the actuals.
17199 Form := First_Formal (Proc);
17200 Act := N;
17201 loop
17202 -- If no formal, something is weird, so be conservative and
17203 -- return True.
17205 if No (Form) then
17206 return True;
17207 end if;
17209 Prev (Act);
17210 exit when No (Act);
17211 Next_Formal (Form);
17212 end loop;
17214 return Ekind (Form) /= E_In_Parameter;
17215 end;
17217 -- Named parameter for procedure or accept call
17219 when N_Parameter_Association =>
17220 declare
17221 Proc : Entity_Id;
17222 Form : Entity_Id;
17224 begin
17225 Proc := Get_Subprogram_Entity (Parent (P));
17227 if No (Proc) then
17228 return True;
17229 end if;
17231 -- Loop through formals to find the one that matches
17233 Form := First_Formal (Proc);
17234 loop
17235 -- If no matching formal, that's peculiar, some kind of
17236 -- previous error, so return True to be conservative.
17237 -- Actually happens with legal code for an unresolved call
17238 -- where we may get the wrong homonym???
17240 if No (Form) then
17241 return True;
17242 end if;
17244 -- Else test for match
17246 if Chars (Form) = Chars (Selector_Name (P)) then
17247 return Ekind (Form) /= E_In_Parameter;
17248 end if;
17250 Next_Formal (Form);
17251 end loop;
17252 end;
17254 -- Test for appearing in a conversion that itself appears in an
17255 -- lvalue context, since this should be an lvalue.
17257 when N_Type_Conversion =>
17258 return May_Be_Lvalue (P);
17260 -- Test for appearance in object renaming declaration
17262 when N_Object_Renaming_Declaration =>
17263 return True;
17265 -- All other references are definitely not lvalues
17267 when others =>
17268 return False;
17269 end case;
17270 end May_Be_Lvalue;
17272 -----------------------
17273 -- Mark_Coextensions --
17274 -----------------------
17276 procedure Mark_Coextensions (Context_Nod : Node_Id; Root_Nod : Node_Id) is
17277 Is_Dynamic : Boolean;
17278 -- Indicates whether the context causes nested coextensions to be
17279 -- dynamic or static
17281 function Mark_Allocator (N : Node_Id) return Traverse_Result;
17282 -- Recognize an allocator node and label it as a dynamic coextension
17284 --------------------
17285 -- Mark_Allocator --
17286 --------------------
17288 function Mark_Allocator (N : Node_Id) return Traverse_Result is
17289 begin
17290 if Nkind (N) = N_Allocator then
17291 if Is_Dynamic then
17292 Set_Is_Dynamic_Coextension (N);
17294 -- If the allocator expression is potentially dynamic, it may
17295 -- be expanded out of order and require dynamic allocation
17296 -- anyway, so we treat the coextension itself as dynamic.
17297 -- Potential optimization ???
17299 elsif Nkind (Expression (N)) = N_Qualified_Expression
17300 and then Nkind (Expression (Expression (N))) = N_Op_Concat
17301 then
17302 Set_Is_Dynamic_Coextension (N);
17303 else
17304 Set_Is_Static_Coextension (N);
17305 end if;
17306 end if;
17308 return OK;
17309 end Mark_Allocator;
17311 procedure Mark_Allocators is new Traverse_Proc (Mark_Allocator);
17313 -- Start of processing for Mark_Coextensions
17315 begin
17316 -- An allocator that appears on the right-hand side of an assignment is
17317 -- treated as a potentially dynamic coextension when the right-hand side
17318 -- is an allocator or a qualified expression.
17320 -- Obj := new ...'(new Coextension ...);
17322 if Nkind (Context_Nod) = N_Assignment_Statement then
17323 Is_Dynamic :=
17324 Nkind_In (Expression (Context_Nod), N_Allocator,
17325 N_Qualified_Expression);
17327 -- An allocator that appears within the expression of a simple return
17328 -- statement is treated as a potentially dynamic coextension when the
17329 -- expression is either aggregate, allocator, or qualified expression.
17331 -- return (new Coextension ...);
17332 -- return new ...'(new Coextension ...);
17334 elsif Nkind (Context_Nod) = N_Simple_Return_Statement then
17335 Is_Dynamic :=
17336 Nkind_In (Expression (Context_Nod), N_Aggregate,
17337 N_Allocator,
17338 N_Qualified_Expression);
17340 -- An allocator that appears within the initialization expression of an
17341 -- object declaration is considered a potentially dynamic coextension
17342 -- when the initialization expression is an allocator or a qualified
17343 -- expression.
17345 -- Obj : ... := new ...'(new Coextension ...);
17347 -- A similar case arises when the object declaration is part of an
17348 -- extended return statement.
17350 -- return Obj : ... := new ...'(new Coextension ...);
17351 -- return Obj : ... := (new Coextension ...);
17353 elsif Nkind (Context_Nod) = N_Object_Declaration then
17354 Is_Dynamic :=
17355 Nkind_In (Root_Nod, N_Allocator, N_Qualified_Expression)
17356 or else
17357 Nkind (Parent (Context_Nod)) = N_Extended_Return_Statement;
17359 -- This routine should not be called with constructs that cannot contain
17360 -- coextensions.
17362 else
17363 raise Program_Error;
17364 end if;
17366 Mark_Allocators (Root_Nod);
17367 end Mark_Coextensions;
17369 -----------------
17370 -- Might_Raise --
17371 -----------------
17373 function Might_Raise (N : Node_Id) return Boolean is
17374 Result : Boolean := False;
17376 function Process (N : Node_Id) return Traverse_Result;
17377 -- Set Result to True if we find something that could raise an exception
17379 -------------
17380 -- Process --
17381 -------------
17383 function Process (N : Node_Id) return Traverse_Result is
17384 begin
17385 if Nkind_In (N, N_Procedure_Call_Statement,
17386 N_Function_Call,
17387 N_Raise_Statement,
17388 N_Raise_Constraint_Error,
17389 N_Raise_Program_Error,
17390 N_Raise_Storage_Error)
17391 then
17392 Result := True;
17393 return Abandon;
17394 else
17395 return OK;
17396 end if;
17397 end Process;
17399 procedure Set_Result is new Traverse_Proc (Process);
17401 -- Start of processing for Might_Raise
17403 begin
17404 -- False if exceptions can't be propagated
17406 if No_Exception_Handlers_Set then
17407 return False;
17408 end if;
17410 -- If the checks handled by the back end are not disabled, we cannot
17411 -- ensure that no exception will be raised.
17413 if not Access_Checks_Suppressed (Empty)
17414 or else not Discriminant_Checks_Suppressed (Empty)
17415 or else not Range_Checks_Suppressed (Empty)
17416 or else not Index_Checks_Suppressed (Empty)
17417 or else Opt.Stack_Checking_Enabled
17418 then
17419 return True;
17420 end if;
17422 Set_Result (N);
17423 return Result;
17424 end Might_Raise;
17426 --------------------------------
17427 -- Nearest_Enclosing_Instance --
17428 --------------------------------
17430 function Nearest_Enclosing_Instance (E : Entity_Id) return Entity_Id is
17431 Inst : Entity_Id;
17433 begin
17434 Inst := Scope (E);
17435 while Present (Inst) and then Inst /= Standard_Standard loop
17436 if Is_Generic_Instance (Inst) then
17437 return Inst;
17438 end if;
17440 Inst := Scope (Inst);
17441 end loop;
17443 return Empty;
17444 end Nearest_Enclosing_Instance;
17446 ----------------------
17447 -- Needs_One_Actual --
17448 ----------------------
17450 function Needs_One_Actual (E : Entity_Id) return Boolean is
17451 Formal : Entity_Id;
17453 begin
17454 -- Ada 2005 or later, and formals present. The first formal must be
17455 -- of a type that supports prefix notation: a controlling argument,
17456 -- a class-wide type, or an access to such.
17458 if Ada_Version >= Ada_2005
17459 and then Present (First_Formal (E))
17460 and then No (Default_Value (First_Formal (E)))
17461 and then
17462 (Is_Controlling_Formal (First_Formal (E))
17463 or else Is_Class_Wide_Type (Etype (First_Formal (E)))
17464 or else Is_Anonymous_Access_Type (Etype (First_Formal (E))))
17465 then
17466 Formal := Next_Formal (First_Formal (E));
17467 while Present (Formal) loop
17468 if No (Default_Value (Formal)) then
17469 return False;
17470 end if;
17472 Next_Formal (Formal);
17473 end loop;
17475 return True;
17477 -- Ada 83/95 or no formals
17479 else
17480 return False;
17481 end if;
17482 end Needs_One_Actual;
17484 ------------------------
17485 -- New_Copy_List_Tree --
17486 ------------------------
17488 function New_Copy_List_Tree (List : List_Id) return List_Id is
17489 NL : List_Id;
17490 E : Node_Id;
17492 begin
17493 if List = No_List then
17494 return No_List;
17496 else
17497 NL := New_List;
17498 E := First (List);
17500 while Present (E) loop
17501 Append (New_Copy_Tree (E), NL);
17502 E := Next (E);
17503 end loop;
17505 return NL;
17506 end if;
17507 end New_Copy_List_Tree;
17509 -------------------
17510 -- New_Copy_Tree --
17511 -------------------
17513 -- The following tables play a key role in replicating entities and Itypes.
17514 -- They are intentionally declared at the library level rather than within
17515 -- New_Copy_Tree to avoid elaborating them on each call. This performance
17516 -- optimization saves up to 2% of the entire compilation time spent in the
17517 -- front end. Care should be taken to reset the tables on each new call to
17518 -- New_Copy_Tree.
17520 NCT_Table_Max : constant := 511;
17522 subtype NCT_Table_Index is Nat range 0 .. NCT_Table_Max - 1;
17524 function NCT_Table_Hash (Key : Node_Or_Entity_Id) return NCT_Table_Index;
17525 -- Obtain the hash value of node or entity Key
17527 --------------------
17528 -- NCT_Table_Hash --
17529 --------------------
17531 function NCT_Table_Hash (Key : Node_Or_Entity_Id) return NCT_Table_Index is
17532 begin
17533 return NCT_Table_Index (Key mod NCT_Table_Max);
17534 end NCT_Table_Hash;
17536 ----------------------
17537 -- NCT_New_Entities --
17538 ----------------------
17540 -- The following table maps old entities and Itypes to their corresponding
17541 -- new entities and Itypes.
17543 -- Aaa -> Xxx
17545 package NCT_New_Entities is new Simple_HTable (
17546 Header_Num => NCT_Table_Index,
17547 Element => Entity_Id,
17548 No_Element => Empty,
17549 Key => Entity_Id,
17550 Hash => NCT_Table_Hash,
17551 Equal => "=");
17553 ------------------------
17554 -- NCT_Pending_Itypes --
17555 ------------------------
17557 -- The following table maps old Associated_Node_For_Itype nodes to a set of
17558 -- new itypes. Given a set of old Itypes Aaa, Bbb, and Ccc, where all three
17559 -- have the same Associated_Node_For_Itype Ppp, and their corresponding new
17560 -- Itypes Xxx, Yyy, Zzz, the table contains the following mapping:
17562 -- Ppp -> (Xxx, Yyy, Zzz)
17564 -- The set is expressed as an Elist
17566 package NCT_Pending_Itypes is new Simple_HTable (
17567 Header_Num => NCT_Table_Index,
17568 Element => Elist_Id,
17569 No_Element => No_Elist,
17570 Key => Node_Id,
17571 Hash => NCT_Table_Hash,
17572 Equal => "=");
17574 NCT_Tables_In_Use : Boolean := False;
17575 -- This flag keeps track of whether the two tables NCT_New_Entities and
17576 -- NCT_Pending_Itypes are in use. The flag is part of an optimization
17577 -- where certain operations are not performed if the tables are not in
17578 -- use. This saves up to 8% of the entire compilation time spent in the
17579 -- front end.
17581 -------------------
17582 -- New_Copy_Tree --
17583 -------------------
17585 function New_Copy_Tree
17586 (Source : Node_Id;
17587 Map : Elist_Id := No_Elist;
17588 New_Sloc : Source_Ptr := No_Location;
17589 New_Scope : Entity_Id := Empty) return Node_Id
17591 -- This routine performs low-level tree manipulations and needs access
17592 -- to the internals of the tree.
17594 use Atree.Unchecked_Access;
17595 use Atree_Private_Part;
17597 EWA_Level : Nat := 0;
17598 -- This counter keeps track of how many N_Expression_With_Actions nodes
17599 -- are encountered during a depth-first traversal of the subtree. These
17600 -- nodes may define new entities in their Actions lists and thus require
17601 -- special processing.
17603 EWA_Inner_Scope_Level : Nat := 0;
17604 -- This counter keeps track of how many scoping constructs appear within
17605 -- an N_Expression_With_Actions node.
17607 procedure Add_New_Entity (Old_Id : Entity_Id; New_Id : Entity_Id);
17608 pragma Inline (Add_New_Entity);
17609 -- Add an entry in the NCT_New_Entities table which maps key Old_Id to
17610 -- value New_Id. Old_Id is an entity which appears within the Actions
17611 -- list of an N_Expression_With_Actions node, or within an entity map.
17612 -- New_Id is the corresponding new entity generated during Phase 1.
17614 procedure Add_Pending_Itype (Assoc_Nod : Node_Id; Itype : Entity_Id);
17615 pragma Inline (Add_New_Entity);
17616 -- Add an entry in the NCT_Pending_Itypes which maps key Assoc_Nod to
17617 -- value Itype. Assoc_Nod is the associated node of an itype. Itype is
17618 -- an itype.
17620 procedure Build_NCT_Tables (Entity_Map : Elist_Id);
17621 pragma Inline (Build_NCT_Tables);
17622 -- Populate tables NCT_New_Entities and NCT_Pending_Itypes with the
17623 -- information supplied in entity map Entity_Map. The format of the
17624 -- entity map must be as follows:
17626 -- Old_Id1, New_Id1, Old_Id2, New_Id2, .., Old_IdN, New_IdN
17628 function Copy_Any_Node_With_Replacement
17629 (N : Node_Or_Entity_Id) return Node_Or_Entity_Id;
17630 pragma Inline (Copy_Any_Node_With_Replacement);
17631 -- Replicate entity or node N by invoking one of the following routines:
17633 -- Copy_Node_With_Replacement
17634 -- Corresponding_Entity
17636 function Copy_Elist_With_Replacement (List : Elist_Id) return Elist_Id;
17637 -- Replicate the elements of entity list List
17639 function Copy_Field_With_Replacement
17640 (Field : Union_Id;
17641 Old_Par : Node_Id := Empty;
17642 New_Par : Node_Id := Empty;
17643 Semantic : Boolean := False) return Union_Id;
17644 -- Replicate field Field by invoking one of the following routines:
17646 -- Copy_Elist_With_Replacement
17647 -- Copy_List_With_Replacement
17648 -- Copy_Node_With_Replacement
17649 -- Corresponding_Entity
17651 -- If the field is not an entity list, entity, itype, syntactic list,
17652 -- or node, then the field is returned unchanged. The routine always
17653 -- replicates entities, itypes, and valid syntactic fields. Old_Par is
17654 -- the expected parent of a syntactic field. New_Par is the new parent
17655 -- associated with a replicated syntactic field. Flag Semantic should
17656 -- be set when the input is a semantic field.
17658 function Copy_List_With_Replacement (List : List_Id) return List_Id;
17659 -- Replicate the elements of syntactic list List
17661 function Copy_Node_With_Replacement (N : Node_Id) return Node_Id;
17662 -- Replicate node N
17664 function Corresponding_Entity (Id : Entity_Id) return Entity_Id;
17665 pragma Inline (Corresponding_Entity);
17666 -- Return the corresponding new entity of Id generated during Phase 1.
17667 -- If there is no such entity, return Id.
17669 function In_Entity_Map
17670 (Id : Entity_Id;
17671 Entity_Map : Elist_Id) return Boolean;
17672 pragma Inline (In_Entity_Map);
17673 -- Determine whether entity Id is one of the old ids specified in entity
17674 -- map Entity_Map. The format of the entity map must be as follows:
17676 -- Old_Id1, New_Id1, Old_Id2, New_Id2, .., Old_IdN, New_IdN
17678 procedure Update_CFS_Sloc (N : Node_Or_Entity_Id);
17679 pragma Inline (Update_CFS_Sloc);
17680 -- Update the Comes_From_Source and Sloc attributes of node or entity N
17682 procedure Update_First_Real_Statement
17683 (Old_HSS : Node_Id;
17684 New_HSS : Node_Id);
17685 pragma Inline (Update_First_Real_Statement);
17686 -- Update semantic attribute First_Real_Statement of handled sequence of
17687 -- statements New_HSS based on handled sequence of statements Old_HSS.
17689 procedure Update_Named_Associations
17690 (Old_Call : Node_Id;
17691 New_Call : Node_Id);
17692 pragma Inline (Update_Named_Associations);
17693 -- Update semantic chain First/Next_Named_Association of call New_call
17694 -- based on call Old_Call.
17696 procedure Update_New_Entities (Entity_Map : Elist_Id);
17697 pragma Inline (Update_New_Entities);
17698 -- Update the semantic attributes of all new entities generated during
17699 -- Phase 1 that do not appear in entity map Entity_Map. The format of
17700 -- the entity map must be as follows:
17702 -- Old_Id1, New_Id1, Old_Id2, New_Id2, .., Old_IdN, New_IdN
17704 procedure Update_Pending_Itypes
17705 (Old_Assoc : Node_Id;
17706 New_Assoc : Node_Id);
17707 pragma Inline (Update_Pending_Itypes);
17708 -- Update semantic attribute Associated_Node_For_Itype to refer to node
17709 -- New_Assoc for all itypes whose associated node is Old_Assoc.
17711 procedure Update_Semantic_Fields (Id : Entity_Id);
17712 pragma Inline (Update_Semantic_Fields);
17713 -- Subsidiary to Update_New_Entities. Update semantic fields of entity
17714 -- or itype Id.
17716 procedure Visit_Any_Node (N : Node_Or_Entity_Id);
17717 pragma Inline (Visit_Any_Node);
17718 -- Visit entity of node N by invoking one of the following routines:
17720 -- Visit_Entity
17721 -- Visit_Itype
17722 -- Visit_Node
17724 procedure Visit_Elist (List : Elist_Id);
17725 -- Visit the elements of entity list List
17727 procedure Visit_Entity (Id : Entity_Id);
17728 -- Visit entity Id. This action may create a new entity of Id and save
17729 -- it in table NCT_New_Entities.
17731 procedure Visit_Field
17732 (Field : Union_Id;
17733 Par_Nod : Node_Id := Empty;
17734 Semantic : Boolean := False);
17735 -- Visit field Field by invoking one of the following routines:
17737 -- Visit_Elist
17738 -- Visit_Entity
17739 -- Visit_Itype
17740 -- Visit_List
17741 -- Visit_Node
17743 -- If the field is not an entity list, entity, itype, syntactic list,
17744 -- or node, then the field is not visited. The routine always visits
17745 -- valid syntactic fields. Par_Nod is the expected parent of the
17746 -- syntactic field. Flag Semantic should be set when the input is a
17747 -- semantic field.
17749 procedure Visit_Itype (Itype : Entity_Id);
17750 -- Visit itype Itype. This action may create a new entity for Itype and
17751 -- save it in table NCT_New_Entities. In addition, the routine may map
17752 -- the associated node of Itype to the new itype in NCT_Pending_Itypes.
17754 procedure Visit_List (List : List_Id);
17755 -- Visit the elements of syntactic list List
17757 procedure Visit_Node (N : Node_Id);
17758 -- Visit node N
17760 procedure Visit_Semantic_Fields (Id : Entity_Id);
17761 pragma Inline (Visit_Semantic_Fields);
17762 -- Subsidiary to Visit_Entity and Visit_Itype. Visit common semantic
17763 -- fields of entity or itype Id.
17765 --------------------
17766 -- Add_New_Entity --
17767 --------------------
17769 procedure Add_New_Entity (Old_Id : Entity_Id; New_Id : Entity_Id) is
17770 begin
17771 pragma Assert (Present (Old_Id));
17772 pragma Assert (Present (New_Id));
17773 pragma Assert (Nkind (Old_Id) in N_Entity);
17774 pragma Assert (Nkind (New_Id) in N_Entity);
17776 NCT_Tables_In_Use := True;
17778 -- Sanity check the NCT_New_Entities table. No previous mapping with
17779 -- key Old_Id should exist.
17781 pragma Assert (No (NCT_New_Entities.Get (Old_Id)));
17783 -- Establish the mapping
17785 -- Old_Id -> New_Id
17787 NCT_New_Entities.Set (Old_Id, New_Id);
17788 end Add_New_Entity;
17790 -----------------------
17791 -- Add_Pending_Itype --
17792 -----------------------
17794 procedure Add_Pending_Itype (Assoc_Nod : Node_Id; Itype : Entity_Id) is
17795 Itypes : Elist_Id;
17797 begin
17798 pragma Assert (Present (Assoc_Nod));
17799 pragma Assert (Present (Itype));
17800 pragma Assert (Nkind (Itype) in N_Entity);
17801 pragma Assert (Is_Itype (Itype));
17803 NCT_Tables_In_Use := True;
17805 -- It is not possible to sanity check the NCT_Pendint_Itypes table
17806 -- directly because a single node may act as the associated node for
17807 -- multiple itypes.
17809 Itypes := NCT_Pending_Itypes.Get (Assoc_Nod);
17811 if No (Itypes) then
17812 Itypes := New_Elmt_List;
17813 NCT_Pending_Itypes.Set (Assoc_Nod, Itypes);
17814 end if;
17816 -- Establish the mapping
17818 -- Assoc_Nod -> (Itype, ...)
17820 -- Avoid inserting the same itype multiple times. This involves a
17821 -- linear search, however the set of itypes with the same associated
17822 -- node is very small.
17824 Append_Unique_Elmt (Itype, Itypes);
17825 end Add_Pending_Itype;
17827 ----------------------
17828 -- Build_NCT_Tables --
17829 ----------------------
17831 procedure Build_NCT_Tables (Entity_Map : Elist_Id) is
17832 Elmt : Elmt_Id;
17833 Old_Id : Entity_Id;
17834 New_Id : Entity_Id;
17836 begin
17837 -- Nothing to do when there is no entity map
17839 if No (Entity_Map) then
17840 return;
17841 end if;
17843 Elmt := First_Elmt (Entity_Map);
17844 while Present (Elmt) loop
17846 -- Extract the (Old_Id, New_Id) pair from the entity map
17848 Old_Id := Node (Elmt);
17849 Next_Elmt (Elmt);
17851 New_Id := Node (Elmt);
17852 Next_Elmt (Elmt);
17854 -- Establish the following mapping within table NCT_New_Entities
17856 -- Old_Id -> New_Id
17858 Add_New_Entity (Old_Id, New_Id);
17860 -- Establish the following mapping within table NCT_Pending_Itypes
17861 -- when the new entity is an itype.
17863 -- Assoc_Nod -> (New_Id, ...)
17865 -- IMPORTANT: the associated node is that of the old itype because
17866 -- the node will be replicated in Phase 2.
17868 if Is_Itype (Old_Id) then
17869 Add_Pending_Itype
17870 (Assoc_Nod => Associated_Node_For_Itype (Old_Id),
17871 Itype => New_Id);
17872 end if;
17873 end loop;
17874 end Build_NCT_Tables;
17876 ------------------------------------
17877 -- Copy_Any_Node_With_Replacement --
17878 ------------------------------------
17880 function Copy_Any_Node_With_Replacement
17881 (N : Node_Or_Entity_Id) return Node_Or_Entity_Id
17883 begin
17884 if Nkind (N) in N_Entity then
17885 return Corresponding_Entity (N);
17886 else
17887 return Copy_Node_With_Replacement (N);
17888 end if;
17889 end Copy_Any_Node_With_Replacement;
17891 ---------------------------------
17892 -- Copy_Elist_With_Replacement --
17893 ---------------------------------
17895 function Copy_Elist_With_Replacement (List : Elist_Id) return Elist_Id is
17896 Elmt : Elmt_Id;
17897 Result : Elist_Id;
17899 begin
17900 -- Copy the contents of the old list. Note that the list itself may
17901 -- be empty, in which case the routine returns a new empty list. This
17902 -- avoids sharing lists between subtrees. The element of an entity
17903 -- list could be an entity or a node, hence the invocation of routine
17904 -- Copy_Any_Node_With_Replacement.
17906 if Present (List) then
17907 Result := New_Elmt_List;
17909 Elmt := First_Elmt (List);
17910 while Present (Elmt) loop
17911 Append_Elmt
17912 (Copy_Any_Node_With_Replacement (Node (Elmt)), Result);
17914 Next_Elmt (Elmt);
17915 end loop;
17917 -- Otherwise the list does not exist
17919 else
17920 Result := No_Elist;
17921 end if;
17923 return Result;
17924 end Copy_Elist_With_Replacement;
17926 ---------------------------------
17927 -- Copy_Field_With_Replacement --
17928 ---------------------------------
17930 function Copy_Field_With_Replacement
17931 (Field : Union_Id;
17932 Old_Par : Node_Id := Empty;
17933 New_Par : Node_Id := Empty;
17934 Semantic : Boolean := False) return Union_Id
17936 begin
17937 -- The field is empty
17939 if Field = Union_Id (Empty) then
17940 return Field;
17942 -- The field is an entity/itype/node
17944 elsif Field in Node_Range then
17945 declare
17946 Old_N : constant Node_Id := Node_Id (Field);
17947 Syntactic : constant Boolean := Parent (Old_N) = Old_Par;
17949 New_N : Node_Id;
17951 begin
17952 -- The field is an entity/itype
17954 if Nkind (Old_N) in N_Entity then
17956 -- An entity/itype is always replicated
17958 New_N := Corresponding_Entity (Old_N);
17960 -- Update the parent pointer when the entity is a syntactic
17961 -- field. Note that itypes do not have parent pointers.
17963 if Syntactic and then New_N /= Old_N then
17964 Set_Parent (New_N, New_Par);
17965 end if;
17967 -- The field is a node
17969 else
17970 -- A node is replicated when it is either a syntactic field
17971 -- or when the caller treats it as a semantic attribute.
17973 if Syntactic or else Semantic then
17974 New_N := Copy_Node_With_Replacement (Old_N);
17976 -- Update the parent pointer when the node is a syntactic
17977 -- field.
17979 if Syntactic and then New_N /= Old_N then
17980 Set_Parent (New_N, New_Par);
17981 end if;
17983 -- Otherwise the node is returned unchanged
17985 else
17986 New_N := Old_N;
17987 end if;
17988 end if;
17990 return Union_Id (New_N);
17991 end;
17993 -- The field is an entity list
17995 elsif Field in Elist_Range then
17996 return Union_Id (Copy_Elist_With_Replacement (Elist_Id (Field)));
17998 -- The field is a syntactic list
18000 elsif Field in List_Range then
18001 declare
18002 Old_List : constant List_Id := List_Id (Field);
18003 Syntactic : constant Boolean := Parent (Old_List) = Old_Par;
18005 New_List : List_Id;
18007 begin
18008 -- A list is replicated when it is either a syntactic field or
18009 -- when the caller treats it as a semantic attribute.
18011 if Syntactic or else Semantic then
18012 New_List := Copy_List_With_Replacement (Old_List);
18014 -- Update the parent pointer when the list is a syntactic
18015 -- field.
18017 if Syntactic and then New_List /= Old_List then
18018 Set_Parent (New_List, New_Par);
18019 end if;
18021 -- Otherwise the list is returned unchanged
18023 else
18024 New_List := Old_List;
18025 end if;
18027 return Union_Id (New_List);
18028 end;
18030 -- Otherwise the field denotes an attribute that does not need to be
18031 -- replicated (Chars, literals, etc).
18033 else
18034 return Field;
18035 end if;
18036 end Copy_Field_With_Replacement;
18038 --------------------------------
18039 -- Copy_List_With_Replacement --
18040 --------------------------------
18042 function Copy_List_With_Replacement (List : List_Id) return List_Id is
18043 Elmt : Node_Id;
18044 Result : List_Id;
18046 begin
18047 -- Copy the contents of the old list. Note that the list itself may
18048 -- be empty, in which case the routine returns a new empty list. This
18049 -- avoids sharing lists between subtrees. The element of a syntactic
18050 -- list is always a node, never an entity or itype, hence the call to
18051 -- routine Copy_Node_With_Replacement.
18053 if Present (List) then
18054 Result := New_List;
18056 Elmt := First (List);
18057 while Present (Elmt) loop
18058 Append (Copy_Node_With_Replacement (Elmt), Result);
18060 Next (Elmt);
18061 end loop;
18063 -- Otherwise the list does not exist
18065 else
18066 Result := No_List;
18067 end if;
18069 return Result;
18070 end Copy_List_With_Replacement;
18072 --------------------------------
18073 -- Copy_Node_With_Replacement --
18074 --------------------------------
18076 function Copy_Node_With_Replacement (N : Node_Id) return Node_Id is
18077 Result : Node_Id;
18079 begin
18080 -- Assume that the node must be returned unchanged
18082 Result := N;
18084 if N > Empty_Or_Error then
18085 pragma Assert (Nkind (N) not in N_Entity);
18087 Result := New_Copy (N);
18089 Set_Field1 (Result,
18090 Copy_Field_With_Replacement
18091 (Field => Field1 (Result),
18092 Old_Par => N,
18093 New_Par => Result));
18095 Set_Field2 (Result,
18096 Copy_Field_With_Replacement
18097 (Field => Field2 (Result),
18098 Old_Par => N,
18099 New_Par => Result));
18101 Set_Field3 (Result,
18102 Copy_Field_With_Replacement
18103 (Field => Field3 (Result),
18104 Old_Par => N,
18105 New_Par => Result));
18107 Set_Field4 (Result,
18108 Copy_Field_With_Replacement
18109 (Field => Field4 (Result),
18110 Old_Par => N,
18111 New_Par => Result));
18113 Set_Field5 (Result,
18114 Copy_Field_With_Replacement
18115 (Field => Field5 (Result),
18116 Old_Par => N,
18117 New_Par => Result));
18119 -- Update the Comes_From_Source and Sloc attributes of the node
18120 -- in case the caller has supplied new values.
18122 Update_CFS_Sloc (Result);
18124 -- Update the Associated_Node_For_Itype attribute of all itypes
18125 -- created during Phase 1 whose associated node is N. As a result
18126 -- the Associated_Node_For_Itype refers to the replicated node.
18127 -- No action needs to be taken when the Associated_Node_For_Itype
18128 -- refers to an entity because this was already handled during
18129 -- Phase 1, in Visit_Itype.
18131 Update_Pending_Itypes
18132 (Old_Assoc => N,
18133 New_Assoc => Result);
18135 -- Update the First/Next_Named_Association chain for a replicated
18136 -- call.
18138 if Nkind_In (N, N_Entry_Call_Statement,
18139 N_Function_Call,
18140 N_Procedure_Call_Statement)
18141 then
18142 Update_Named_Associations
18143 (Old_Call => N,
18144 New_Call => Result);
18146 -- Update the Renamed_Object attribute of a replicated object
18147 -- declaration.
18149 elsif Nkind (N) = N_Object_Renaming_Declaration then
18150 Set_Renamed_Object (Defining_Entity (Result), Name (Result));
18152 -- Update the First_Real_Statement attribute of a replicated
18153 -- handled sequence of statements.
18155 elsif Nkind (N) = N_Handled_Sequence_Of_Statements then
18156 Update_First_Real_Statement
18157 (Old_HSS => N,
18158 New_HSS => Result);
18159 end if;
18160 end if;
18162 return Result;
18163 end Copy_Node_With_Replacement;
18165 --------------------------
18166 -- Corresponding_Entity --
18167 --------------------------
18169 function Corresponding_Entity (Id : Entity_Id) return Entity_Id is
18170 New_Id : Entity_Id;
18171 Result : Entity_Id;
18173 begin
18174 -- Assume that the entity must be returned unchanged
18176 Result := Id;
18178 if Id > Empty_Or_Error then
18179 pragma Assert (Nkind (Id) in N_Entity);
18181 -- Determine whether the entity has a corresponding new entity
18182 -- generated during Phase 1 and if it does, use it.
18184 if NCT_Tables_In_Use then
18185 New_Id := NCT_New_Entities.Get (Id);
18187 if Present (New_Id) then
18188 Result := New_Id;
18189 end if;
18190 end if;
18191 end if;
18193 return Result;
18194 end Corresponding_Entity;
18196 -------------------
18197 -- In_Entity_Map --
18198 -------------------
18200 function In_Entity_Map
18201 (Id : Entity_Id;
18202 Entity_Map : Elist_Id) return Boolean
18204 Elmt : Elmt_Id;
18205 Old_Id : Entity_Id;
18207 begin
18208 -- The entity map contains pairs (Old_Id, New_Id). The advancement
18209 -- step always skips the New_Id portion of the pair.
18211 if Present (Entity_Map) then
18212 Elmt := First_Elmt (Entity_Map);
18213 while Present (Elmt) loop
18214 Old_Id := Node (Elmt);
18216 if Old_Id = Id then
18217 return True;
18218 end if;
18220 Next_Elmt (Elmt);
18221 Next_Elmt (Elmt);
18222 end loop;
18223 end if;
18225 return False;
18226 end In_Entity_Map;
18228 ---------------------
18229 -- Update_CFS_Sloc --
18230 ---------------------
18232 procedure Update_CFS_Sloc (N : Node_Or_Entity_Id) is
18233 begin
18234 -- A new source location defaults the Comes_From_Source attribute
18236 if New_Sloc /= No_Location then
18237 Set_Comes_From_Source (N, Default_Node.Comes_From_Source);
18238 Set_Sloc (N, New_Sloc);
18239 end if;
18240 end Update_CFS_Sloc;
18242 ---------------------------------
18243 -- Update_First_Real_Statement --
18244 ---------------------------------
18246 procedure Update_First_Real_Statement
18247 (Old_HSS : Node_Id;
18248 New_HSS : Node_Id)
18250 Old_First_Stmt : constant Node_Id := First_Real_Statement (Old_HSS);
18252 New_Stmt : Node_Id;
18253 Old_Stmt : Node_Id;
18255 begin
18256 -- Recreate the First_Real_Statement attribute of a handled sequence
18257 -- of statements by traversing the statement lists of both sequences
18258 -- in parallel.
18260 if Present (Old_First_Stmt) then
18261 New_Stmt := First (Statements (New_HSS));
18262 Old_Stmt := First (Statements (Old_HSS));
18263 while Present (Old_Stmt) and then Old_Stmt /= Old_First_Stmt loop
18264 Next (New_Stmt);
18265 Next (Old_Stmt);
18266 end loop;
18268 pragma Assert (Present (New_Stmt));
18269 pragma Assert (Present (Old_Stmt));
18271 Set_First_Real_Statement (New_HSS, New_Stmt);
18272 end if;
18273 end Update_First_Real_Statement;
18275 -------------------------------
18276 -- Update_Named_Associations --
18277 -------------------------------
18279 procedure Update_Named_Associations
18280 (Old_Call : Node_Id;
18281 New_Call : Node_Id)
18283 New_Act : Node_Id;
18284 New_Next : Node_Id;
18285 Old_Act : Node_Id;
18286 Old_Next : Node_Id;
18288 begin
18289 -- Recreate the First/Next_Named_Actual chain of a call by traversing
18290 -- the chains of both the old and new calls in parallel.
18292 New_Act := First (Parameter_Associations (New_Call));
18293 Old_Act := First (Parameter_Associations (Old_Call));
18294 while Present (Old_Act) loop
18295 if Nkind (Old_Act) = N_Parameter_Association
18296 and then Present (Next_Named_Actual (Old_Act))
18297 then
18298 if First_Named_Actual (Old_Call) =
18299 Explicit_Actual_Parameter (Old_Act)
18300 then
18301 Set_First_Named_Actual (New_Call,
18302 Explicit_Actual_Parameter (New_Act));
18303 end if;
18305 -- Scan the actual parameter list to find the next suitable
18306 -- named actual. Note that the list may be out of order.
18308 New_Next := First (Parameter_Associations (New_Call));
18309 Old_Next := First (Parameter_Associations (Old_Call));
18310 while Nkind (Old_Next) /= N_Parameter_Association
18311 or else Explicit_Actual_Parameter (Old_Next) /=
18312 Next_Named_Actual (Old_Act)
18313 loop
18314 Next (New_Next);
18315 Next (Old_Next);
18316 end loop;
18318 Set_Next_Named_Actual (New_Act,
18319 Explicit_Actual_Parameter (New_Next));
18320 end if;
18322 Next (New_Act);
18323 Next (Old_Act);
18324 end loop;
18325 end Update_Named_Associations;
18327 -------------------------
18328 -- Update_New_Entities --
18329 -------------------------
18331 procedure Update_New_Entities (Entity_Map : Elist_Id) is
18332 New_Id : Entity_Id := Empty;
18333 Old_Id : Entity_Id := Empty;
18335 begin
18336 if NCT_Tables_In_Use then
18337 NCT_New_Entities.Get_First (Old_Id, New_Id);
18339 -- Update the semantic fields of all new entities created during
18340 -- Phase 1 which were not supplied via an entity map.
18341 -- ??? Is there a better way of distinguishing those?
18343 while Present (Old_Id) and then Present (New_Id) loop
18344 if not (Present (Entity_Map)
18345 and then In_Entity_Map (Old_Id, Entity_Map))
18346 then
18347 Update_Semantic_Fields (New_Id);
18348 end if;
18350 NCT_New_Entities.Get_Next (Old_Id, New_Id);
18351 end loop;
18352 end if;
18353 end Update_New_Entities;
18355 ---------------------------
18356 -- Update_Pending_Itypes --
18357 ---------------------------
18359 procedure Update_Pending_Itypes
18360 (Old_Assoc : Node_Id;
18361 New_Assoc : Node_Id)
18363 Item : Elmt_Id;
18364 Itypes : Elist_Id;
18366 begin
18367 if NCT_Tables_In_Use then
18368 Itypes := NCT_Pending_Itypes.Get (Old_Assoc);
18370 -- Update the Associated_Node_For_Itype attribute for all itypes
18371 -- which originally refer to Old_Assoc to designate New_Assoc.
18373 if Present (Itypes) then
18374 Item := First_Elmt (Itypes);
18375 while Present (Item) loop
18376 Set_Associated_Node_For_Itype (Node (Item), New_Assoc);
18378 Next_Elmt (Item);
18379 end loop;
18380 end if;
18381 end if;
18382 end Update_Pending_Itypes;
18384 ----------------------------
18385 -- Update_Semantic_Fields --
18386 ----------------------------
18388 procedure Update_Semantic_Fields (Id : Entity_Id) is
18389 begin
18390 -- Discriminant_Constraint
18392 if Has_Discriminants (Base_Type (Id)) then
18393 Set_Discriminant_Constraint (Id, Elist_Id (
18394 Copy_Field_With_Replacement
18395 (Field => Union_Id (Discriminant_Constraint (Id)),
18396 Semantic => True)));
18397 end if;
18399 -- Etype
18401 Set_Etype (Id, Node_Id (
18402 Copy_Field_With_Replacement
18403 (Field => Union_Id (Etype (Id)),
18404 Semantic => True)));
18406 -- First_Index
18407 -- Packed_Array_Impl_Type
18409 if Is_Array_Type (Id) then
18410 if Present (First_Index (Id)) then
18411 Set_First_Index (Id, First (List_Id (
18412 Copy_Field_With_Replacement
18413 (Field => Union_Id (List_Containing (First_Index (Id))),
18414 Semantic => True))));
18415 end if;
18417 if Is_Packed (Id) then
18418 Set_Packed_Array_Impl_Type (Id, Node_Id (
18419 Copy_Field_With_Replacement
18420 (Field => Union_Id (Packed_Array_Impl_Type (Id)),
18421 Semantic => True)));
18422 end if;
18423 end if;
18425 -- Next_Entity
18427 Set_Next_Entity (Id, Node_Id (
18428 Copy_Field_With_Replacement
18429 (Field => Union_Id (Next_Entity (Id)),
18430 Semantic => True)));
18432 -- Scalar_Range
18434 if Is_Discrete_Type (Id) then
18435 Set_Scalar_Range (Id, Node_Id (
18436 Copy_Field_With_Replacement
18437 (Field => Union_Id (Scalar_Range (Id)),
18438 Semantic => True)));
18439 end if;
18441 -- Scope
18443 -- Update the scope when the caller specified an explicit one
18445 if Present (New_Scope) then
18446 Set_Scope (Id, New_Scope);
18447 else
18448 Set_Scope (Id, Node_Id (
18449 Copy_Field_With_Replacement
18450 (Field => Union_Id (Scope (Id)),
18451 Semantic => True)));
18452 end if;
18453 end Update_Semantic_Fields;
18455 --------------------
18456 -- Visit_Any_Node --
18457 --------------------
18459 procedure Visit_Any_Node (N : Node_Or_Entity_Id) is
18460 begin
18461 if Nkind (N) in N_Entity then
18462 if Is_Itype (N) then
18463 Visit_Itype (N);
18464 else
18465 Visit_Entity (N);
18466 end if;
18467 else
18468 Visit_Node (N);
18469 end if;
18470 end Visit_Any_Node;
18472 -----------------
18473 -- Visit_Elist --
18474 -----------------
18476 procedure Visit_Elist (List : Elist_Id) is
18477 Elmt : Elmt_Id;
18479 begin
18480 -- The element of an entity list could be an entity, itype, or a
18481 -- node, hence the call to Visit_Any_Node.
18483 if Present (List) then
18484 Elmt := First_Elmt (List);
18485 while Present (Elmt) loop
18486 Visit_Any_Node (Node (Elmt));
18488 Next_Elmt (Elmt);
18489 end loop;
18490 end if;
18491 end Visit_Elist;
18493 ------------------
18494 -- Visit_Entity --
18495 ------------------
18497 procedure Visit_Entity (Id : Entity_Id) is
18498 New_Id : Entity_Id;
18500 begin
18501 pragma Assert (Nkind (Id) in N_Entity);
18502 pragma Assert (not Is_Itype (Id));
18504 -- Nothing to do if the entity is not defined in the Actions list of
18505 -- an N_Expression_With_Actions node.
18507 if EWA_Level = 0 then
18508 return;
18510 -- Nothing to do if the entity is defined within a scoping construct
18511 -- of an N_Expression_With_Actions node.
18513 elsif EWA_Inner_Scope_Level > 0 then
18514 return;
18516 -- Nothing to do if the entity is not an object or a type. Relaxing
18517 -- this restriction leads to a performance penalty.
18519 elsif not Ekind_In (Id, E_Constant, E_Variable)
18520 and then not Is_Type (Id)
18521 then
18522 return;
18524 -- Nothing to do if the entity was already visited
18526 elsif NCT_Tables_In_Use
18527 and then Present (NCT_New_Entities.Get (Id))
18528 then
18529 return;
18531 -- Nothing to do if the declaration node of the entity is not within
18532 -- the subtree being replicated.
18534 elsif not In_Subtree
18535 (Root => Source,
18536 N => Declaration_Node (Id))
18537 then
18538 return;
18539 end if;
18541 -- Create a new entity by directly copying the old entity. This
18542 -- action causes all attributes of the old entity to be inherited.
18544 New_Id := New_Copy (Id);
18546 -- Create a new name for the new entity because the back end needs
18547 -- distinct names for debugging purposes.
18549 Set_Chars (New_Id, New_Internal_Name ('T'));
18551 -- Update the Comes_From_Source and Sloc attributes of the entity in
18552 -- case the caller has supplied new values.
18554 Update_CFS_Sloc (New_Id);
18556 -- Establish the following mapping within table NCT_New_Entities:
18558 -- Id -> New_Id
18560 Add_New_Entity (Id, New_Id);
18562 -- Deal with the semantic fields of entities. The fields are visited
18563 -- because they may mention entities which reside within the subtree
18564 -- being copied.
18566 Visit_Semantic_Fields (Id);
18567 end Visit_Entity;
18569 -----------------
18570 -- Visit_Field --
18571 -----------------
18573 procedure Visit_Field
18574 (Field : Union_Id;
18575 Par_Nod : Node_Id := Empty;
18576 Semantic : Boolean := False)
18578 begin
18579 -- The field is empty
18581 if Field = Union_Id (Empty) then
18582 return;
18584 -- The field is an entity/itype/node
18586 elsif Field in Node_Range then
18587 declare
18588 N : constant Node_Id := Node_Id (Field);
18590 begin
18591 -- The field is an entity/itype
18593 if Nkind (N) in N_Entity then
18595 -- Itypes are always visited
18597 if Is_Itype (N) then
18598 Visit_Itype (N);
18600 -- An entity is visited when it is either a syntactic field
18601 -- or when the caller treats it as a semantic attribute.
18603 elsif Parent (N) = Par_Nod or else Semantic then
18604 Visit_Entity (N);
18605 end if;
18607 -- The field is a node
18609 else
18610 -- A node is visited when it is either a syntactic field or
18611 -- when the caller treats it as a semantic attribute.
18613 if Parent (N) = Par_Nod or else Semantic then
18614 Visit_Node (N);
18615 end if;
18616 end if;
18617 end;
18619 -- The field is an entity list
18621 elsif Field in Elist_Range then
18622 Visit_Elist (Elist_Id (Field));
18624 -- The field is a syntax list
18626 elsif Field in List_Range then
18627 declare
18628 List : constant List_Id := List_Id (Field);
18630 begin
18631 -- A syntax list is visited when it is either a syntactic field
18632 -- or when the caller treats it as a semantic attribute.
18634 if Parent (List) = Par_Nod or else Semantic then
18635 Visit_List (List);
18636 end if;
18637 end;
18639 -- Otherwise the field denotes information which does not need to be
18640 -- visited (chars, literals, etc.).
18642 else
18643 null;
18644 end if;
18645 end Visit_Field;
18647 -----------------
18648 -- Visit_Itype --
18649 -----------------
18651 procedure Visit_Itype (Itype : Entity_Id) is
18652 New_Assoc : Node_Id;
18653 New_Itype : Entity_Id;
18654 Old_Assoc : Node_Id;
18656 begin
18657 pragma Assert (Nkind (Itype) in N_Entity);
18658 pragma Assert (Is_Itype (Itype));
18660 -- Itypes that describe the designated type of access to subprograms
18661 -- have the structure of subprogram declarations, with signatures,
18662 -- etc. Either we duplicate the signatures completely, or choose to
18663 -- share such itypes, which is fine because their elaboration will
18664 -- have no side effects.
18666 if Ekind (Itype) = E_Subprogram_Type then
18667 return;
18669 -- Nothing to do if the itype was already visited
18671 elsif NCT_Tables_In_Use
18672 and then Present (NCT_New_Entities.Get (Itype))
18673 then
18674 return;
18676 -- Nothing to do if the associated node of the itype is not within
18677 -- the subtree being replicated.
18679 elsif not In_Subtree
18680 (Root => Source,
18681 N => Associated_Node_For_Itype (Itype))
18682 then
18683 return;
18684 end if;
18686 -- Create a new itype by directly copying the old itype. This action
18687 -- causes all attributes of the old itype to be inherited.
18689 New_Itype := New_Copy (Itype);
18691 -- Create a new name for the new itype because the back end requires
18692 -- distinct names for debugging purposes.
18694 Set_Chars (New_Itype, New_Internal_Name ('T'));
18696 -- Update the Comes_From_Source and Sloc attributes of the itype in
18697 -- case the caller has supplied new values.
18699 Update_CFS_Sloc (New_Itype);
18701 -- Establish the following mapping within table NCT_New_Entities:
18703 -- Itype -> New_Itype
18705 Add_New_Entity (Itype, New_Itype);
18707 -- The new itype must be unfrozen because the resulting subtree may
18708 -- be inserted anywhere and cause an earlier or later freezing.
18710 if Present (Freeze_Node (New_Itype)) then
18711 Set_Freeze_Node (New_Itype, Empty);
18712 Set_Is_Frozen (New_Itype, False);
18713 end if;
18715 -- If a record subtype is simply copied, the entity list will be
18716 -- shared. Thus cloned_Subtype must be set to indicate the sharing.
18717 -- ??? What does this do?
18719 if Ekind_In (Itype, E_Class_Wide_Subtype, E_Record_Subtype) then
18720 Set_Cloned_Subtype (New_Itype, Itype);
18721 end if;
18723 -- The associated node may denote an entity, in which case it may
18724 -- already have a new corresponding entity created during a prior
18725 -- call to Visit_Entity or Visit_Itype for the same subtree.
18727 -- Given
18728 -- Old_Assoc ---------> New_Assoc
18730 -- Created by Visit_Itype
18731 -- Itype -------------> New_Itype
18732 -- ANFI = Old_Assoc ANFI = Old_Assoc < must be updated
18734 -- In the example above, Old_Assoc is an arbitrary entity that was
18735 -- already visited for the same subtree and has a corresponding new
18736 -- entity New_Assoc. Old_Assoc was inherited by New_Itype by virtue
18737 -- of copying entities, however it must be updated to New_Assoc.
18739 Old_Assoc := Associated_Node_For_Itype (Itype);
18741 if Nkind (Old_Assoc) in N_Entity then
18742 if NCT_Tables_In_Use then
18743 New_Assoc := NCT_New_Entities.Get (Old_Assoc);
18745 if Present (New_Assoc) then
18746 Set_Associated_Node_For_Itype (New_Itype, New_Assoc);
18747 end if;
18748 end if;
18750 -- Otherwise the associated node denotes a node. Postpone the update
18751 -- until Phase 2 when the node is replicated. Establish the following
18752 -- mapping within table NCT_Pending_Itypes:
18754 -- Old_Assoc -> (New_Type, ...)
18756 else
18757 Add_Pending_Itype (Old_Assoc, New_Itype);
18758 end if;
18760 -- Deal with the semantic fields of itypes. The fields are visited
18761 -- because they may mention entities that reside within the subtree
18762 -- being copied.
18764 Visit_Semantic_Fields (Itype);
18765 end Visit_Itype;
18767 ----------------
18768 -- Visit_List --
18769 ----------------
18771 procedure Visit_List (List : List_Id) is
18772 Elmt : Node_Id;
18774 begin
18775 -- Note that the element of a syntactic list is always a node, never
18776 -- an entity or itype, hence the call to Visit_Node.
18778 if Present (List) then
18779 Elmt := First (List);
18780 while Present (Elmt) loop
18781 Visit_Node (Elmt);
18783 Next (Elmt);
18784 end loop;
18785 end if;
18786 end Visit_List;
18788 ----------------
18789 -- Visit_Node --
18790 ----------------
18792 procedure Visit_Node (N : Node_Or_Entity_Id) is
18793 begin
18794 pragma Assert (Nkind (N) not in N_Entity);
18796 if Nkind (N) = N_Expression_With_Actions then
18797 EWA_Level := EWA_Level + 1;
18799 elsif EWA_Level > 0
18800 and then Nkind_In (N, N_Block_Statement,
18801 N_Subprogram_Body,
18802 N_Subprogram_Declaration)
18803 then
18804 EWA_Inner_Scope_Level := EWA_Inner_Scope_Level + 1;
18805 end if;
18807 Visit_Field
18808 (Field => Field1 (N),
18809 Par_Nod => N);
18811 Visit_Field
18812 (Field => Field2 (N),
18813 Par_Nod => N);
18815 Visit_Field
18816 (Field => Field3 (N),
18817 Par_Nod => N);
18819 Visit_Field
18820 (Field => Field4 (N),
18821 Par_Nod => N);
18823 Visit_Field
18824 (Field => Field5 (N),
18825 Par_Nod => N);
18827 if EWA_Level > 0
18828 and then Nkind_In (N, N_Block_Statement,
18829 N_Subprogram_Body,
18830 N_Subprogram_Declaration)
18831 then
18832 EWA_Inner_Scope_Level := EWA_Inner_Scope_Level - 1;
18834 elsif Nkind (N) = N_Expression_With_Actions then
18835 EWA_Level := EWA_Level - 1;
18836 end if;
18837 end Visit_Node;
18839 ---------------------------
18840 -- Visit_Semantic_Fields --
18841 ---------------------------
18843 procedure Visit_Semantic_Fields (Id : Entity_Id) is
18844 begin
18845 pragma Assert (Nkind (Id) in N_Entity);
18847 -- Discriminant_Constraint
18849 if Has_Discriminants (Base_Type (Id)) then
18850 Visit_Field
18851 (Field => Union_Id (Discriminant_Constraint (Id)),
18852 Semantic => True);
18853 end if;
18855 -- Etype
18857 Visit_Field
18858 (Field => Union_Id (Etype (Id)),
18859 Semantic => True);
18861 -- First_Index
18862 -- Packed_Array_Impl_Type
18864 if Is_Array_Type (Id) then
18865 if Present (First_Index (Id)) then
18866 Visit_Field
18867 (Field => Union_Id (List_Containing (First_Index (Id))),
18868 Semantic => True);
18869 end if;
18871 if Is_Packed (Id) then
18872 Visit_Field
18873 (Field => Union_Id (Packed_Array_Impl_Type (Id)),
18874 Semantic => True);
18875 end if;
18876 end if;
18878 -- Scalar_Range
18880 if Is_Discrete_Type (Id) then
18881 Visit_Field
18882 (Field => Union_Id (Scalar_Range (Id)),
18883 Semantic => True);
18884 end if;
18885 end Visit_Semantic_Fields;
18887 -- Start of processing for New_Copy_Tree
18889 begin
18890 -- Routine New_Copy_Tree performs a deep copy of a subtree by creating
18891 -- shallow copies for each node within, and then updating the child and
18892 -- parent pointers accordingly. This process is straightforward, however
18893 -- the routine must deal with the following complications:
18895 -- * Entities defined within N_Expression_With_Actions nodes must be
18896 -- replicated rather than shared to avoid introducing two identical
18897 -- symbols within the same scope. Note that no other expression can
18898 -- currently define entities.
18900 -- do
18901 -- Source_Low : ...;
18902 -- Source_High : ...;
18904 -- <reference to Source_Low>
18905 -- <reference to Source_High>
18906 -- in ... end;
18908 -- New_Copy_Tree handles this case by first creating new entities
18909 -- and then updating all existing references to point to these new
18910 -- entities.
18912 -- do
18913 -- New_Low : ...;
18914 -- New_High : ...;
18916 -- <reference to New_Low>
18917 -- <reference to New_High>
18918 -- in ... end;
18920 -- * Itypes defined within the subtree must be replicated to avoid any
18921 -- dependencies on invalid or inaccessible data.
18923 -- subtype Source_Itype is ... range Source_Low .. Source_High;
18925 -- New_Copy_Tree handles this case by first creating a new itype in
18926 -- the same fashion as entities, and then updating various relevant
18927 -- constraints.
18929 -- subtype New_Itype is ... range New_Low .. New_High;
18931 -- * The Associated_Node_For_Itype field of itypes must be updated to
18932 -- reference the proper replicated entity or node.
18934 -- * Semantic fields of entities such as Etype and Scope must be
18935 -- updated to reference the proper replicated entities.
18937 -- * Semantic fields of nodes such as First_Real_Statement must be
18938 -- updated to reference the proper replicated nodes.
18940 -- To meet all these demands, routine New_Copy_Tree is split into two
18941 -- phases.
18943 -- Phase 1 traverses the tree in order to locate entities and itypes
18944 -- defined within the subtree. New entities are generated and saved in
18945 -- table NCT_New_Entities. The semantic fields of all new entities and
18946 -- itypes are then updated accordingly.
18948 -- Phase 2 traverses the tree in order to replicate each node. Various
18949 -- semantic fields of nodes and entities are updated accordingly.
18951 -- Preparatory phase. Clear the contents of tables NCT_New_Entities and
18952 -- NCT_Pending_Itypes in case a previous call to New_Copy_Tree left some
18953 -- data inside.
18955 if NCT_Tables_In_Use then
18956 NCT_Tables_In_Use := False;
18958 NCT_New_Entities.Reset;
18959 NCT_Pending_Itypes.Reset;
18960 end if;
18962 -- Populate tables NCT_New_Entities and NCT_Pending_Itypes with data
18963 -- supplied by a linear entity map. The tables offer faster access to
18964 -- the same data.
18966 Build_NCT_Tables (Map);
18968 -- Execute Phase 1. Traverse the subtree and generate new entities for
18969 -- the following cases:
18971 -- * An entity defined within an N_Expression_With_Actions node
18973 -- * An itype referenced within the subtree where the associated node
18974 -- is also in the subtree.
18976 -- All new entities are accessible via table NCT_New_Entities, which
18977 -- contains mappings of the form:
18979 -- Old_Entity -> New_Entity
18980 -- Old_Itype -> New_Itype
18982 -- In addition, the associated nodes of all new itypes are mapped in
18983 -- table NCT_Pending_Itypes:
18985 -- Assoc_Nod -> (New_Itype1, New_Itype2, .., New_ItypeN)
18987 Visit_Any_Node (Source);
18989 -- Update the semantic attributes of all new entities generated during
18990 -- Phase 1 before starting Phase 2. The updates could be performed in
18991 -- routine Corresponding_Entity, however this may cause the same entity
18992 -- to be updated multiple times, effectively generating useless nodes.
18993 -- Keeping the updates separates from Phase 2 ensures that only one set
18994 -- of attributes is generated for an entity at any one time.
18996 Update_New_Entities (Map);
18998 -- Execute Phase 2. Replicate the source subtree one node at a time.
18999 -- The following transformations take place:
19001 -- * References to entities and itypes are updated to refer to the
19002 -- new entities and itypes generated during Phase 1.
19004 -- * All Associated_Node_For_Itype attributes of itypes are updated
19005 -- to refer to the new replicated Associated_Node_For_Itype.
19007 return Copy_Node_With_Replacement (Source);
19008 end New_Copy_Tree;
19010 -------------------------
19011 -- New_External_Entity --
19012 -------------------------
19014 function New_External_Entity
19015 (Kind : Entity_Kind;
19016 Scope_Id : Entity_Id;
19017 Sloc_Value : Source_Ptr;
19018 Related_Id : Entity_Id;
19019 Suffix : Character;
19020 Suffix_Index : Nat := 0;
19021 Prefix : Character := ' ') return Entity_Id
19023 N : constant Entity_Id :=
19024 Make_Defining_Identifier (Sloc_Value,
19025 New_External_Name
19026 (Chars (Related_Id), Suffix, Suffix_Index, Prefix));
19028 begin
19029 Set_Ekind (N, Kind);
19030 Set_Is_Internal (N, True);
19031 Append_Entity (N, Scope_Id);
19032 Set_Public_Status (N);
19034 if Kind in Type_Kind then
19035 Init_Size_Align (N);
19036 end if;
19038 return N;
19039 end New_External_Entity;
19041 -------------------------
19042 -- New_Internal_Entity --
19043 -------------------------
19045 function New_Internal_Entity
19046 (Kind : Entity_Kind;
19047 Scope_Id : Entity_Id;
19048 Sloc_Value : Source_Ptr;
19049 Id_Char : Character) return Entity_Id
19051 N : constant Entity_Id := Make_Temporary (Sloc_Value, Id_Char);
19053 begin
19054 Set_Ekind (N, Kind);
19055 Set_Is_Internal (N, True);
19056 Append_Entity (N, Scope_Id);
19058 if Kind in Type_Kind then
19059 Init_Size_Align (N);
19060 end if;
19062 return N;
19063 end New_Internal_Entity;
19065 -----------------
19066 -- Next_Actual --
19067 -----------------
19069 function Next_Actual (Actual_Id : Node_Id) return Node_Id is
19070 N : Node_Id;
19072 begin
19073 -- If we are pointing at a positional parameter, it is a member of a
19074 -- node list (the list of parameters), and the next parameter is the
19075 -- next node on the list, unless we hit a parameter association, then
19076 -- we shift to using the chain whose head is the First_Named_Actual in
19077 -- the parent, and then is threaded using the Next_Named_Actual of the
19078 -- Parameter_Association. All this fiddling is because the original node
19079 -- list is in the textual call order, and what we need is the
19080 -- declaration order.
19082 if Is_List_Member (Actual_Id) then
19083 N := Next (Actual_Id);
19085 if Nkind (N) = N_Parameter_Association then
19086 return First_Named_Actual (Parent (Actual_Id));
19087 else
19088 return N;
19089 end if;
19091 else
19092 return Next_Named_Actual (Parent (Actual_Id));
19093 end if;
19094 end Next_Actual;
19096 procedure Next_Actual (Actual_Id : in out Node_Id) is
19097 begin
19098 Actual_Id := Next_Actual (Actual_Id);
19099 end Next_Actual;
19101 -----------------
19102 -- Next_Global --
19103 -----------------
19105 function Next_Global (Node : Node_Id) return Node_Id is
19106 begin
19107 -- The global item may either be in a list, or by itself, in which case
19108 -- there is no next global item with the same mode.
19110 if Is_List_Member (Node) then
19111 return Next (Node);
19112 else
19113 return Empty;
19114 end if;
19115 end Next_Global;
19117 procedure Next_Global (Node : in out Node_Id) is
19118 begin
19119 Node := Next_Global (Node);
19120 end Next_Global;
19122 ----------------------------------
19123 -- New_Requires_Transient_Scope --
19124 ----------------------------------
19126 function New_Requires_Transient_Scope (Id : Entity_Id) return Boolean is
19127 function Caller_Known_Size_Record (Typ : Entity_Id) return Boolean;
19128 -- This is called for untagged records and protected types, with
19129 -- nondefaulted discriminants. Returns True if the size of function
19130 -- results is known at the call site, False otherwise. Returns False
19131 -- if there is a variant part that depends on the discriminants of
19132 -- this type, or if there is an array constrained by the discriminants
19133 -- of this type. ???Currently, this is overly conservative (the array
19134 -- could be nested inside some other record that is constrained by
19135 -- nondiscriminants). That is, the recursive calls are too conservative.
19137 function Large_Max_Size_Mutable (Typ : Entity_Id) return Boolean;
19138 -- Returns True if Typ is a nonlimited record with defaulted
19139 -- discriminants whose max size makes it unsuitable for allocating on
19140 -- the primary stack.
19142 ------------------------------
19143 -- Caller_Known_Size_Record --
19144 ------------------------------
19146 function Caller_Known_Size_Record (Typ : Entity_Id) return Boolean is
19147 pragma Assert (Typ = Underlying_Type (Typ));
19149 begin
19150 if Has_Variant_Part (Typ) and then not Is_Definite_Subtype (Typ) then
19151 return False;
19152 end if;
19154 declare
19155 Comp : Entity_Id;
19157 begin
19158 Comp := First_Entity (Typ);
19159 while Present (Comp) loop
19161 -- Only look at E_Component entities. No need to look at
19162 -- E_Discriminant entities, and we must ignore internal
19163 -- subtypes generated for constrained components.
19165 if Ekind (Comp) = E_Component then
19166 declare
19167 Comp_Type : constant Entity_Id :=
19168 Underlying_Type (Etype (Comp));
19170 begin
19171 if Is_Record_Type (Comp_Type)
19172 or else
19173 Is_Protected_Type (Comp_Type)
19174 then
19175 if not Caller_Known_Size_Record (Comp_Type) then
19176 return False;
19177 end if;
19179 elsif Is_Array_Type (Comp_Type) then
19180 if Size_Depends_On_Discriminant (Comp_Type) then
19181 return False;
19182 end if;
19183 end if;
19184 end;
19185 end if;
19187 Next_Entity (Comp);
19188 end loop;
19189 end;
19191 return True;
19192 end Caller_Known_Size_Record;
19194 ------------------------------
19195 -- Large_Max_Size_Mutable --
19196 ------------------------------
19198 function Large_Max_Size_Mutable (Typ : Entity_Id) return Boolean is
19199 pragma Assert (Typ = Underlying_Type (Typ));
19201 function Is_Large_Discrete_Type (T : Entity_Id) return Boolean;
19202 -- Returns true if the discrete type T has a large range
19204 ----------------------------
19205 -- Is_Large_Discrete_Type --
19206 ----------------------------
19208 function Is_Large_Discrete_Type (T : Entity_Id) return Boolean is
19209 Threshold : constant Int := 16;
19210 -- Arbitrary threshold above which we consider it "large". We want
19211 -- a fairly large threshold, because these large types really
19212 -- shouldn't have default discriminants in the first place, in
19213 -- most cases.
19215 begin
19216 return UI_To_Int (RM_Size (T)) > Threshold;
19217 end Is_Large_Discrete_Type;
19219 -- Start of processing for Large_Max_Size_Mutable
19221 begin
19222 if Is_Record_Type (Typ)
19223 and then not Is_Limited_View (Typ)
19224 and then Has_Defaulted_Discriminants (Typ)
19225 then
19226 -- Loop through the components, looking for an array whose upper
19227 -- bound(s) depends on discriminants, where both the subtype of
19228 -- the discriminant and the index subtype are too large.
19230 declare
19231 Comp : Entity_Id;
19233 begin
19234 Comp := First_Entity (Typ);
19235 while Present (Comp) loop
19236 if Ekind (Comp) = E_Component then
19237 declare
19238 Comp_Type : constant Entity_Id :=
19239 Underlying_Type (Etype (Comp));
19241 Hi : Node_Id;
19242 Indx : Node_Id;
19243 Ityp : Entity_Id;
19245 begin
19246 if Is_Array_Type (Comp_Type) then
19247 Indx := First_Index (Comp_Type);
19249 while Present (Indx) loop
19250 Ityp := Etype (Indx);
19251 Hi := Type_High_Bound (Ityp);
19253 if Nkind (Hi) = N_Identifier
19254 and then Ekind (Entity (Hi)) = E_Discriminant
19255 and then Is_Large_Discrete_Type (Ityp)
19256 and then Is_Large_Discrete_Type
19257 (Etype (Entity (Hi)))
19258 then
19259 return True;
19260 end if;
19262 Next_Index (Indx);
19263 end loop;
19264 end if;
19265 end;
19266 end if;
19268 Next_Entity (Comp);
19269 end loop;
19270 end;
19271 end if;
19273 return False;
19274 end Large_Max_Size_Mutable;
19276 -- Local declarations
19278 Typ : constant Entity_Id := Underlying_Type (Id);
19280 -- Start of processing for New_Requires_Transient_Scope
19282 begin
19283 -- This is a private type which is not completed yet. This can only
19284 -- happen in a default expression (of a formal parameter or of a
19285 -- record component). Do not expand transient scope in this case.
19287 if No (Typ) then
19288 return False;
19290 -- Do not expand transient scope for non-existent procedure return or
19291 -- string literal types.
19293 elsif Typ = Standard_Void_Type
19294 or else Ekind (Typ) = E_String_Literal_Subtype
19295 then
19296 return False;
19298 -- If Typ is a generic formal incomplete type, then we want to look at
19299 -- the actual type.
19301 elsif Ekind (Typ) = E_Record_Subtype
19302 and then Present (Cloned_Subtype (Typ))
19303 then
19304 return New_Requires_Transient_Scope (Cloned_Subtype (Typ));
19306 -- Functions returning specific tagged types may dispatch on result, so
19307 -- their returned value is allocated on the secondary stack, even in the
19308 -- definite case. We must treat nondispatching functions the same way,
19309 -- because access-to-function types can point at both, so the calling
19310 -- conventions must be compatible. Is_Tagged_Type includes controlled
19311 -- types and class-wide types. Controlled type temporaries need
19312 -- finalization.
19314 -- ???It's not clear why we need to return noncontrolled types with
19315 -- controlled components on the secondary stack.
19317 elsif Is_Tagged_Type (Typ) or else Has_Controlled_Component (Typ) then
19318 return True;
19320 -- Untagged definite subtypes are known size. This includes all
19321 -- elementary [sub]types. Tasks are known size even if they have
19322 -- discriminants. So we return False here, with one exception:
19323 -- For a type like:
19324 -- type T (Last : Natural := 0) is
19325 -- X : String (1 .. Last);
19326 -- end record;
19327 -- we return True. That's because for "P(F(...));", where F returns T,
19328 -- we don't know the size of the result at the call site, so if we
19329 -- allocated it on the primary stack, we would have to allocate the
19330 -- maximum size, which is way too big.
19332 elsif Is_Definite_Subtype (Typ) or else Is_Task_Type (Typ) then
19333 return Large_Max_Size_Mutable (Typ);
19335 -- Indefinite (discriminated) untagged record or protected type
19337 elsif Is_Record_Type (Typ) or else Is_Protected_Type (Typ) then
19338 return not Caller_Known_Size_Record (Typ);
19340 -- Unconstrained array
19342 else
19343 pragma Assert (Is_Array_Type (Typ) and not Is_Definite_Subtype (Typ));
19344 return True;
19345 end if;
19346 end New_Requires_Transient_Scope;
19348 --------------------------
19349 -- No_Heap_Finalization --
19350 --------------------------
19352 function No_Heap_Finalization (Typ : Entity_Id) return Boolean is
19353 begin
19354 if Ekind_In (Typ, E_Access_Type, E_General_Access_Type)
19355 and then Is_Library_Level_Entity (Typ)
19356 then
19357 -- A global No_Heap_Finalization pragma applies to all library-level
19358 -- named access-to-object types.
19360 if Present (No_Heap_Finalization_Pragma) then
19361 return True;
19363 -- The library-level named access-to-object type itself is subject to
19364 -- pragma No_Heap_Finalization.
19366 elsif Present (Get_Pragma (Typ, Pragma_No_Heap_Finalization)) then
19367 return True;
19368 end if;
19369 end if;
19371 return False;
19372 end No_Heap_Finalization;
19374 -----------------------
19375 -- Normalize_Actuals --
19376 -----------------------
19378 -- Chain actuals according to formals of subprogram. If there are no named
19379 -- associations, the chain is simply the list of Parameter Associations,
19380 -- since the order is the same as the declaration order. If there are named
19381 -- associations, then the First_Named_Actual field in the N_Function_Call
19382 -- or N_Procedure_Call_Statement node points to the Parameter_Association
19383 -- node for the parameter that comes first in declaration order. The
19384 -- remaining named parameters are then chained in declaration order using
19385 -- Next_Named_Actual.
19387 -- This routine also verifies that the number of actuals is compatible with
19388 -- the number and default values of formals, but performs no type checking
19389 -- (type checking is done by the caller).
19391 -- If the matching succeeds, Success is set to True and the caller proceeds
19392 -- with type-checking. If the match is unsuccessful, then Success is set to
19393 -- False, and the caller attempts a different interpretation, if there is
19394 -- one.
19396 -- If the flag Report is on, the call is not overloaded, and a failure to
19397 -- match can be reported here, rather than in the caller.
19399 procedure Normalize_Actuals
19400 (N : Node_Id;
19401 S : Entity_Id;
19402 Report : Boolean;
19403 Success : out Boolean)
19405 Actuals : constant List_Id := Parameter_Associations (N);
19406 Actual : Node_Id := Empty;
19407 Formal : Entity_Id;
19408 Last : Node_Id := Empty;
19409 First_Named : Node_Id := Empty;
19410 Found : Boolean;
19412 Formals_To_Match : Integer := 0;
19413 Actuals_To_Match : Integer := 0;
19415 procedure Chain (A : Node_Id);
19416 -- Add named actual at the proper place in the list, using the
19417 -- Next_Named_Actual link.
19419 function Reporting return Boolean;
19420 -- Determines if an error is to be reported. To report an error, we
19421 -- need Report to be True, and also we do not report errors caused
19422 -- by calls to init procs that occur within other init procs. Such
19423 -- errors must always be cascaded errors, since if all the types are
19424 -- declared correctly, the compiler will certainly build decent calls.
19426 -----------
19427 -- Chain --
19428 -----------
19430 procedure Chain (A : Node_Id) is
19431 begin
19432 if No (Last) then
19434 -- Call node points to first actual in list
19436 Set_First_Named_Actual (N, Explicit_Actual_Parameter (A));
19438 else
19439 Set_Next_Named_Actual (Last, Explicit_Actual_Parameter (A));
19440 end if;
19442 Last := A;
19443 Set_Next_Named_Actual (Last, Empty);
19444 end Chain;
19446 ---------------
19447 -- Reporting --
19448 ---------------
19450 function Reporting return Boolean is
19451 begin
19452 if not Report then
19453 return False;
19455 elsif not Within_Init_Proc then
19456 return True;
19458 elsif Is_Init_Proc (Entity (Name (N))) then
19459 return False;
19461 else
19462 return True;
19463 end if;
19464 end Reporting;
19466 -- Start of processing for Normalize_Actuals
19468 begin
19469 if Is_Access_Type (S) then
19471 -- The name in the call is a function call that returns an access
19472 -- to subprogram. The designated type has the list of formals.
19474 Formal := First_Formal (Designated_Type (S));
19475 else
19476 Formal := First_Formal (S);
19477 end if;
19479 while Present (Formal) loop
19480 Formals_To_Match := Formals_To_Match + 1;
19481 Next_Formal (Formal);
19482 end loop;
19484 -- Find if there is a named association, and verify that no positional
19485 -- associations appear after named ones.
19487 if Present (Actuals) then
19488 Actual := First (Actuals);
19489 end if;
19491 while Present (Actual)
19492 and then Nkind (Actual) /= N_Parameter_Association
19493 loop
19494 Actuals_To_Match := Actuals_To_Match + 1;
19495 Next (Actual);
19496 end loop;
19498 if No (Actual) and Actuals_To_Match = Formals_To_Match then
19500 -- Most common case: positional notation, no defaults
19502 Success := True;
19503 return;
19505 elsif Actuals_To_Match > Formals_To_Match then
19507 -- Too many actuals: will not work
19509 if Reporting then
19510 if Is_Entity_Name (Name (N)) then
19511 Error_Msg_N ("too many arguments in call to&", Name (N));
19512 else
19513 Error_Msg_N ("too many arguments in call", N);
19514 end if;
19515 end if;
19517 Success := False;
19518 return;
19519 end if;
19521 First_Named := Actual;
19523 while Present (Actual) loop
19524 if Nkind (Actual) /= N_Parameter_Association then
19525 Error_Msg_N
19526 ("positional parameters not allowed after named ones", Actual);
19527 Success := False;
19528 return;
19530 else
19531 Actuals_To_Match := Actuals_To_Match + 1;
19532 end if;
19534 Next (Actual);
19535 end loop;
19537 if Present (Actuals) then
19538 Actual := First (Actuals);
19539 end if;
19541 Formal := First_Formal (S);
19542 while Present (Formal) loop
19544 -- Match the formals in order. If the corresponding actual is
19545 -- positional, nothing to do. Else scan the list of named actuals
19546 -- to find the one with the right name.
19548 if Present (Actual)
19549 and then Nkind (Actual) /= N_Parameter_Association
19550 then
19551 Next (Actual);
19552 Actuals_To_Match := Actuals_To_Match - 1;
19553 Formals_To_Match := Formals_To_Match - 1;
19555 else
19556 -- For named parameters, search the list of actuals to find
19557 -- one that matches the next formal name.
19559 Actual := First_Named;
19560 Found := False;
19561 while Present (Actual) loop
19562 if Chars (Selector_Name (Actual)) = Chars (Formal) then
19563 Found := True;
19564 Chain (Actual);
19565 Actuals_To_Match := Actuals_To_Match - 1;
19566 Formals_To_Match := Formals_To_Match - 1;
19567 exit;
19568 end if;
19570 Next (Actual);
19571 end loop;
19573 if not Found then
19574 if Ekind (Formal) /= E_In_Parameter
19575 or else No (Default_Value (Formal))
19576 then
19577 if Reporting then
19578 if (Comes_From_Source (S)
19579 or else Sloc (S) = Standard_Location)
19580 and then Is_Overloadable (S)
19581 then
19582 if No (Actuals)
19583 and then
19584 Nkind_In (Parent (N), N_Procedure_Call_Statement,
19585 N_Function_Call,
19586 N_Parameter_Association)
19587 and then Ekind (S) /= E_Function
19588 then
19589 Set_Etype (N, Etype (S));
19591 else
19592 Error_Msg_Name_1 := Chars (S);
19593 Error_Msg_Sloc := Sloc (S);
19594 Error_Msg_NE
19595 ("missing argument for parameter & "
19596 & "in call to % declared #", N, Formal);
19597 end if;
19599 elsif Is_Overloadable (S) then
19600 Error_Msg_Name_1 := Chars (S);
19602 -- Point to type derivation that generated the
19603 -- operation.
19605 Error_Msg_Sloc := Sloc (Parent (S));
19607 Error_Msg_NE
19608 ("missing argument for parameter & "
19609 & "in call to % (inherited) #", N, Formal);
19611 else
19612 Error_Msg_NE
19613 ("missing argument for parameter &", N, Formal);
19614 end if;
19615 end if;
19617 Success := False;
19618 return;
19620 else
19621 Formals_To_Match := Formals_To_Match - 1;
19622 end if;
19623 end if;
19624 end if;
19626 Next_Formal (Formal);
19627 end loop;
19629 if Formals_To_Match = 0 and then Actuals_To_Match = 0 then
19630 Success := True;
19631 return;
19633 else
19634 if Reporting then
19636 -- Find some superfluous named actual that did not get
19637 -- attached to the list of associations.
19639 Actual := First (Actuals);
19640 while Present (Actual) loop
19641 if Nkind (Actual) = N_Parameter_Association
19642 and then Actual /= Last
19643 and then No (Next_Named_Actual (Actual))
19644 then
19645 -- A validity check may introduce a copy of a call that
19646 -- includes an extra actual (for example for an unrelated
19647 -- accessibility check). Check that the extra actual matches
19648 -- some extra formal, which must exist already because
19649 -- subprogram must be frozen at this point.
19651 if Present (Extra_Formals (S))
19652 and then not Comes_From_Source (Actual)
19653 and then Nkind (Actual) = N_Parameter_Association
19654 and then Chars (Extra_Formals (S)) =
19655 Chars (Selector_Name (Actual))
19656 then
19657 null;
19658 else
19659 Error_Msg_N
19660 ("unmatched actual & in call", Selector_Name (Actual));
19661 exit;
19662 end if;
19663 end if;
19665 Next (Actual);
19666 end loop;
19667 end if;
19669 Success := False;
19670 return;
19671 end if;
19672 end Normalize_Actuals;
19674 --------------------------------
19675 -- Note_Possible_Modification --
19676 --------------------------------
19678 procedure Note_Possible_Modification (N : Node_Id; Sure : Boolean) is
19679 Modification_Comes_From_Source : constant Boolean :=
19680 Comes_From_Source (Parent (N));
19682 Ent : Entity_Id;
19683 Exp : Node_Id;
19685 begin
19686 -- Loop to find referenced entity, if there is one
19688 Exp := N;
19689 loop
19690 Ent := Empty;
19692 if Is_Entity_Name (Exp) then
19693 Ent := Entity (Exp);
19695 -- If the entity is missing, it is an undeclared identifier,
19696 -- and there is nothing to annotate.
19698 if No (Ent) then
19699 return;
19700 end if;
19702 elsif Nkind (Exp) = N_Explicit_Dereference then
19703 declare
19704 P : constant Node_Id := Prefix (Exp);
19706 begin
19707 -- In formal verification mode, keep track of all reads and
19708 -- writes through explicit dereferences.
19710 if GNATprove_Mode then
19711 SPARK_Specific.Generate_Dereference (N, 'm');
19712 end if;
19714 if Nkind (P) = N_Selected_Component
19715 and then Present (Entry_Formal (Entity (Selector_Name (P))))
19716 then
19717 -- Case of a reference to an entry formal
19719 Ent := Entry_Formal (Entity (Selector_Name (P)));
19721 elsif Nkind (P) = N_Identifier
19722 and then Nkind (Parent (Entity (P))) = N_Object_Declaration
19723 and then Present (Expression (Parent (Entity (P))))
19724 and then Nkind (Expression (Parent (Entity (P)))) =
19725 N_Reference
19726 then
19727 -- Case of a reference to a value on which side effects have
19728 -- been removed.
19730 Exp := Prefix (Expression (Parent (Entity (P))));
19731 goto Continue;
19733 else
19734 return;
19735 end if;
19736 end;
19738 elsif Nkind_In (Exp, N_Type_Conversion,
19739 N_Unchecked_Type_Conversion)
19740 then
19741 Exp := Expression (Exp);
19742 goto Continue;
19744 elsif Nkind_In (Exp, N_Slice,
19745 N_Indexed_Component,
19746 N_Selected_Component)
19747 then
19748 -- Special check, if the prefix is an access type, then return
19749 -- since we are modifying the thing pointed to, not the prefix.
19750 -- When we are expanding, most usually the prefix is replaced
19751 -- by an explicit dereference, and this test is not needed, but
19752 -- in some cases (notably -gnatc mode and generics) when we do
19753 -- not do full expansion, we need this special test.
19755 if Is_Access_Type (Etype (Prefix (Exp))) then
19756 return;
19758 -- Otherwise go to prefix and keep going
19760 else
19761 Exp := Prefix (Exp);
19762 goto Continue;
19763 end if;
19765 -- All other cases, not a modification
19767 else
19768 return;
19769 end if;
19771 -- Now look for entity being referenced
19773 if Present (Ent) then
19774 if Is_Object (Ent) then
19775 if Comes_From_Source (Exp)
19776 or else Modification_Comes_From_Source
19777 then
19778 -- Give warning if pragma unmodified is given and we are
19779 -- sure this is a modification.
19781 if Has_Pragma_Unmodified (Ent) and then Sure then
19783 -- Note that the entity may be present only as a result
19784 -- of pragma Unused.
19786 if Has_Pragma_Unused (Ent) then
19787 Error_Msg_NE ("??pragma Unused given for &!", N, Ent);
19788 else
19789 Error_Msg_NE
19790 ("??pragma Unmodified given for &!", N, Ent);
19791 end if;
19792 end if;
19794 Set_Never_Set_In_Source (Ent, False);
19795 end if;
19797 Set_Is_True_Constant (Ent, False);
19798 Set_Current_Value (Ent, Empty);
19799 Set_Is_Known_Null (Ent, False);
19801 if not Can_Never_Be_Null (Ent) then
19802 Set_Is_Known_Non_Null (Ent, False);
19803 end if;
19805 -- Follow renaming chain
19807 if (Ekind (Ent) = E_Variable or else Ekind (Ent) = E_Constant)
19808 and then Present (Renamed_Object (Ent))
19809 then
19810 Exp := Renamed_Object (Ent);
19812 -- If the entity is the loop variable in an iteration over
19813 -- a container, retrieve container expression to indicate
19814 -- possible modification.
19816 if Present (Related_Expression (Ent))
19817 and then Nkind (Parent (Related_Expression (Ent))) =
19818 N_Iterator_Specification
19819 then
19820 Exp := Original_Node (Related_Expression (Ent));
19821 end if;
19823 goto Continue;
19825 -- The expression may be the renaming of a subcomponent of an
19826 -- array or container. The assignment to the subcomponent is
19827 -- a modification of the container.
19829 elsif Comes_From_Source (Original_Node (Exp))
19830 and then Nkind_In (Original_Node (Exp), N_Selected_Component,
19831 N_Indexed_Component)
19832 then
19833 Exp := Prefix (Original_Node (Exp));
19834 goto Continue;
19835 end if;
19837 -- Generate a reference only if the assignment comes from
19838 -- source. This excludes, for example, calls to a dispatching
19839 -- assignment operation when the left-hand side is tagged. In
19840 -- GNATprove mode, we need those references also on generated
19841 -- code, as these are used to compute the local effects of
19842 -- subprograms.
19844 if Modification_Comes_From_Source or GNATprove_Mode then
19845 Generate_Reference (Ent, Exp, 'm');
19847 -- If the target of the assignment is the bound variable
19848 -- in an iterator, indicate that the corresponding array
19849 -- or container is also modified.
19851 if Ada_Version >= Ada_2012
19852 and then Nkind (Parent (Ent)) = N_Iterator_Specification
19853 then
19854 declare
19855 Domain : constant Node_Id := Name (Parent (Ent));
19857 begin
19858 -- TBD : in the full version of the construct, the
19859 -- domain of iteration can be given by an expression.
19861 if Is_Entity_Name (Domain) then
19862 Generate_Reference (Entity (Domain), Exp, 'm');
19863 Set_Is_True_Constant (Entity (Domain), False);
19864 Set_Never_Set_In_Source (Entity (Domain), False);
19865 end if;
19866 end;
19867 end if;
19868 end if;
19869 end if;
19871 Kill_Checks (Ent);
19873 -- If we are sure this is a modification from source, and we know
19874 -- this modifies a constant, then give an appropriate warning.
19876 if Sure
19877 and then Modification_Comes_From_Source
19878 and then Overlays_Constant (Ent)
19879 and then Address_Clause_Overlay_Warnings
19880 then
19881 declare
19882 Addr : constant Node_Id := Address_Clause (Ent);
19883 O_Ent : Entity_Id;
19884 Off : Boolean;
19886 begin
19887 Find_Overlaid_Entity (Addr, O_Ent, Off);
19889 Error_Msg_Sloc := Sloc (Addr);
19890 Error_Msg_NE
19891 ("??constant& may be modified via address clause#",
19892 N, O_Ent);
19893 end;
19894 end if;
19896 return;
19897 end if;
19899 <<Continue>>
19900 null;
19901 end loop;
19902 end Note_Possible_Modification;
19904 -----------------
19905 -- Null_Status --
19906 -----------------
19908 function Null_Status (N : Node_Id) return Null_Status_Kind is
19909 function Is_Null_Excluding_Def (Def : Node_Id) return Boolean;
19910 -- Determine whether definition Def carries a null exclusion
19912 function Null_Status_Of_Entity (Id : Entity_Id) return Null_Status_Kind;
19913 -- Determine the null status of arbitrary entity Id
19915 function Null_Status_Of_Type (Typ : Entity_Id) return Null_Status_Kind;
19916 -- Determine the null status of type Typ
19918 ---------------------------
19919 -- Is_Null_Excluding_Def --
19920 ---------------------------
19922 function Is_Null_Excluding_Def (Def : Node_Id) return Boolean is
19923 begin
19924 return
19925 Nkind_In (Def, N_Access_Definition,
19926 N_Access_Function_Definition,
19927 N_Access_Procedure_Definition,
19928 N_Access_To_Object_Definition,
19929 N_Component_Definition,
19930 N_Derived_Type_Definition)
19931 and then Null_Exclusion_Present (Def);
19932 end Is_Null_Excluding_Def;
19934 ---------------------------
19935 -- Null_Status_Of_Entity --
19936 ---------------------------
19938 function Null_Status_Of_Entity
19939 (Id : Entity_Id) return Null_Status_Kind
19941 Decl : constant Node_Id := Declaration_Node (Id);
19942 Def : Node_Id;
19944 begin
19945 -- The value of an imported or exported entity may be set externally
19946 -- regardless of a null exclusion. As a result, the value cannot be
19947 -- determined statically.
19949 if Is_Imported (Id) or else Is_Exported (Id) then
19950 return Unknown;
19952 elsif Nkind_In (Decl, N_Component_Declaration,
19953 N_Discriminant_Specification,
19954 N_Formal_Object_Declaration,
19955 N_Object_Declaration,
19956 N_Object_Renaming_Declaration,
19957 N_Parameter_Specification)
19958 then
19959 -- A component declaration yields a non-null value when either
19960 -- its component definition or access definition carries a null
19961 -- exclusion.
19963 if Nkind (Decl) = N_Component_Declaration then
19964 Def := Component_Definition (Decl);
19966 if Is_Null_Excluding_Def (Def) then
19967 return Is_Non_Null;
19968 end if;
19970 Def := Access_Definition (Def);
19972 if Present (Def) and then Is_Null_Excluding_Def (Def) then
19973 return Is_Non_Null;
19974 end if;
19976 -- A formal object declaration yields a non-null value if its
19977 -- access definition carries a null exclusion. If the object is
19978 -- default initialized, then the value depends on the expression.
19980 elsif Nkind (Decl) = N_Formal_Object_Declaration then
19981 Def := Access_Definition (Decl);
19983 if Present (Def) and then Is_Null_Excluding_Def (Def) then
19984 return Is_Non_Null;
19985 end if;
19987 -- A constant may yield a null or non-null value depending on its
19988 -- initialization expression.
19990 elsif Ekind (Id) = E_Constant then
19991 return Null_Status (Constant_Value (Id));
19993 -- The construct yields a non-null value when it has a null
19994 -- exclusion.
19996 elsif Null_Exclusion_Present (Decl) then
19997 return Is_Non_Null;
19999 -- An object renaming declaration yields a non-null value if its
20000 -- access definition carries a null exclusion. Otherwise the value
20001 -- depends on the renamed name.
20003 elsif Nkind (Decl) = N_Object_Renaming_Declaration then
20004 Def := Access_Definition (Decl);
20006 if Present (Def) and then Is_Null_Excluding_Def (Def) then
20007 return Is_Non_Null;
20009 else
20010 return Null_Status (Name (Decl));
20011 end if;
20012 end if;
20013 end if;
20015 -- At this point the declaration of the entity does not carry a null
20016 -- exclusion and lacks an initialization expression. Check the status
20017 -- of its type.
20019 return Null_Status_Of_Type (Etype (Id));
20020 end Null_Status_Of_Entity;
20022 -------------------------
20023 -- Null_Status_Of_Type --
20024 -------------------------
20026 function Null_Status_Of_Type (Typ : Entity_Id) return Null_Status_Kind is
20027 Curr : Entity_Id;
20028 Decl : Node_Id;
20030 begin
20031 -- Traverse the type chain looking for types with null exclusion
20033 Curr := Typ;
20034 while Present (Curr) and then Etype (Curr) /= Curr loop
20035 Decl := Parent (Curr);
20037 -- Guard against itypes which do not always have declarations. A
20038 -- type yields a non-null value if it carries a null exclusion.
20040 if Present (Decl) then
20041 if Nkind (Decl) = N_Full_Type_Declaration
20042 and then Is_Null_Excluding_Def (Type_Definition (Decl))
20043 then
20044 return Is_Non_Null;
20046 elsif Nkind (Decl) = N_Subtype_Declaration
20047 and then Null_Exclusion_Present (Decl)
20048 then
20049 return Is_Non_Null;
20050 end if;
20051 end if;
20053 Curr := Etype (Curr);
20054 end loop;
20056 -- The type chain does not contain any null excluding types
20058 return Unknown;
20059 end Null_Status_Of_Type;
20061 -- Start of processing for Null_Status
20063 begin
20064 -- An allocator always creates a non-null value
20066 if Nkind (N) = N_Allocator then
20067 return Is_Non_Null;
20069 -- Taking the 'Access of something yields a non-null value
20071 elsif Nkind (N) = N_Attribute_Reference
20072 and then Nam_In (Attribute_Name (N), Name_Access,
20073 Name_Unchecked_Access,
20074 Name_Unrestricted_Access)
20075 then
20076 return Is_Non_Null;
20078 -- "null" yields null
20080 elsif Nkind (N) = N_Null then
20081 return Is_Null;
20083 -- Check the status of the operand of a type conversion
20085 elsif Nkind (N) = N_Type_Conversion then
20086 return Null_Status (Expression (N));
20088 -- The input denotes a reference to an entity. Determine whether the
20089 -- entity or its type yields a null or non-null value.
20091 elsif Is_Entity_Name (N) and then Present (Entity (N)) then
20092 return Null_Status_Of_Entity (Entity (N));
20093 end if;
20095 -- Otherwise it is not possible to determine the null status of the
20096 -- subexpression at compile time without resorting to simple flow
20097 -- analysis.
20099 return Unknown;
20100 end Null_Status;
20102 --------------------------------------
20103 -- Null_To_Null_Address_Convert_OK --
20104 --------------------------------------
20106 function Null_To_Null_Address_Convert_OK
20107 (N : Node_Id;
20108 Typ : Entity_Id := Empty) return Boolean
20110 begin
20111 if not Relaxed_RM_Semantics then
20112 return False;
20113 end if;
20115 if Nkind (N) = N_Null then
20116 return Present (Typ) and then Is_Descendant_Of_Address (Typ);
20118 elsif Nkind_In (N, N_Op_Eq, N_Op_Ge, N_Op_Gt, N_Op_Le, N_Op_Lt, N_Op_Ne)
20119 then
20120 declare
20121 L : constant Node_Id := Left_Opnd (N);
20122 R : constant Node_Id := Right_Opnd (N);
20124 begin
20125 -- We check the Etype of the complementary operand since the
20126 -- N_Null node is not decorated at this stage.
20128 return
20129 ((Nkind (L) = N_Null
20130 and then Is_Descendant_Of_Address (Etype (R)))
20131 or else
20132 (Nkind (R) = N_Null
20133 and then Is_Descendant_Of_Address (Etype (L))));
20134 end;
20135 end if;
20137 return False;
20138 end Null_To_Null_Address_Convert_OK;
20140 -------------------------
20141 -- Object_Access_Level --
20142 -------------------------
20144 -- Returns the static accessibility level of the view denoted by Obj. Note
20145 -- that the value returned is the result of a call to Scope_Depth. Only
20146 -- scope depths associated with dynamic scopes can actually be returned.
20147 -- Since only relative levels matter for accessibility checking, the fact
20148 -- that the distance between successive levels of accessibility is not
20149 -- always one is immaterial (invariant: if level(E2) is deeper than
20150 -- level(E1), then Scope_Depth(E1) < Scope_Depth(E2)).
20152 function Object_Access_Level (Obj : Node_Id) return Uint is
20153 function Is_Interface_Conversion (N : Node_Id) return Boolean;
20154 -- Determine whether N is a construct of the form
20155 -- Some_Type (Operand._tag'Address)
20156 -- This construct appears in the context of dispatching calls.
20158 function Reference_To (Obj : Node_Id) return Node_Id;
20159 -- An explicit dereference is created when removing side-effects from
20160 -- expressions for constraint checking purposes. In this case a local
20161 -- access type is created for it. The correct access level is that of
20162 -- the original source node. We detect this case by noting that the
20163 -- prefix of the dereference is created by an object declaration whose
20164 -- initial expression is a reference.
20166 -----------------------------
20167 -- Is_Interface_Conversion --
20168 -----------------------------
20170 function Is_Interface_Conversion (N : Node_Id) return Boolean is
20171 begin
20172 return Nkind (N) = N_Unchecked_Type_Conversion
20173 and then Nkind (Expression (N)) = N_Attribute_Reference
20174 and then Attribute_Name (Expression (N)) = Name_Address;
20175 end Is_Interface_Conversion;
20177 ------------------
20178 -- Reference_To --
20179 ------------------
20181 function Reference_To (Obj : Node_Id) return Node_Id is
20182 Pref : constant Node_Id := Prefix (Obj);
20183 begin
20184 if Is_Entity_Name (Pref)
20185 and then Nkind (Parent (Entity (Pref))) = N_Object_Declaration
20186 and then Present (Expression (Parent (Entity (Pref))))
20187 and then Nkind (Expression (Parent (Entity (Pref)))) = N_Reference
20188 then
20189 return (Prefix (Expression (Parent (Entity (Pref)))));
20190 else
20191 return Empty;
20192 end if;
20193 end Reference_To;
20195 -- Local variables
20197 E : Entity_Id;
20199 -- Start of processing for Object_Access_Level
20201 begin
20202 if Nkind (Obj) = N_Defining_Identifier
20203 or else Is_Entity_Name (Obj)
20204 then
20205 if Nkind (Obj) = N_Defining_Identifier then
20206 E := Obj;
20207 else
20208 E := Entity (Obj);
20209 end if;
20211 if Is_Prival (E) then
20212 E := Prival_Link (E);
20213 end if;
20215 -- If E is a type then it denotes a current instance. For this case
20216 -- we add one to the normal accessibility level of the type to ensure
20217 -- that current instances are treated as always being deeper than
20218 -- than the level of any visible named access type (see 3.10.2(21)).
20220 if Is_Type (E) then
20221 return Type_Access_Level (E) + 1;
20223 elsif Present (Renamed_Object (E)) then
20224 return Object_Access_Level (Renamed_Object (E));
20226 -- Similarly, if E is a component of the current instance of a
20227 -- protected type, any instance of it is assumed to be at a deeper
20228 -- level than the type. For a protected object (whose type is an
20229 -- anonymous protected type) its components are at the same level
20230 -- as the type itself.
20232 elsif not Is_Overloadable (E)
20233 and then Ekind (Scope (E)) = E_Protected_Type
20234 and then Comes_From_Source (Scope (E))
20235 then
20236 return Type_Access_Level (Scope (E)) + 1;
20238 else
20239 -- Aliased formals of functions take their access level from the
20240 -- point of call, i.e. require a dynamic check. For static check
20241 -- purposes, this is smaller than the level of the subprogram
20242 -- itself. For procedures the aliased makes no difference.
20244 if Is_Formal (E)
20245 and then Is_Aliased (E)
20246 and then Ekind (Scope (E)) = E_Function
20247 then
20248 return Type_Access_Level (Etype (E));
20250 else
20251 return Scope_Depth (Enclosing_Dynamic_Scope (E));
20252 end if;
20253 end if;
20255 elsif Nkind_In (Obj, N_Indexed_Component, N_Selected_Component) then
20256 if Is_Access_Type (Etype (Prefix (Obj))) then
20257 return Type_Access_Level (Etype (Prefix (Obj)));
20258 else
20259 return Object_Access_Level (Prefix (Obj));
20260 end if;
20262 elsif Nkind (Obj) = N_Explicit_Dereference then
20264 -- If the prefix is a selected access discriminant then we make a
20265 -- recursive call on the prefix, which will in turn check the level
20266 -- of the prefix object of the selected discriminant.
20268 -- In Ada 2012, if the discriminant has implicit dereference and
20269 -- the context is a selected component, treat this as an object of
20270 -- unknown scope (see below). This is necessary in compile-only mode;
20271 -- otherwise expansion will already have transformed the prefix into
20272 -- a temporary.
20274 if Nkind (Prefix (Obj)) = N_Selected_Component
20275 and then Ekind (Etype (Prefix (Obj))) = E_Anonymous_Access_Type
20276 and then
20277 Ekind (Entity (Selector_Name (Prefix (Obj)))) = E_Discriminant
20278 and then
20279 (not Has_Implicit_Dereference
20280 (Entity (Selector_Name (Prefix (Obj))))
20281 or else Nkind (Parent (Obj)) /= N_Selected_Component)
20282 then
20283 return Object_Access_Level (Prefix (Obj));
20285 -- Detect an interface conversion in the context of a dispatching
20286 -- call. Use the original form of the conversion to find the access
20287 -- level of the operand.
20289 elsif Is_Interface (Etype (Obj))
20290 and then Is_Interface_Conversion (Prefix (Obj))
20291 and then Nkind (Original_Node (Obj)) = N_Type_Conversion
20292 then
20293 return Object_Access_Level (Original_Node (Obj));
20295 elsif not Comes_From_Source (Obj) then
20296 declare
20297 Ref : constant Node_Id := Reference_To (Obj);
20298 begin
20299 if Present (Ref) then
20300 return Object_Access_Level (Ref);
20301 else
20302 return Type_Access_Level (Etype (Prefix (Obj)));
20303 end if;
20304 end;
20306 else
20307 return Type_Access_Level (Etype (Prefix (Obj)));
20308 end if;
20310 elsif Nkind_In (Obj, N_Type_Conversion, N_Unchecked_Type_Conversion) then
20311 return Object_Access_Level (Expression (Obj));
20313 elsif Nkind (Obj) = N_Function_Call then
20315 -- Function results are objects, so we get either the access level of
20316 -- the function or, in the case of an indirect call, the level of the
20317 -- access-to-subprogram type. (This code is used for Ada 95, but it
20318 -- looks wrong, because it seems that we should be checking the level
20319 -- of the call itself, even for Ada 95. However, using the Ada 2005
20320 -- version of the code causes regressions in several tests that are
20321 -- compiled with -gnat95. ???)
20323 if Ada_Version < Ada_2005 then
20324 if Is_Entity_Name (Name (Obj)) then
20325 return Subprogram_Access_Level (Entity (Name (Obj)));
20326 else
20327 return Type_Access_Level (Etype (Prefix (Name (Obj))));
20328 end if;
20330 -- For Ada 2005, the level of the result object of a function call is
20331 -- defined to be the level of the call's innermost enclosing master.
20332 -- We determine that by querying the depth of the innermost enclosing
20333 -- dynamic scope.
20335 else
20336 Return_Master_Scope_Depth_Of_Call : declare
20337 function Innermost_Master_Scope_Depth
20338 (N : Node_Id) return Uint;
20339 -- Returns the scope depth of the given node's innermost
20340 -- enclosing dynamic scope (effectively the accessibility
20341 -- level of the innermost enclosing master).
20343 ----------------------------------
20344 -- Innermost_Master_Scope_Depth --
20345 ----------------------------------
20347 function Innermost_Master_Scope_Depth
20348 (N : Node_Id) return Uint
20350 Node_Par : Node_Id := Parent (N);
20352 begin
20353 -- Locate the nearest enclosing node (by traversing Parents)
20354 -- that Defining_Entity can be applied to, and return the
20355 -- depth of that entity's nearest enclosing dynamic scope.
20357 while Present (Node_Par) loop
20358 case Nkind (Node_Par) is
20359 when N_Abstract_Subprogram_Declaration
20360 | N_Block_Statement
20361 | N_Body_Stub
20362 | N_Component_Declaration
20363 | N_Entry_Body
20364 | N_Entry_Declaration
20365 | N_Exception_Declaration
20366 | N_Formal_Object_Declaration
20367 | N_Formal_Package_Declaration
20368 | N_Formal_Subprogram_Declaration
20369 | N_Formal_Type_Declaration
20370 | N_Full_Type_Declaration
20371 | N_Function_Specification
20372 | N_Generic_Declaration
20373 | N_Generic_Instantiation
20374 | N_Implicit_Label_Declaration
20375 | N_Incomplete_Type_Declaration
20376 | N_Loop_Parameter_Specification
20377 | N_Number_Declaration
20378 | N_Object_Declaration
20379 | N_Package_Declaration
20380 | N_Package_Specification
20381 | N_Parameter_Specification
20382 | N_Private_Extension_Declaration
20383 | N_Private_Type_Declaration
20384 | N_Procedure_Specification
20385 | N_Proper_Body
20386 | N_Protected_Type_Declaration
20387 | N_Renaming_Declaration
20388 | N_Single_Protected_Declaration
20389 | N_Single_Task_Declaration
20390 | N_Subprogram_Declaration
20391 | N_Subtype_Declaration
20392 | N_Subunit
20393 | N_Task_Type_Declaration
20395 return Scope_Depth
20396 (Nearest_Dynamic_Scope
20397 (Defining_Entity (Node_Par)));
20399 when others =>
20400 null;
20401 end case;
20403 Node_Par := Parent (Node_Par);
20404 end loop;
20406 pragma Assert (False);
20408 -- Should never reach the following return
20410 return Scope_Depth (Current_Scope) + 1;
20411 end Innermost_Master_Scope_Depth;
20413 -- Start of processing for Return_Master_Scope_Depth_Of_Call
20415 begin
20416 return Innermost_Master_Scope_Depth (Obj);
20417 end Return_Master_Scope_Depth_Of_Call;
20418 end if;
20420 -- For convenience we handle qualified expressions, even though they
20421 -- aren't technically object names.
20423 elsif Nkind (Obj) = N_Qualified_Expression then
20424 return Object_Access_Level (Expression (Obj));
20426 -- Ditto for aggregates. They have the level of the temporary that
20427 -- will hold their value.
20429 elsif Nkind (Obj) = N_Aggregate then
20430 return Object_Access_Level (Current_Scope);
20432 -- Otherwise return the scope level of Standard. (If there are cases
20433 -- that fall through to this point they will be treated as having
20434 -- global accessibility for now. ???)
20436 else
20437 return Scope_Depth (Standard_Standard);
20438 end if;
20439 end Object_Access_Level;
20441 ----------------------------------
20442 -- Old_Requires_Transient_Scope --
20443 ----------------------------------
20445 function Old_Requires_Transient_Scope (Id : Entity_Id) return Boolean is
20446 Typ : constant Entity_Id := Underlying_Type (Id);
20448 begin
20449 -- This is a private type which is not completed yet. This can only
20450 -- happen in a default expression (of a formal parameter or of a
20451 -- record component). Do not expand transient scope in this case.
20453 if No (Typ) then
20454 return False;
20456 -- Do not expand transient scope for non-existent procedure return
20458 elsif Typ = Standard_Void_Type then
20459 return False;
20461 -- Elementary types do not require a transient scope
20463 elsif Is_Elementary_Type (Typ) then
20464 return False;
20466 -- Generally, indefinite subtypes require a transient scope, since the
20467 -- back end cannot generate temporaries, since this is not a valid type
20468 -- for declaring an object. It might be possible to relax this in the
20469 -- future, e.g. by declaring the maximum possible space for the type.
20471 elsif not Is_Definite_Subtype (Typ) then
20472 return True;
20474 -- Functions returning tagged types may dispatch on result so their
20475 -- returned value is allocated on the secondary stack. Controlled
20476 -- type temporaries need finalization.
20478 elsif Is_Tagged_Type (Typ) or else Has_Controlled_Component (Typ) then
20479 return True;
20481 -- Record type
20483 elsif Is_Record_Type (Typ) then
20484 declare
20485 Comp : Entity_Id;
20487 begin
20488 Comp := First_Entity (Typ);
20489 while Present (Comp) loop
20490 if Ekind (Comp) = E_Component then
20492 -- ???It's not clear we need a full recursive call to
20493 -- Old_Requires_Transient_Scope here. Note that the
20494 -- following can't happen.
20496 pragma Assert (Is_Definite_Subtype (Etype (Comp)));
20497 pragma Assert (not Has_Controlled_Component (Etype (Comp)));
20499 if Old_Requires_Transient_Scope (Etype (Comp)) then
20500 return True;
20501 end if;
20502 end if;
20504 Next_Entity (Comp);
20505 end loop;
20506 end;
20508 return False;
20510 -- String literal types never require transient scope
20512 elsif Ekind (Typ) = E_String_Literal_Subtype then
20513 return False;
20515 -- Array type. Note that we already know that this is a constrained
20516 -- array, since unconstrained arrays will fail the indefinite test.
20518 elsif Is_Array_Type (Typ) then
20520 -- If component type requires a transient scope, the array does too
20522 if Old_Requires_Transient_Scope (Component_Type (Typ)) then
20523 return True;
20525 -- Otherwise, we only need a transient scope if the size depends on
20526 -- the value of one or more discriminants.
20528 else
20529 return Size_Depends_On_Discriminant (Typ);
20530 end if;
20532 -- All other cases do not require a transient scope
20534 else
20535 pragma Assert (Is_Protected_Type (Typ) or else Is_Task_Type (Typ));
20536 return False;
20537 end if;
20538 end Old_Requires_Transient_Scope;
20540 ---------------------------------
20541 -- Original_Aspect_Pragma_Name --
20542 ---------------------------------
20544 function Original_Aspect_Pragma_Name (N : Node_Id) return Name_Id is
20545 Item : Node_Id;
20546 Item_Nam : Name_Id;
20548 begin
20549 pragma Assert (Nkind_In (N, N_Aspect_Specification, N_Pragma));
20551 Item := N;
20553 -- The pragma was generated to emulate an aspect, use the original
20554 -- aspect specification.
20556 if Nkind (Item) = N_Pragma and then From_Aspect_Specification (Item) then
20557 Item := Corresponding_Aspect (Item);
20558 end if;
20560 -- Retrieve the name of the aspect/pragma. Note that Pre, Pre_Class,
20561 -- Post and Post_Class rewrite their pragma identifier to preserve the
20562 -- original name.
20563 -- ??? this is kludgey
20565 if Nkind (Item) = N_Pragma then
20566 Item_Nam := Chars (Original_Node (Pragma_Identifier (Item)));
20568 else
20569 pragma Assert (Nkind (Item) = N_Aspect_Specification);
20570 Item_Nam := Chars (Identifier (Item));
20571 end if;
20573 -- Deal with 'Class by converting the name to its _XXX form
20575 if Class_Present (Item) then
20576 if Item_Nam = Name_Invariant then
20577 Item_Nam := Name_uInvariant;
20579 elsif Item_Nam = Name_Post then
20580 Item_Nam := Name_uPost;
20582 elsif Item_Nam = Name_Pre then
20583 Item_Nam := Name_uPre;
20585 elsif Nam_In (Item_Nam, Name_Type_Invariant,
20586 Name_Type_Invariant_Class)
20587 then
20588 Item_Nam := Name_uType_Invariant;
20590 -- Nothing to do for other cases (e.g. a Check that derived from
20591 -- Pre_Class and has the flag set). Also we do nothing if the name
20592 -- is already in special _xxx form.
20594 end if;
20595 end if;
20597 return Item_Nam;
20598 end Original_Aspect_Pragma_Name;
20600 --------------------------------------
20601 -- Original_Corresponding_Operation --
20602 --------------------------------------
20604 function Original_Corresponding_Operation (S : Entity_Id) return Entity_Id
20606 Typ : constant Entity_Id := Find_Dispatching_Type (S);
20608 begin
20609 -- If S is an inherited primitive S2 the original corresponding
20610 -- operation of S is the original corresponding operation of S2
20612 if Present (Alias (S))
20613 and then Find_Dispatching_Type (Alias (S)) /= Typ
20614 then
20615 return Original_Corresponding_Operation (Alias (S));
20617 -- If S overrides an inherited subprogram S2 the original corresponding
20618 -- operation of S is the original corresponding operation of S2
20620 elsif Present (Overridden_Operation (S)) then
20621 return Original_Corresponding_Operation (Overridden_Operation (S));
20623 -- otherwise it is S itself
20625 else
20626 return S;
20627 end if;
20628 end Original_Corresponding_Operation;
20630 -------------------
20631 -- Output_Entity --
20632 -------------------
20634 procedure Output_Entity (Id : Entity_Id) is
20635 Scop : Entity_Id;
20637 begin
20638 Scop := Scope (Id);
20640 -- The entity may lack a scope when it is in the process of being
20641 -- analyzed. Use the current scope as an approximation.
20643 if No (Scop) then
20644 Scop := Current_Scope;
20645 end if;
20647 Output_Name (Chars (Id), Scop);
20648 end Output_Entity;
20650 -----------------
20651 -- Output_Name --
20652 -----------------
20654 procedure Output_Name (Nam : Name_Id; Scop : Entity_Id := Current_Scope) is
20655 begin
20656 Write_Str
20657 (Get_Name_String
20658 (Get_Qualified_Name
20659 (Nam => Nam,
20660 Suffix => No_Name,
20661 Scop => Scop)));
20662 Write_Eol;
20663 end Output_Name;
20665 ----------------------
20666 -- Policy_In_Effect --
20667 ----------------------
20669 function Policy_In_Effect (Policy : Name_Id) return Name_Id is
20670 function Policy_In_List (List : Node_Id) return Name_Id;
20671 -- Determine the mode of a policy in a N_Pragma list
20673 --------------------
20674 -- Policy_In_List --
20675 --------------------
20677 function Policy_In_List (List : Node_Id) return Name_Id is
20678 Arg1 : Node_Id;
20679 Arg2 : Node_Id;
20680 Prag : Node_Id;
20682 begin
20683 Prag := List;
20684 while Present (Prag) loop
20685 Arg1 := First (Pragma_Argument_Associations (Prag));
20686 Arg2 := Next (Arg1);
20688 Arg1 := Get_Pragma_Arg (Arg1);
20689 Arg2 := Get_Pragma_Arg (Arg2);
20691 -- The current Check_Policy pragma matches the requested policy or
20692 -- appears in the single argument form (Assertion, policy_id).
20694 if Nam_In (Chars (Arg1), Name_Assertion, Policy) then
20695 return Chars (Arg2);
20696 end if;
20698 Prag := Next_Pragma (Prag);
20699 end loop;
20701 return No_Name;
20702 end Policy_In_List;
20704 -- Local variables
20706 Kind : Name_Id;
20708 -- Start of processing for Policy_In_Effect
20710 begin
20711 if not Is_Valid_Assertion_Kind (Policy) then
20712 raise Program_Error;
20713 end if;
20715 -- Inspect all policy pragmas that appear within scopes (if any)
20717 Kind := Policy_In_List (Check_Policy_List);
20719 -- Inspect all configuration policy pragmas (if any)
20721 if Kind = No_Name then
20722 Kind := Policy_In_List (Check_Policy_List_Config);
20723 end if;
20725 -- The context lacks policy pragmas, determine the mode based on whether
20726 -- assertions are enabled at the configuration level. This ensures that
20727 -- the policy is preserved when analyzing generics.
20729 if Kind = No_Name then
20730 if Assertions_Enabled_Config then
20731 Kind := Name_Check;
20732 else
20733 Kind := Name_Ignore;
20734 end if;
20735 end if;
20737 return Kind;
20738 end Policy_In_Effect;
20740 ----------------------------------
20741 -- Predicate_Tests_On_Arguments --
20742 ----------------------------------
20744 function Predicate_Tests_On_Arguments (Subp : Entity_Id) return Boolean is
20745 begin
20746 -- Always test predicates on indirect call
20748 if Ekind (Subp) = E_Subprogram_Type then
20749 return True;
20751 -- Do not test predicates on call to generated default Finalize, since
20752 -- we are not interested in whether something we are finalizing (and
20753 -- typically destroying) satisfies its predicates.
20755 elsif Chars (Subp) = Name_Finalize
20756 and then not Comes_From_Source (Subp)
20757 then
20758 return False;
20760 -- Do not test predicates on any internally generated routines
20762 elsif Is_Internal_Name (Chars (Subp)) then
20763 return False;
20765 -- Do not test predicates on call to Init_Proc, since if needed the
20766 -- predicate test will occur at some other point.
20768 elsif Is_Init_Proc (Subp) then
20769 return False;
20771 -- Do not test predicates on call to predicate function, since this
20772 -- would cause infinite recursion.
20774 elsif Ekind (Subp) = E_Function
20775 and then (Is_Predicate_Function (Subp)
20776 or else
20777 Is_Predicate_Function_M (Subp))
20778 then
20779 return False;
20781 -- For now, no other exceptions
20783 else
20784 return True;
20785 end if;
20786 end Predicate_Tests_On_Arguments;
20788 -----------------------
20789 -- Private_Component --
20790 -----------------------
20792 function Private_Component (Type_Id : Entity_Id) return Entity_Id is
20793 Ancestor : constant Entity_Id := Base_Type (Type_Id);
20795 function Trace_Components
20796 (T : Entity_Id;
20797 Check : Boolean) return Entity_Id;
20798 -- Recursive function that does the work, and checks against circular
20799 -- definition for each subcomponent type.
20801 ----------------------
20802 -- Trace_Components --
20803 ----------------------
20805 function Trace_Components
20806 (T : Entity_Id;
20807 Check : Boolean) return Entity_Id
20809 Btype : constant Entity_Id := Base_Type (T);
20810 Component : Entity_Id;
20811 P : Entity_Id;
20812 Candidate : Entity_Id := Empty;
20814 begin
20815 if Check and then Btype = Ancestor then
20816 Error_Msg_N ("circular type definition", Type_Id);
20817 return Any_Type;
20818 end if;
20820 if Is_Private_Type (Btype) and then not Is_Generic_Type (Btype) then
20821 if Present (Full_View (Btype))
20822 and then Is_Record_Type (Full_View (Btype))
20823 and then not Is_Frozen (Btype)
20824 then
20825 -- To indicate that the ancestor depends on a private type, the
20826 -- current Btype is sufficient. However, to check for circular
20827 -- definition we must recurse on the full view.
20829 Candidate := Trace_Components (Full_View (Btype), True);
20831 if Candidate = Any_Type then
20832 return Any_Type;
20833 else
20834 return Btype;
20835 end if;
20837 else
20838 return Btype;
20839 end if;
20841 elsif Is_Array_Type (Btype) then
20842 return Trace_Components (Component_Type (Btype), True);
20844 elsif Is_Record_Type (Btype) then
20845 Component := First_Entity (Btype);
20846 while Present (Component)
20847 and then Comes_From_Source (Component)
20848 loop
20849 -- Skip anonymous types generated by constrained components
20851 if not Is_Type (Component) then
20852 P := Trace_Components (Etype (Component), True);
20854 if Present (P) then
20855 if P = Any_Type then
20856 return P;
20857 else
20858 Candidate := P;
20859 end if;
20860 end if;
20861 end if;
20863 Next_Entity (Component);
20864 end loop;
20866 return Candidate;
20868 else
20869 return Empty;
20870 end if;
20871 end Trace_Components;
20873 -- Start of processing for Private_Component
20875 begin
20876 return Trace_Components (Type_Id, False);
20877 end Private_Component;
20879 ---------------------------
20880 -- Primitive_Names_Match --
20881 ---------------------------
20883 function Primitive_Names_Match (E1, E2 : Entity_Id) return Boolean is
20884 function Non_Internal_Name (E : Entity_Id) return Name_Id;
20885 -- Given an internal name, returns the corresponding non-internal name
20887 ------------------------
20888 -- Non_Internal_Name --
20889 ------------------------
20891 function Non_Internal_Name (E : Entity_Id) return Name_Id is
20892 begin
20893 Get_Name_String (Chars (E));
20894 Name_Len := Name_Len - 1;
20895 return Name_Find;
20896 end Non_Internal_Name;
20898 -- Start of processing for Primitive_Names_Match
20900 begin
20901 pragma Assert (Present (E1) and then Present (E2));
20903 return Chars (E1) = Chars (E2)
20904 or else
20905 (not Is_Internal_Name (Chars (E1))
20906 and then Is_Internal_Name (Chars (E2))
20907 and then Non_Internal_Name (E2) = Chars (E1))
20908 or else
20909 (not Is_Internal_Name (Chars (E2))
20910 and then Is_Internal_Name (Chars (E1))
20911 and then Non_Internal_Name (E1) = Chars (E2))
20912 or else
20913 (Is_Predefined_Dispatching_Operation (E1)
20914 and then Is_Predefined_Dispatching_Operation (E2)
20915 and then Same_TSS (E1, E2))
20916 or else
20917 (Is_Init_Proc (E1) and then Is_Init_Proc (E2));
20918 end Primitive_Names_Match;
20920 -----------------------
20921 -- Process_End_Label --
20922 -----------------------
20924 procedure Process_End_Label
20925 (N : Node_Id;
20926 Typ : Character;
20927 Ent : Entity_Id)
20929 Loc : Source_Ptr;
20930 Nam : Node_Id;
20931 Scop : Entity_Id;
20933 Label_Ref : Boolean;
20934 -- Set True if reference to end label itself is required
20936 Endl : Node_Id;
20937 -- Gets set to the operator symbol or identifier that references the
20938 -- entity Ent. For the child unit case, this is the identifier from the
20939 -- designator. For other cases, this is simply Endl.
20941 procedure Generate_Parent_Ref (N : Node_Id; E : Entity_Id);
20942 -- N is an identifier node that appears as a parent unit reference in
20943 -- the case where Ent is a child unit. This procedure generates an
20944 -- appropriate cross-reference entry. E is the corresponding entity.
20946 -------------------------
20947 -- Generate_Parent_Ref --
20948 -------------------------
20950 procedure Generate_Parent_Ref (N : Node_Id; E : Entity_Id) is
20951 begin
20952 -- If names do not match, something weird, skip reference
20954 if Chars (E) = Chars (N) then
20956 -- Generate the reference. We do NOT consider this as a reference
20957 -- for unreferenced symbol purposes.
20959 Generate_Reference (E, N, 'r', Set_Ref => False, Force => True);
20961 if Style_Check then
20962 Style.Check_Identifier (N, E);
20963 end if;
20964 end if;
20965 end Generate_Parent_Ref;
20967 -- Start of processing for Process_End_Label
20969 begin
20970 -- If no node, ignore. This happens in some error situations, and
20971 -- also for some internally generated structures where no end label
20972 -- references are required in any case.
20974 if No (N) then
20975 return;
20976 end if;
20978 -- Nothing to do if no End_Label, happens for internally generated
20979 -- constructs where we don't want an end label reference anyway. Also
20980 -- nothing to do if Endl is a string literal, which means there was
20981 -- some prior error (bad operator symbol)
20983 Endl := End_Label (N);
20985 if No (Endl) or else Nkind (Endl) = N_String_Literal then
20986 return;
20987 end if;
20989 -- Reference node is not in extended main source unit
20991 if not In_Extended_Main_Source_Unit (N) then
20993 -- Generally we do not collect references except for the extended
20994 -- main source unit. The one exception is the 'e' entry for a
20995 -- package spec, where it is useful for a client to have the
20996 -- ending information to define scopes.
20998 if Typ /= 'e' then
20999 return;
21001 else
21002 Label_Ref := False;
21004 -- For this case, we can ignore any parent references, but we
21005 -- need the package name itself for the 'e' entry.
21007 if Nkind (Endl) = N_Designator then
21008 Endl := Identifier (Endl);
21009 end if;
21010 end if;
21012 -- Reference is in extended main source unit
21014 else
21015 Label_Ref := True;
21017 -- For designator, generate references for the parent entries
21019 if Nkind (Endl) = N_Designator then
21021 -- Generate references for the prefix if the END line comes from
21022 -- source (otherwise we do not need these references) We climb the
21023 -- scope stack to find the expected entities.
21025 if Comes_From_Source (Endl) then
21026 Nam := Name (Endl);
21027 Scop := Current_Scope;
21028 while Nkind (Nam) = N_Selected_Component loop
21029 Scop := Scope (Scop);
21030 exit when No (Scop);
21031 Generate_Parent_Ref (Selector_Name (Nam), Scop);
21032 Nam := Prefix (Nam);
21033 end loop;
21035 if Present (Scop) then
21036 Generate_Parent_Ref (Nam, Scope (Scop));
21037 end if;
21038 end if;
21040 Endl := Identifier (Endl);
21041 end if;
21042 end if;
21044 -- If the end label is not for the given entity, then either we have
21045 -- some previous error, or this is a generic instantiation for which
21046 -- we do not need to make a cross-reference in this case anyway. In
21047 -- either case we simply ignore the call.
21049 if Chars (Ent) /= Chars (Endl) then
21050 return;
21051 end if;
21053 -- If label was really there, then generate a normal reference and then
21054 -- adjust the location in the end label to point past the name (which
21055 -- should almost always be the semicolon).
21057 Loc := Sloc (Endl);
21059 if Comes_From_Source (Endl) then
21061 -- If a label reference is required, then do the style check and
21062 -- generate an l-type cross-reference entry for the label
21064 if Label_Ref then
21065 if Style_Check then
21066 Style.Check_Identifier (Endl, Ent);
21067 end if;
21069 Generate_Reference (Ent, Endl, 'l', Set_Ref => False);
21070 end if;
21072 -- Set the location to point past the label (normally this will
21073 -- mean the semicolon immediately following the label). This is
21074 -- done for the sake of the 'e' or 't' entry generated below.
21076 Get_Decoded_Name_String (Chars (Endl));
21077 Set_Sloc (Endl, Sloc (Endl) + Source_Ptr (Name_Len));
21079 else
21080 -- In SPARK mode, no missing label is allowed for packages and
21081 -- subprogram bodies. Detect those cases by testing whether
21082 -- Process_End_Label was called for a body (Typ = 't') or a package.
21084 if Restriction_Check_Required (SPARK_05)
21085 and then (Typ = 't' or else Ekind (Ent) = E_Package)
21086 then
21087 Error_Msg_Node_1 := Endl;
21088 Check_SPARK_05_Restriction
21089 ("`END &` required", Endl, Force => True);
21090 end if;
21091 end if;
21093 -- Now generate the e/t reference
21095 Generate_Reference (Ent, Endl, Typ, Set_Ref => False, Force => True);
21097 -- Restore Sloc, in case modified above, since we have an identifier
21098 -- and the normal Sloc should be left set in the tree.
21100 Set_Sloc (Endl, Loc);
21101 end Process_End_Label;
21103 --------------------------------
21104 -- Propagate_Concurrent_Flags --
21105 --------------------------------
21107 procedure Propagate_Concurrent_Flags
21108 (Typ : Entity_Id;
21109 Comp_Typ : Entity_Id)
21111 begin
21112 if Has_Task (Comp_Typ) then
21113 Set_Has_Task (Typ);
21114 end if;
21116 if Has_Protected (Comp_Typ) then
21117 Set_Has_Protected (Typ);
21118 end if;
21120 if Has_Timing_Event (Comp_Typ) then
21121 Set_Has_Timing_Event (Typ);
21122 end if;
21123 end Propagate_Concurrent_Flags;
21125 ------------------------------
21126 -- Propagate_DIC_Attributes --
21127 ------------------------------
21129 procedure Propagate_DIC_Attributes
21130 (Typ : Entity_Id;
21131 From_Typ : Entity_Id)
21133 DIC_Proc : Entity_Id;
21135 begin
21136 if Present (Typ) and then Present (From_Typ) then
21137 pragma Assert (Is_Type (Typ) and then Is_Type (From_Typ));
21139 -- Nothing to do if both the source and the destination denote the
21140 -- same type.
21142 if From_Typ = Typ then
21143 return;
21144 end if;
21146 DIC_Proc := DIC_Procedure (From_Typ);
21148 -- The setting of the attributes is intentionally conservative. This
21149 -- prevents accidental clobbering of enabled attributes.
21151 if Has_Inherited_DIC (From_Typ)
21152 and then not Has_Inherited_DIC (Typ)
21153 then
21154 Set_Has_Inherited_DIC (Typ);
21155 end if;
21157 if Has_Own_DIC (From_Typ) and then not Has_Own_DIC (Typ) then
21158 Set_Has_Own_DIC (Typ);
21159 end if;
21161 if Present (DIC_Proc) and then No (DIC_Procedure (Typ)) then
21162 Set_DIC_Procedure (Typ, DIC_Proc);
21163 end if;
21164 end if;
21165 end Propagate_DIC_Attributes;
21167 ------------------------------------
21168 -- Propagate_Invariant_Attributes --
21169 ------------------------------------
21171 procedure Propagate_Invariant_Attributes
21172 (Typ : Entity_Id;
21173 From_Typ : Entity_Id)
21175 Full_IP : Entity_Id;
21176 Part_IP : Entity_Id;
21178 begin
21179 if Present (Typ) and then Present (From_Typ) then
21180 pragma Assert (Is_Type (Typ) and then Is_Type (From_Typ));
21182 -- Nothing to do if both the source and the destination denote the
21183 -- same type.
21185 if From_Typ = Typ then
21186 return;
21187 end if;
21189 Full_IP := Invariant_Procedure (From_Typ);
21190 Part_IP := Partial_Invariant_Procedure (From_Typ);
21192 -- The setting of the attributes is intentionally conservative. This
21193 -- prevents accidental clobbering of enabled attributes.
21195 if Has_Inheritable_Invariants (From_Typ)
21196 and then not Has_Inheritable_Invariants (Typ)
21197 then
21198 Set_Has_Inheritable_Invariants (Typ, True);
21199 end if;
21201 if Has_Inherited_Invariants (From_Typ)
21202 and then not Has_Inherited_Invariants (Typ)
21203 then
21204 Set_Has_Inherited_Invariants (Typ, True);
21205 end if;
21207 if Has_Own_Invariants (From_Typ)
21208 and then not Has_Own_Invariants (Typ)
21209 then
21210 Set_Has_Own_Invariants (Typ, True);
21211 end if;
21213 if Present (Full_IP) and then No (Invariant_Procedure (Typ)) then
21214 Set_Invariant_Procedure (Typ, Full_IP);
21215 end if;
21217 if Present (Part_IP) and then No (Partial_Invariant_Procedure (Typ))
21218 then
21219 Set_Partial_Invariant_Procedure (Typ, Part_IP);
21220 end if;
21221 end if;
21222 end Propagate_Invariant_Attributes;
21224 ---------------------------------------
21225 -- Record_Possible_Part_Of_Reference --
21226 ---------------------------------------
21228 procedure Record_Possible_Part_Of_Reference
21229 (Var_Id : Entity_Id;
21230 Ref : Node_Id)
21232 Encap : constant Entity_Id := Encapsulating_State (Var_Id);
21233 Refs : Elist_Id;
21235 begin
21236 -- The variable is a constituent of a single protected/task type. Such
21237 -- a variable acts as a component of the type and must appear within a
21238 -- specific region (SPARK RM 9.3). Instead of recording the reference,
21239 -- verify its legality now.
21241 if Present (Encap) and then Is_Single_Concurrent_Object (Encap) then
21242 Check_Part_Of_Reference (Var_Id, Ref);
21244 -- The variable is subject to pragma Part_Of and may eventually become a
21245 -- constituent of a single protected/task type. Record the reference to
21246 -- verify its placement when the contract of the variable is analyzed.
21248 elsif Present (Get_Pragma (Var_Id, Pragma_Part_Of)) then
21249 Refs := Part_Of_References (Var_Id);
21251 if No (Refs) then
21252 Refs := New_Elmt_List;
21253 Set_Part_Of_References (Var_Id, Refs);
21254 end if;
21256 Append_Elmt (Ref, Refs);
21257 end if;
21258 end Record_Possible_Part_Of_Reference;
21260 ----------------
21261 -- Referenced --
21262 ----------------
21264 function Referenced (Id : Entity_Id; Expr : Node_Id) return Boolean is
21265 Seen : Boolean := False;
21267 function Is_Reference (N : Node_Id) return Traverse_Result;
21268 -- Determine whether node N denotes a reference to Id. If this is the
21269 -- case, set global flag Seen to True and stop the traversal.
21271 ------------------
21272 -- Is_Reference --
21273 ------------------
21275 function Is_Reference (N : Node_Id) return Traverse_Result is
21276 begin
21277 if Is_Entity_Name (N)
21278 and then Present (Entity (N))
21279 and then Entity (N) = Id
21280 then
21281 Seen := True;
21282 return Abandon;
21283 else
21284 return OK;
21285 end if;
21286 end Is_Reference;
21288 procedure Inspect_Expression is new Traverse_Proc (Is_Reference);
21290 -- Start of processing for Referenced
21292 begin
21293 Inspect_Expression (Expr);
21294 return Seen;
21295 end Referenced;
21297 ------------------------------------
21298 -- References_Generic_Formal_Type --
21299 ------------------------------------
21301 function References_Generic_Formal_Type (N : Node_Id) return Boolean is
21303 function Process (N : Node_Id) return Traverse_Result;
21304 -- Process one node in search for generic formal type
21306 -------------
21307 -- Process --
21308 -------------
21310 function Process (N : Node_Id) return Traverse_Result is
21311 begin
21312 if Nkind (N) in N_Has_Entity then
21313 declare
21314 E : constant Entity_Id := Entity (N);
21315 begin
21316 if Present (E) then
21317 if Is_Generic_Type (E) then
21318 return Abandon;
21319 elsif Present (Etype (E))
21320 and then Is_Generic_Type (Etype (E))
21321 then
21322 return Abandon;
21323 end if;
21324 end if;
21325 end;
21326 end if;
21328 return Atree.OK;
21329 end Process;
21331 function Traverse is new Traverse_Func (Process);
21332 -- Traverse tree to look for generic type
21334 begin
21335 if Inside_A_Generic then
21336 return Traverse (N) = Abandon;
21337 else
21338 return False;
21339 end if;
21340 end References_Generic_Formal_Type;
21342 -------------------
21343 -- Remove_Entity --
21344 -------------------
21346 procedure Remove_Entity (Id : Entity_Id) is
21347 Scop : constant Entity_Id := Scope (Id);
21348 Prev_Id : Entity_Id;
21350 begin
21351 -- Remove the entity from the homonym chain. When the entity is the
21352 -- head of the chain, associate the entry in the name table with its
21353 -- homonym effectively making it the new head of the chain.
21355 if Current_Entity (Id) = Id then
21356 Set_Name_Entity_Id (Chars (Id), Homonym (Id));
21358 -- Otherwise link the previous and next homonyms
21360 else
21361 Prev_Id := Current_Entity (Id);
21362 while Present (Prev_Id) and then Homonym (Prev_Id) /= Id loop
21363 Prev_Id := Homonym (Prev_Id);
21364 end loop;
21366 Set_Homonym (Prev_Id, Homonym (Id));
21367 end if;
21369 -- Remove the entity from the scope entity chain. When the entity is
21370 -- the head of the chain, set the next entity as the new head of the
21371 -- chain.
21373 if First_Entity (Scop) = Id then
21374 Prev_Id := Empty;
21375 Set_First_Entity (Scop, Next_Entity (Id));
21377 -- Otherwise the entity is either in the middle of the chain or it acts
21378 -- as its tail. Traverse and link the previous and next entities.
21380 else
21381 Prev_Id := First_Entity (Scop);
21382 while Present (Prev_Id) and then Next_Entity (Prev_Id) /= Id loop
21383 Next_Entity (Prev_Id);
21384 end loop;
21386 Set_Next_Entity (Prev_Id, Next_Entity (Id));
21387 end if;
21389 -- Handle the case where the entity acts as the tail of the scope entity
21390 -- chain.
21392 if Last_Entity (Scop) = Id then
21393 Set_Last_Entity (Scop, Prev_Id);
21394 end if;
21395 end Remove_Entity;
21397 --------------------
21398 -- Remove_Homonym --
21399 --------------------
21401 procedure Remove_Homonym (E : Entity_Id) is
21402 Prev : Entity_Id := Empty;
21403 H : Entity_Id;
21405 begin
21406 if E = Current_Entity (E) then
21407 if Present (Homonym (E)) then
21408 Set_Current_Entity (Homonym (E));
21409 else
21410 Set_Name_Entity_Id (Chars (E), Empty);
21411 end if;
21413 else
21414 H := Current_Entity (E);
21415 while Present (H) and then H /= E loop
21416 Prev := H;
21417 H := Homonym (H);
21418 end loop;
21420 -- If E is not on the homonym chain, nothing to do
21422 if Present (H) then
21423 Set_Homonym (Prev, Homonym (E));
21424 end if;
21425 end if;
21426 end Remove_Homonym;
21428 ------------------------------
21429 -- Remove_Overloaded_Entity --
21430 ------------------------------
21432 procedure Remove_Overloaded_Entity (Id : Entity_Id) is
21433 procedure Remove_Primitive_Of (Typ : Entity_Id);
21434 -- Remove primitive subprogram Id from the list of primitives that
21435 -- belong to type Typ.
21437 -------------------------
21438 -- Remove_Primitive_Of --
21439 -------------------------
21441 procedure Remove_Primitive_Of (Typ : Entity_Id) is
21442 Prims : Elist_Id;
21444 begin
21445 if Is_Tagged_Type (Typ) then
21446 Prims := Direct_Primitive_Operations (Typ);
21448 if Present (Prims) then
21449 Remove (Prims, Id);
21450 end if;
21451 end if;
21452 end Remove_Primitive_Of;
21454 -- Local variables
21456 Formal : Entity_Id;
21458 -- Start of processing for Remove_Overloaded_Entity
21460 begin
21461 -- Remove the entity from both the homonym and scope chains
21463 Remove_Entity (Id);
21465 -- The entity denotes a primitive subprogram. Remove it from the list of
21466 -- primitives of the associated controlling type.
21468 if Ekind_In (Id, E_Function, E_Procedure) and then Is_Primitive (Id) then
21469 Formal := First_Formal (Id);
21470 while Present (Formal) loop
21471 if Is_Controlling_Formal (Formal) then
21472 Remove_Primitive_Of (Etype (Formal));
21473 exit;
21474 end if;
21476 Next_Formal (Formal);
21477 end loop;
21479 if Ekind (Id) = E_Function and then Has_Controlling_Result (Id) then
21480 Remove_Primitive_Of (Etype (Id));
21481 end if;
21482 end if;
21483 end Remove_Overloaded_Entity;
21485 ---------------------
21486 -- Rep_To_Pos_Flag --
21487 ---------------------
21489 function Rep_To_Pos_Flag (E : Entity_Id; Loc : Source_Ptr) return Node_Id is
21490 begin
21491 return New_Occurrence_Of
21492 (Boolean_Literals (not Range_Checks_Suppressed (E)), Loc);
21493 end Rep_To_Pos_Flag;
21495 --------------------
21496 -- Require_Entity --
21497 --------------------
21499 procedure Require_Entity (N : Node_Id) is
21500 begin
21501 if Is_Entity_Name (N) and then No (Entity (N)) then
21502 if Total_Errors_Detected /= 0 then
21503 Set_Entity (N, Any_Id);
21504 else
21505 raise Program_Error;
21506 end if;
21507 end if;
21508 end Require_Entity;
21510 ------------------------------
21511 -- Requires_Transient_Scope --
21512 ------------------------------
21514 -- A transient scope is required when variable-sized temporaries are
21515 -- allocated on the secondary stack, or when finalization actions must be
21516 -- generated before the next instruction.
21518 function Requires_Transient_Scope (Id : Entity_Id) return Boolean is
21519 Old_Result : constant Boolean := Old_Requires_Transient_Scope (Id);
21521 begin
21522 if Debug_Flag_QQ then
21523 return Old_Result;
21524 end if;
21526 declare
21527 New_Result : constant Boolean := New_Requires_Transient_Scope (Id);
21529 begin
21530 -- Assert that we're not putting things on the secondary stack if we
21531 -- didn't before; we are trying to AVOID secondary stack when
21532 -- possible.
21534 if not Old_Result then
21535 pragma Assert (not New_Result);
21536 null;
21537 end if;
21539 if New_Result /= Old_Result then
21540 Results_Differ (Id, Old_Result, New_Result);
21541 end if;
21543 return New_Result;
21544 end;
21545 end Requires_Transient_Scope;
21547 --------------------
21548 -- Results_Differ --
21549 --------------------
21551 procedure Results_Differ
21552 (Id : Entity_Id;
21553 Old_Val : Boolean;
21554 New_Val : Boolean)
21556 begin
21557 if False then -- False to disable; True for debugging
21558 Treepr.Print_Tree_Node (Id);
21560 if Old_Val = New_Val then
21561 raise Program_Error;
21562 end if;
21563 end if;
21564 end Results_Differ;
21566 --------------------------
21567 -- Reset_Analyzed_Flags --
21568 --------------------------
21570 procedure Reset_Analyzed_Flags (N : Node_Id) is
21571 function Clear_Analyzed (N : Node_Id) return Traverse_Result;
21572 -- Function used to reset Analyzed flags in tree. Note that we do
21573 -- not reset Analyzed flags in entities, since there is no need to
21574 -- reanalyze entities, and indeed, it is wrong to do so, since it
21575 -- can result in generating auxiliary stuff more than once.
21577 --------------------
21578 -- Clear_Analyzed --
21579 --------------------
21581 function Clear_Analyzed (N : Node_Id) return Traverse_Result is
21582 begin
21583 if Nkind (N) not in N_Entity then
21584 Set_Analyzed (N, False);
21585 end if;
21587 return OK;
21588 end Clear_Analyzed;
21590 procedure Reset_Analyzed is new Traverse_Proc (Clear_Analyzed);
21592 -- Start of processing for Reset_Analyzed_Flags
21594 begin
21595 Reset_Analyzed (N);
21596 end Reset_Analyzed_Flags;
21598 ------------------------
21599 -- Restore_SPARK_Mode --
21600 ------------------------
21602 procedure Restore_SPARK_Mode
21603 (Mode : SPARK_Mode_Type;
21604 Prag : Node_Id)
21606 begin
21607 SPARK_Mode := Mode;
21608 SPARK_Mode_Pragma := Prag;
21609 end Restore_SPARK_Mode;
21611 --------------------------------
21612 -- Returns_Unconstrained_Type --
21613 --------------------------------
21615 function Returns_Unconstrained_Type (Subp : Entity_Id) return Boolean is
21616 begin
21617 return Ekind (Subp) = E_Function
21618 and then not Is_Scalar_Type (Etype (Subp))
21619 and then not Is_Access_Type (Etype (Subp))
21620 and then not Is_Constrained (Etype (Subp));
21621 end Returns_Unconstrained_Type;
21623 ----------------------------
21624 -- Root_Type_Of_Full_View --
21625 ----------------------------
21627 function Root_Type_Of_Full_View (T : Entity_Id) return Entity_Id is
21628 Rtyp : constant Entity_Id := Root_Type (T);
21630 begin
21631 -- The root type of the full view may itself be a private type. Keep
21632 -- looking for the ultimate derivation parent.
21634 if Is_Private_Type (Rtyp) and then Present (Full_View (Rtyp)) then
21635 return Root_Type_Of_Full_View (Full_View (Rtyp));
21636 else
21637 return Rtyp;
21638 end if;
21639 end Root_Type_Of_Full_View;
21641 ---------------------------
21642 -- Safe_To_Capture_Value --
21643 ---------------------------
21645 function Safe_To_Capture_Value
21646 (N : Node_Id;
21647 Ent : Entity_Id;
21648 Cond : Boolean := False) return Boolean
21650 begin
21651 -- The only entities for which we track constant values are variables
21652 -- which are not renamings, constants, out parameters, and in out
21653 -- parameters, so check if we have this case.
21655 -- Note: it may seem odd to track constant values for constants, but in
21656 -- fact this routine is used for other purposes than simply capturing
21657 -- the value. In particular, the setting of Known[_Non]_Null.
21659 if (Ekind (Ent) = E_Variable and then No (Renamed_Object (Ent)))
21660 or else
21661 Ekind_In (Ent, E_Constant, E_Out_Parameter, E_In_Out_Parameter)
21662 then
21663 null;
21665 -- For conditionals, we also allow loop parameters and all formals,
21666 -- including in parameters.
21668 elsif Cond and then Ekind_In (Ent, E_Loop_Parameter, E_In_Parameter) then
21669 null;
21671 -- For all other cases, not just unsafe, but impossible to capture
21672 -- Current_Value, since the above are the only entities which have
21673 -- Current_Value fields.
21675 else
21676 return False;
21677 end if;
21679 -- Skip if volatile or aliased, since funny things might be going on in
21680 -- these cases which we cannot necessarily track. Also skip any variable
21681 -- for which an address clause is given, or whose address is taken. Also
21682 -- never capture value of library level variables (an attempt to do so
21683 -- can occur in the case of package elaboration code).
21685 if Treat_As_Volatile (Ent)
21686 or else Is_Aliased (Ent)
21687 or else Present (Address_Clause (Ent))
21688 or else Address_Taken (Ent)
21689 or else (Is_Library_Level_Entity (Ent)
21690 and then Ekind (Ent) = E_Variable)
21691 then
21692 return False;
21693 end if;
21695 -- OK, all above conditions are met. We also require that the scope of
21696 -- the reference be the same as the scope of the entity, not counting
21697 -- packages and blocks and loops.
21699 declare
21700 E_Scope : constant Entity_Id := Scope (Ent);
21701 R_Scope : Entity_Id;
21703 begin
21704 R_Scope := Current_Scope;
21705 while R_Scope /= Standard_Standard loop
21706 exit when R_Scope = E_Scope;
21708 if not Ekind_In (R_Scope, E_Package, E_Block, E_Loop) then
21709 return False;
21710 else
21711 R_Scope := Scope (R_Scope);
21712 end if;
21713 end loop;
21714 end;
21716 -- We also require that the reference does not appear in a context
21717 -- where it is not sure to be executed (i.e. a conditional context
21718 -- or an exception handler). We skip this if Cond is True, since the
21719 -- capturing of values from conditional tests handles this ok.
21721 if Cond then
21722 return True;
21723 end if;
21725 declare
21726 Desc : Node_Id;
21727 P : Node_Id;
21729 begin
21730 Desc := N;
21732 -- Seems dubious that case expressions are not handled here ???
21734 P := Parent (N);
21735 while Present (P) loop
21736 if Nkind (P) = N_If_Statement
21737 or else Nkind (P) = N_Case_Statement
21738 or else (Nkind (P) in N_Short_Circuit
21739 and then Desc = Right_Opnd (P))
21740 or else (Nkind (P) = N_If_Expression
21741 and then Desc /= First (Expressions (P)))
21742 or else Nkind (P) = N_Exception_Handler
21743 or else Nkind (P) = N_Selective_Accept
21744 or else Nkind (P) = N_Conditional_Entry_Call
21745 or else Nkind (P) = N_Timed_Entry_Call
21746 or else Nkind (P) = N_Asynchronous_Select
21747 then
21748 return False;
21750 else
21751 Desc := P;
21752 P := Parent (P);
21754 -- A special Ada 2012 case: the original node may be part
21755 -- of the else_actions of a conditional expression, in which
21756 -- case it might not have been expanded yet, and appears in
21757 -- a non-syntactic list of actions. In that case it is clearly
21758 -- not safe to save a value.
21760 if No (P)
21761 and then Is_List_Member (Desc)
21762 and then No (Parent (List_Containing (Desc)))
21763 then
21764 return False;
21765 end if;
21766 end if;
21767 end loop;
21768 end;
21770 -- OK, looks safe to set value
21772 return True;
21773 end Safe_To_Capture_Value;
21775 ---------------
21776 -- Same_Name --
21777 ---------------
21779 function Same_Name (N1, N2 : Node_Id) return Boolean is
21780 K1 : constant Node_Kind := Nkind (N1);
21781 K2 : constant Node_Kind := Nkind (N2);
21783 begin
21784 if (K1 = N_Identifier or else K1 = N_Defining_Identifier)
21785 and then (K2 = N_Identifier or else K2 = N_Defining_Identifier)
21786 then
21787 return Chars (N1) = Chars (N2);
21789 elsif (K1 = N_Selected_Component or else K1 = N_Expanded_Name)
21790 and then (K2 = N_Selected_Component or else K2 = N_Expanded_Name)
21791 then
21792 return Same_Name (Selector_Name (N1), Selector_Name (N2))
21793 and then Same_Name (Prefix (N1), Prefix (N2));
21795 else
21796 return False;
21797 end if;
21798 end Same_Name;
21800 -----------------
21801 -- Same_Object --
21802 -----------------
21804 function Same_Object (Node1, Node2 : Node_Id) return Boolean is
21805 N1 : constant Node_Id := Original_Node (Node1);
21806 N2 : constant Node_Id := Original_Node (Node2);
21807 -- We do the tests on original nodes, since we are most interested
21808 -- in the original source, not any expansion that got in the way.
21810 K1 : constant Node_Kind := Nkind (N1);
21811 K2 : constant Node_Kind := Nkind (N2);
21813 begin
21814 -- First case, both are entities with same entity
21816 if K1 in N_Has_Entity and then K2 in N_Has_Entity then
21817 declare
21818 EN1 : constant Entity_Id := Entity (N1);
21819 EN2 : constant Entity_Id := Entity (N2);
21820 begin
21821 if Present (EN1) and then Present (EN2)
21822 and then (Ekind_In (EN1, E_Variable, E_Constant)
21823 or else Is_Formal (EN1))
21824 and then EN1 = EN2
21825 then
21826 return True;
21827 end if;
21828 end;
21829 end if;
21831 -- Second case, selected component with same selector, same record
21833 if K1 = N_Selected_Component
21834 and then K2 = N_Selected_Component
21835 and then Chars (Selector_Name (N1)) = Chars (Selector_Name (N2))
21836 then
21837 return Same_Object (Prefix (N1), Prefix (N2));
21839 -- Third case, indexed component with same subscripts, same array
21841 elsif K1 = N_Indexed_Component
21842 and then K2 = N_Indexed_Component
21843 and then Same_Object (Prefix (N1), Prefix (N2))
21844 then
21845 declare
21846 E1, E2 : Node_Id;
21847 begin
21848 E1 := First (Expressions (N1));
21849 E2 := First (Expressions (N2));
21850 while Present (E1) loop
21851 if not Same_Value (E1, E2) then
21852 return False;
21853 else
21854 Next (E1);
21855 Next (E2);
21856 end if;
21857 end loop;
21859 return True;
21860 end;
21862 -- Fourth case, slice of same array with same bounds
21864 elsif K1 = N_Slice
21865 and then K2 = N_Slice
21866 and then Nkind (Discrete_Range (N1)) = N_Range
21867 and then Nkind (Discrete_Range (N2)) = N_Range
21868 and then Same_Value (Low_Bound (Discrete_Range (N1)),
21869 Low_Bound (Discrete_Range (N2)))
21870 and then Same_Value (High_Bound (Discrete_Range (N1)),
21871 High_Bound (Discrete_Range (N2)))
21872 then
21873 return Same_Name (Prefix (N1), Prefix (N2));
21875 -- All other cases, not clearly the same object
21877 else
21878 return False;
21879 end if;
21880 end Same_Object;
21882 ---------------
21883 -- Same_Type --
21884 ---------------
21886 function Same_Type (T1, T2 : Entity_Id) return Boolean is
21887 begin
21888 if T1 = T2 then
21889 return True;
21891 elsif not Is_Constrained (T1)
21892 and then not Is_Constrained (T2)
21893 and then Base_Type (T1) = Base_Type (T2)
21894 then
21895 return True;
21897 -- For now don't bother with case of identical constraints, to be
21898 -- fiddled with later on perhaps (this is only used for optimization
21899 -- purposes, so it is not critical to do a best possible job)
21901 else
21902 return False;
21903 end if;
21904 end Same_Type;
21906 ----------------
21907 -- Same_Value --
21908 ----------------
21910 function Same_Value (Node1, Node2 : Node_Id) return Boolean is
21911 begin
21912 if Compile_Time_Known_Value (Node1)
21913 and then Compile_Time_Known_Value (Node2)
21914 then
21915 -- Handle properly compile-time expressions that are not
21916 -- scalar.
21918 if Is_String_Type (Etype (Node1)) then
21919 return Expr_Value_S (Node1) = Expr_Value_S (Node2);
21921 else
21922 return Expr_Value (Node1) = Expr_Value (Node2);
21923 end if;
21925 elsif Same_Object (Node1, Node2) then
21926 return True;
21927 else
21928 return False;
21929 end if;
21930 end Same_Value;
21932 --------------------
21933 -- Set_SPARK_Mode --
21934 --------------------
21936 procedure Set_SPARK_Mode (Context : Entity_Id) is
21937 begin
21938 -- Do not consider illegal or partially decorated constructs
21940 if Ekind (Context) = E_Void or else Error_Posted (Context) then
21941 null;
21943 elsif Present (SPARK_Pragma (Context)) then
21944 Install_SPARK_Mode
21945 (Mode => Get_SPARK_Mode_From_Annotation (SPARK_Pragma (Context)),
21946 Prag => SPARK_Pragma (Context));
21947 end if;
21948 end Set_SPARK_Mode;
21950 -------------------------
21951 -- Scalar_Part_Present --
21952 -------------------------
21954 function Scalar_Part_Present (T : Entity_Id) return Boolean is
21955 C : Entity_Id;
21957 begin
21958 if Is_Scalar_Type (T) then
21959 return True;
21961 elsif Is_Array_Type (T) then
21962 return Scalar_Part_Present (Component_Type (T));
21964 elsif Is_Record_Type (T) or else Has_Discriminants (T) then
21965 C := First_Component_Or_Discriminant (T);
21966 while Present (C) loop
21967 if Scalar_Part_Present (Etype (C)) then
21968 return True;
21969 else
21970 Next_Component_Or_Discriminant (C);
21971 end if;
21972 end loop;
21973 end if;
21975 return False;
21976 end Scalar_Part_Present;
21978 ------------------------
21979 -- Scope_Is_Transient --
21980 ------------------------
21982 function Scope_Is_Transient return Boolean is
21983 begin
21984 return Scope_Stack.Table (Scope_Stack.Last).Is_Transient;
21985 end Scope_Is_Transient;
21987 ------------------
21988 -- Scope_Within --
21989 ------------------
21991 function Scope_Within (Scope1, Scope2 : Entity_Id) return Boolean is
21992 Scop : Entity_Id;
21994 begin
21995 Scop := Scope1;
21996 while Scop /= Standard_Standard loop
21997 Scop := Scope (Scop);
21999 if Scop = Scope2 then
22000 return True;
22001 end if;
22002 end loop;
22004 return False;
22005 end Scope_Within;
22007 --------------------------
22008 -- Scope_Within_Or_Same --
22009 --------------------------
22011 function Scope_Within_Or_Same (Scope1, Scope2 : Entity_Id) return Boolean is
22012 Scop : Entity_Id;
22014 begin
22015 Scop := Scope1;
22016 while Scop /= Standard_Standard loop
22017 if Scop = Scope2 then
22018 return True;
22019 else
22020 Scop := Scope (Scop);
22021 end if;
22022 end loop;
22024 return False;
22025 end Scope_Within_Or_Same;
22027 --------------------
22028 -- Set_Convention --
22029 --------------------
22031 procedure Set_Convention (E : Entity_Id; Val : Snames.Convention_Id) is
22032 begin
22033 Basic_Set_Convention (E, Val);
22035 if Is_Type (E)
22036 and then Is_Access_Subprogram_Type (Base_Type (E))
22037 and then Has_Foreign_Convention (E)
22038 then
22040 -- A pragma Convention in an instance may apply to the subtype
22041 -- created for a formal, in which case we have already verified
22042 -- that conventions of actual and formal match and there is nothing
22043 -- to flag on the subtype.
22045 if In_Instance then
22046 null;
22047 else
22048 Set_Can_Use_Internal_Rep (E, False);
22049 end if;
22050 end if;
22052 -- If E is an object or component, and the type of E is an anonymous
22053 -- access type with no convention set, then also set the convention of
22054 -- the anonymous access type. We do not do this for anonymous protected
22055 -- types, since protected types always have the default convention.
22057 if Present (Etype (E))
22058 and then (Is_Object (E)
22059 or else Ekind (E) = E_Component
22061 -- Allow E_Void (happens for pragma Convention appearing
22062 -- in the middle of a record applying to a component)
22064 or else Ekind (E) = E_Void)
22065 then
22066 declare
22067 Typ : constant Entity_Id := Etype (E);
22069 begin
22070 if Ekind_In (Typ, E_Anonymous_Access_Type,
22071 E_Anonymous_Access_Subprogram_Type)
22072 and then not Has_Convention_Pragma (Typ)
22073 then
22074 Basic_Set_Convention (Typ, Val);
22075 Set_Has_Convention_Pragma (Typ);
22077 -- And for the access subprogram type, deal similarly with the
22078 -- designated E_Subprogram_Type if it is also internal (which
22079 -- it always is?)
22081 if Ekind (Typ) = E_Anonymous_Access_Subprogram_Type then
22082 declare
22083 Dtype : constant Entity_Id := Designated_Type (Typ);
22084 begin
22085 if Ekind (Dtype) = E_Subprogram_Type
22086 and then Is_Itype (Dtype)
22087 and then not Has_Convention_Pragma (Dtype)
22088 then
22089 Basic_Set_Convention (Dtype, Val);
22090 Set_Has_Convention_Pragma (Dtype);
22091 end if;
22092 end;
22093 end if;
22094 end if;
22095 end;
22096 end if;
22097 end Set_Convention;
22099 ------------------------
22100 -- Set_Current_Entity --
22101 ------------------------
22103 -- The given entity is to be set as the currently visible definition of its
22104 -- associated name (i.e. the Node_Id associated with its name). All we have
22105 -- to do is to get the name from the identifier, and then set the
22106 -- associated Node_Id to point to the given entity.
22108 procedure Set_Current_Entity (E : Entity_Id) is
22109 begin
22110 Set_Name_Entity_Id (Chars (E), E);
22111 end Set_Current_Entity;
22113 ---------------------------
22114 -- Set_Debug_Info_Needed --
22115 ---------------------------
22117 procedure Set_Debug_Info_Needed (T : Entity_Id) is
22119 procedure Set_Debug_Info_Needed_If_Not_Set (E : Entity_Id);
22120 pragma Inline (Set_Debug_Info_Needed_If_Not_Set);
22121 -- Used to set debug info in a related node if not set already
22123 --------------------------------------
22124 -- Set_Debug_Info_Needed_If_Not_Set --
22125 --------------------------------------
22127 procedure Set_Debug_Info_Needed_If_Not_Set (E : Entity_Id) is
22128 begin
22129 if Present (E) and then not Needs_Debug_Info (E) then
22130 Set_Debug_Info_Needed (E);
22132 -- For a private type, indicate that the full view also needs
22133 -- debug information.
22135 if Is_Type (E)
22136 and then Is_Private_Type (E)
22137 and then Present (Full_View (E))
22138 then
22139 Set_Debug_Info_Needed (Full_View (E));
22140 end if;
22141 end if;
22142 end Set_Debug_Info_Needed_If_Not_Set;
22144 -- Start of processing for Set_Debug_Info_Needed
22146 begin
22147 -- Nothing to do if argument is Empty or has Debug_Info_Off set, which
22148 -- indicates that Debug_Info_Needed is never required for the entity.
22149 -- Nothing to do if entity comes from a predefined file. Library files
22150 -- are compiled without debug information, but inlined bodies of these
22151 -- routines may appear in user code, and debug information on them ends
22152 -- up complicating debugging the user code.
22154 if No (T)
22155 or else Debug_Info_Off (T)
22156 then
22157 return;
22159 elsif In_Inlined_Body and then In_Predefined_Unit (T) then
22160 Set_Needs_Debug_Info (T, False);
22161 end if;
22163 -- Set flag in entity itself. Note that we will go through the following
22164 -- circuitry even if the flag is already set on T. That's intentional,
22165 -- it makes sure that the flag will be set in subsidiary entities.
22167 Set_Needs_Debug_Info (T);
22169 -- Set flag on subsidiary entities if not set already
22171 if Is_Object (T) then
22172 Set_Debug_Info_Needed_If_Not_Set (Etype (T));
22174 elsif Is_Type (T) then
22175 Set_Debug_Info_Needed_If_Not_Set (Etype (T));
22177 if Is_Record_Type (T) then
22178 declare
22179 Ent : Entity_Id := First_Entity (T);
22180 begin
22181 while Present (Ent) loop
22182 Set_Debug_Info_Needed_If_Not_Set (Ent);
22183 Next_Entity (Ent);
22184 end loop;
22185 end;
22187 -- For a class wide subtype, we also need debug information
22188 -- for the equivalent type.
22190 if Ekind (T) = E_Class_Wide_Subtype then
22191 Set_Debug_Info_Needed_If_Not_Set (Equivalent_Type (T));
22192 end if;
22194 elsif Is_Array_Type (T) then
22195 Set_Debug_Info_Needed_If_Not_Set (Component_Type (T));
22197 declare
22198 Indx : Node_Id := First_Index (T);
22199 begin
22200 while Present (Indx) loop
22201 Set_Debug_Info_Needed_If_Not_Set (Etype (Indx));
22202 Indx := Next_Index (Indx);
22203 end loop;
22204 end;
22206 -- For a packed array type, we also need debug information for
22207 -- the type used to represent the packed array. Conversely, we
22208 -- also need it for the former if we need it for the latter.
22210 if Is_Packed (T) then
22211 Set_Debug_Info_Needed_If_Not_Set (Packed_Array_Impl_Type (T));
22212 end if;
22214 if Is_Packed_Array_Impl_Type (T) then
22215 Set_Debug_Info_Needed_If_Not_Set (Original_Array_Type (T));
22216 end if;
22218 elsif Is_Access_Type (T) then
22219 Set_Debug_Info_Needed_If_Not_Set (Directly_Designated_Type (T));
22221 elsif Is_Private_Type (T) then
22222 declare
22223 FV : constant Entity_Id := Full_View (T);
22225 begin
22226 Set_Debug_Info_Needed_If_Not_Set (FV);
22228 -- If the full view is itself a derived private type, we need
22229 -- debug information on its underlying type.
22231 if Present (FV)
22232 and then Is_Private_Type (FV)
22233 and then Present (Underlying_Full_View (FV))
22234 then
22235 Set_Needs_Debug_Info (Underlying_Full_View (FV));
22236 end if;
22237 end;
22239 elsif Is_Protected_Type (T) then
22240 Set_Debug_Info_Needed_If_Not_Set (Corresponding_Record_Type (T));
22242 elsif Is_Scalar_Type (T) then
22244 -- If the subrange bounds are materialized by dedicated constant
22245 -- objects, also include them in the debug info to make sure the
22246 -- debugger can properly use them.
22248 if Present (Scalar_Range (T))
22249 and then Nkind (Scalar_Range (T)) = N_Range
22250 then
22251 declare
22252 Low_Bnd : constant Node_Id := Type_Low_Bound (T);
22253 High_Bnd : constant Node_Id := Type_High_Bound (T);
22255 begin
22256 if Is_Entity_Name (Low_Bnd) then
22257 Set_Debug_Info_Needed_If_Not_Set (Entity (Low_Bnd));
22258 end if;
22260 if Is_Entity_Name (High_Bnd) then
22261 Set_Debug_Info_Needed_If_Not_Set (Entity (High_Bnd));
22262 end if;
22263 end;
22264 end if;
22265 end if;
22266 end if;
22267 end Set_Debug_Info_Needed;
22269 ----------------------------
22270 -- Set_Entity_With_Checks --
22271 ----------------------------
22273 procedure Set_Entity_With_Checks (N : Node_Id; Val : Entity_Id) is
22274 Val_Actual : Entity_Id;
22275 Nod : Node_Id;
22276 Post_Node : Node_Id;
22278 begin
22279 -- Unconditionally set the entity
22281 Set_Entity (N, Val);
22283 -- The node to post on is the selector in the case of an expanded name,
22284 -- and otherwise the node itself.
22286 if Nkind (N) = N_Expanded_Name then
22287 Post_Node := Selector_Name (N);
22288 else
22289 Post_Node := N;
22290 end if;
22292 -- Check for violation of No_Fixed_IO
22294 if Restriction_Check_Required (No_Fixed_IO)
22295 and then
22296 ((RTU_Loaded (Ada_Text_IO)
22297 and then (Is_RTE (Val, RE_Decimal_IO)
22298 or else
22299 Is_RTE (Val, RE_Fixed_IO)))
22301 or else
22302 (RTU_Loaded (Ada_Wide_Text_IO)
22303 and then (Is_RTE (Val, RO_WT_Decimal_IO)
22304 or else
22305 Is_RTE (Val, RO_WT_Fixed_IO)))
22307 or else
22308 (RTU_Loaded (Ada_Wide_Wide_Text_IO)
22309 and then (Is_RTE (Val, RO_WW_Decimal_IO)
22310 or else
22311 Is_RTE (Val, RO_WW_Fixed_IO))))
22313 -- A special extra check, don't complain about a reference from within
22314 -- the Ada.Interrupts package itself!
22316 and then not In_Same_Extended_Unit (N, Val)
22317 then
22318 Check_Restriction (No_Fixed_IO, Post_Node);
22319 end if;
22321 -- Remaining checks are only done on source nodes. Note that we test
22322 -- for violation of No_Fixed_IO even on non-source nodes, because the
22323 -- cases for checking violations of this restriction are instantiations
22324 -- where the reference in the instance has Comes_From_Source False.
22326 if not Comes_From_Source (N) then
22327 return;
22328 end if;
22330 -- Check for violation of No_Abort_Statements, which is triggered by
22331 -- call to Ada.Task_Identification.Abort_Task.
22333 if Restriction_Check_Required (No_Abort_Statements)
22334 and then (Is_RTE (Val, RE_Abort_Task))
22336 -- A special extra check, don't complain about a reference from within
22337 -- the Ada.Task_Identification package itself!
22339 and then not In_Same_Extended_Unit (N, Val)
22340 then
22341 Check_Restriction (No_Abort_Statements, Post_Node);
22342 end if;
22344 if Val = Standard_Long_Long_Integer then
22345 Check_Restriction (No_Long_Long_Integers, Post_Node);
22346 end if;
22348 -- Check for violation of No_Dynamic_Attachment
22350 if Restriction_Check_Required (No_Dynamic_Attachment)
22351 and then RTU_Loaded (Ada_Interrupts)
22352 and then (Is_RTE (Val, RE_Is_Reserved) or else
22353 Is_RTE (Val, RE_Is_Attached) or else
22354 Is_RTE (Val, RE_Current_Handler) or else
22355 Is_RTE (Val, RE_Attach_Handler) or else
22356 Is_RTE (Val, RE_Exchange_Handler) or else
22357 Is_RTE (Val, RE_Detach_Handler) or else
22358 Is_RTE (Val, RE_Reference))
22360 -- A special extra check, don't complain about a reference from within
22361 -- the Ada.Interrupts package itself!
22363 and then not In_Same_Extended_Unit (N, Val)
22364 then
22365 Check_Restriction (No_Dynamic_Attachment, Post_Node);
22366 end if;
22368 -- Check for No_Implementation_Identifiers
22370 if Restriction_Check_Required (No_Implementation_Identifiers) then
22372 -- We have an implementation defined entity if it is marked as
22373 -- implementation defined, or is defined in a package marked as
22374 -- implementation defined. However, library packages themselves
22375 -- are excluded (we don't want to flag Interfaces itself, just
22376 -- the entities within it).
22378 if (Is_Implementation_Defined (Val)
22379 or else
22380 (Present (Scope (Val))
22381 and then Is_Implementation_Defined (Scope (Val))))
22382 and then not (Ekind_In (Val, E_Package, E_Generic_Package)
22383 and then Is_Library_Level_Entity (Val))
22384 then
22385 Check_Restriction (No_Implementation_Identifiers, Post_Node);
22386 end if;
22387 end if;
22389 -- Do the style check
22391 if Style_Check
22392 and then not Suppress_Style_Checks (Val)
22393 and then not In_Instance
22394 then
22395 if Nkind (N) = N_Identifier then
22396 Nod := N;
22397 elsif Nkind (N) = N_Expanded_Name then
22398 Nod := Selector_Name (N);
22399 else
22400 return;
22401 end if;
22403 -- A special situation arises for derived operations, where we want
22404 -- to do the check against the parent (since the Sloc of the derived
22405 -- operation points to the derived type declaration itself).
22407 Val_Actual := Val;
22408 while not Comes_From_Source (Val_Actual)
22409 and then Nkind (Val_Actual) in N_Entity
22410 and then (Ekind (Val_Actual) = E_Enumeration_Literal
22411 or else Is_Subprogram_Or_Generic_Subprogram (Val_Actual))
22412 and then Present (Alias (Val_Actual))
22413 loop
22414 Val_Actual := Alias (Val_Actual);
22415 end loop;
22417 -- Renaming declarations for generic actuals do not come from source,
22418 -- and have a different name from that of the entity they rename, so
22419 -- there is no style check to perform here.
22421 if Chars (Nod) = Chars (Val_Actual) then
22422 Style.Check_Identifier (Nod, Val_Actual);
22423 end if;
22424 end if;
22426 Set_Entity (N, Val);
22427 end Set_Entity_With_Checks;
22429 ------------------------
22430 -- Set_Name_Entity_Id --
22431 ------------------------
22433 procedure Set_Name_Entity_Id (Id : Name_Id; Val : Entity_Id) is
22434 begin
22435 Set_Name_Table_Int (Id, Int (Val));
22436 end Set_Name_Entity_Id;
22438 ---------------------
22439 -- Set_Next_Actual --
22440 ---------------------
22442 procedure Set_Next_Actual (Ass1_Id : Node_Id; Ass2_Id : Node_Id) is
22443 begin
22444 if Nkind (Parent (Ass1_Id)) = N_Parameter_Association then
22445 Set_First_Named_Actual (Parent (Ass1_Id), Ass2_Id);
22446 end if;
22447 end Set_Next_Actual;
22449 ----------------------------------
22450 -- Set_Optimize_Alignment_Flags --
22451 ----------------------------------
22453 procedure Set_Optimize_Alignment_Flags (E : Entity_Id) is
22454 begin
22455 if Optimize_Alignment = 'S' then
22456 Set_Optimize_Alignment_Space (E);
22457 elsif Optimize_Alignment = 'T' then
22458 Set_Optimize_Alignment_Time (E);
22459 end if;
22460 end Set_Optimize_Alignment_Flags;
22462 -----------------------
22463 -- Set_Public_Status --
22464 -----------------------
22466 procedure Set_Public_Status (Id : Entity_Id) is
22467 S : constant Entity_Id := Current_Scope;
22469 function Within_HSS_Or_If (E : Entity_Id) return Boolean;
22470 -- Determines if E is defined within handled statement sequence or
22471 -- an if statement, returns True if so, False otherwise.
22473 ----------------------
22474 -- Within_HSS_Or_If --
22475 ----------------------
22477 function Within_HSS_Or_If (E : Entity_Id) return Boolean is
22478 N : Node_Id;
22479 begin
22480 N := Declaration_Node (E);
22481 loop
22482 N := Parent (N);
22484 if No (N) then
22485 return False;
22487 elsif Nkind_In (N, N_Handled_Sequence_Of_Statements,
22488 N_If_Statement)
22489 then
22490 return True;
22491 end if;
22492 end loop;
22493 end Within_HSS_Or_If;
22495 -- Start of processing for Set_Public_Status
22497 begin
22498 -- Everything in the scope of Standard is public
22500 if S = Standard_Standard then
22501 Set_Is_Public (Id);
22503 -- Entity is definitely not public if enclosing scope is not public
22505 elsif not Is_Public (S) then
22506 return;
22508 -- An object or function declaration that occurs in a handled sequence
22509 -- of statements or within an if statement is the declaration for a
22510 -- temporary object or local subprogram generated by the expander. It
22511 -- never needs to be made public and furthermore, making it public can
22512 -- cause back end problems.
22514 elsif Nkind_In (Parent (Id), N_Object_Declaration,
22515 N_Function_Specification)
22516 and then Within_HSS_Or_If (Id)
22517 then
22518 return;
22520 -- Entities in public packages or records are public
22522 elsif Ekind (S) = E_Package or Is_Record_Type (S) then
22523 Set_Is_Public (Id);
22525 -- The bounds of an entry family declaration can generate object
22526 -- declarations that are visible to the back-end, e.g. in the
22527 -- the declaration of a composite type that contains tasks.
22529 elsif Is_Concurrent_Type (S)
22530 and then not Has_Completion (S)
22531 and then Nkind (Parent (Id)) = N_Object_Declaration
22532 then
22533 Set_Is_Public (Id);
22534 end if;
22535 end Set_Public_Status;
22537 -----------------------------
22538 -- Set_Referenced_Modified --
22539 -----------------------------
22541 procedure Set_Referenced_Modified (N : Node_Id; Out_Param : Boolean) is
22542 Pref : Node_Id;
22544 begin
22545 -- Deal with indexed or selected component where prefix is modified
22547 if Nkind_In (N, N_Indexed_Component, N_Selected_Component) then
22548 Pref := Prefix (N);
22550 -- If prefix is access type, then it is the designated object that is
22551 -- being modified, which means we have no entity to set the flag on.
22553 if No (Etype (Pref)) or else Is_Access_Type (Etype (Pref)) then
22554 return;
22556 -- Otherwise chase the prefix
22558 else
22559 Set_Referenced_Modified (Pref, Out_Param);
22560 end if;
22562 -- Otherwise see if we have an entity name (only other case to process)
22564 elsif Is_Entity_Name (N) and then Present (Entity (N)) then
22565 Set_Referenced_As_LHS (Entity (N), not Out_Param);
22566 Set_Referenced_As_Out_Parameter (Entity (N), Out_Param);
22567 end if;
22568 end Set_Referenced_Modified;
22570 ------------------
22571 -- Set_Rep_Info --
22572 ------------------
22574 procedure Set_Rep_Info (T1 : Entity_Id; T2 : Entity_Id) is
22575 begin
22576 Set_Is_Atomic (T1, Is_Atomic (T2));
22577 Set_Is_Independent (T1, Is_Independent (T2));
22578 Set_Is_Volatile_Full_Access (T1, Is_Volatile_Full_Access (T2));
22580 if Is_Base_Type (T1) then
22581 Set_Is_Volatile (T1, Is_Volatile (T2));
22582 end if;
22583 end Set_Rep_Info;
22585 ----------------------------
22586 -- Set_Scope_Is_Transient --
22587 ----------------------------
22589 procedure Set_Scope_Is_Transient (V : Boolean := True) is
22590 begin
22591 Scope_Stack.Table (Scope_Stack.Last).Is_Transient := V;
22592 end Set_Scope_Is_Transient;
22594 -------------------
22595 -- Set_Size_Info --
22596 -------------------
22598 procedure Set_Size_Info (T1, T2 : Entity_Id) is
22599 begin
22600 -- We copy Esize, but not RM_Size, since in general RM_Size is
22601 -- subtype specific and does not get inherited by all subtypes.
22603 Set_Esize (T1, Esize (T2));
22604 Set_Has_Biased_Representation (T1, Has_Biased_Representation (T2));
22606 if Is_Discrete_Or_Fixed_Point_Type (T1)
22607 and then
22608 Is_Discrete_Or_Fixed_Point_Type (T2)
22609 then
22610 Set_Is_Unsigned_Type (T1, Is_Unsigned_Type (T2));
22611 end if;
22613 Set_Alignment (T1, Alignment (T2));
22614 end Set_Size_Info;
22616 ------------------------------
22617 -- Should_Ignore_Pragma_Par --
22618 ------------------------------
22620 function Should_Ignore_Pragma_Par (Prag_Name : Name_Id) return Boolean is
22621 pragma Assert (Compiler_State = Parsing);
22622 -- This one can't work during semantic analysis, because we don't have a
22623 -- correct Current_Source_File.
22625 Result : constant Boolean :=
22626 Get_Name_Table_Boolean3 (Prag_Name)
22627 and then not Is_Internal_File_Name
22628 (File_Name (Current_Source_File));
22629 begin
22630 return Result;
22631 end Should_Ignore_Pragma_Par;
22633 ------------------------------
22634 -- Should_Ignore_Pragma_Sem --
22635 ------------------------------
22637 function Should_Ignore_Pragma_Sem (N : Node_Id) return Boolean is
22638 pragma Assert (Compiler_State = Analyzing);
22639 Prag_Name : constant Name_Id := Pragma_Name (N);
22640 Result : constant Boolean :=
22641 Get_Name_Table_Boolean3 (Prag_Name)
22642 and then not In_Internal_Unit (N);
22644 begin
22645 return Result;
22646 end Should_Ignore_Pragma_Sem;
22648 --------------------
22649 -- Static_Boolean --
22650 --------------------
22652 function Static_Boolean (N : Node_Id) return Uint is
22653 begin
22654 Analyze_And_Resolve (N, Standard_Boolean);
22656 if N = Error
22657 or else Error_Posted (N)
22658 or else Etype (N) = Any_Type
22659 then
22660 return No_Uint;
22661 end if;
22663 if Is_OK_Static_Expression (N) then
22664 if not Raises_Constraint_Error (N) then
22665 return Expr_Value (N);
22666 else
22667 return No_Uint;
22668 end if;
22670 elsif Etype (N) = Any_Type then
22671 return No_Uint;
22673 else
22674 Flag_Non_Static_Expr
22675 ("static boolean expression required here", N);
22676 return No_Uint;
22677 end if;
22678 end Static_Boolean;
22680 --------------------
22681 -- Static_Integer --
22682 --------------------
22684 function Static_Integer (N : Node_Id) return Uint is
22685 begin
22686 Analyze_And_Resolve (N, Any_Integer);
22688 if N = Error
22689 or else Error_Posted (N)
22690 or else Etype (N) = Any_Type
22691 then
22692 return No_Uint;
22693 end if;
22695 if Is_OK_Static_Expression (N) then
22696 if not Raises_Constraint_Error (N) then
22697 return Expr_Value (N);
22698 else
22699 return No_Uint;
22700 end if;
22702 elsif Etype (N) = Any_Type then
22703 return No_Uint;
22705 else
22706 Flag_Non_Static_Expr
22707 ("static integer expression required here", N);
22708 return No_Uint;
22709 end if;
22710 end Static_Integer;
22712 --------------------------
22713 -- Statically_Different --
22714 --------------------------
22716 function Statically_Different (E1, E2 : Node_Id) return Boolean is
22717 R1 : constant Node_Id := Get_Referenced_Object (E1);
22718 R2 : constant Node_Id := Get_Referenced_Object (E2);
22719 begin
22720 return Is_Entity_Name (R1)
22721 and then Is_Entity_Name (R2)
22722 and then Entity (R1) /= Entity (R2)
22723 and then not Is_Formal (Entity (R1))
22724 and then not Is_Formal (Entity (R2));
22725 end Statically_Different;
22727 --------------------------------------
22728 -- Subject_To_Loop_Entry_Attributes --
22729 --------------------------------------
22731 function Subject_To_Loop_Entry_Attributes (N : Node_Id) return Boolean is
22732 Stmt : Node_Id;
22734 begin
22735 Stmt := N;
22737 -- The expansion mechanism transform a loop subject to at least one
22738 -- 'Loop_Entry attribute into a conditional block. Infinite loops lack
22739 -- the conditional part.
22741 if Nkind_In (Stmt, N_Block_Statement, N_If_Statement)
22742 and then Nkind (Original_Node (N)) = N_Loop_Statement
22743 then
22744 Stmt := Original_Node (N);
22745 end if;
22747 return
22748 Nkind (Stmt) = N_Loop_Statement
22749 and then Present (Identifier (Stmt))
22750 and then Present (Entity (Identifier (Stmt)))
22751 and then Has_Loop_Entry_Attributes (Entity (Identifier (Stmt)));
22752 end Subject_To_Loop_Entry_Attributes;
22754 -----------------------------
22755 -- Subprogram_Access_Level --
22756 -----------------------------
22758 function Subprogram_Access_Level (Subp : Entity_Id) return Uint is
22759 begin
22760 if Present (Alias (Subp)) then
22761 return Subprogram_Access_Level (Alias (Subp));
22762 else
22763 return Scope_Depth (Enclosing_Dynamic_Scope (Subp));
22764 end if;
22765 end Subprogram_Access_Level;
22767 ---------------------
22768 -- Subprogram_Name --
22769 ---------------------
22771 function Subprogram_Name (N : Node_Id) return String is
22772 Buf : Bounded_String;
22773 Ent : Node_Id := N;
22775 begin
22776 while Present (Ent) loop
22777 case Nkind (Ent) is
22778 when N_Subprogram_Body =>
22779 Ent := Defining_Unit_Name (Specification (Ent));
22780 exit;
22782 when N_Package_Body
22783 | N_Package_Specification
22784 | N_Subprogram_Specification
22786 Ent := Defining_Unit_Name (Ent);
22787 exit;
22789 when N_Protected_Body
22790 | N_Protected_Type_Declaration
22791 | N_Task_Body
22793 exit;
22795 when others =>
22796 null;
22797 end case;
22799 Ent := Parent (Ent);
22800 end loop;
22802 if No (Ent) then
22803 return "unknown subprogram";
22804 end if;
22806 Append_Entity_Name (Buf, Ent);
22807 return +Buf;
22808 end Subprogram_Name;
22810 -------------------------------
22811 -- Support_Atomic_Primitives --
22812 -------------------------------
22814 function Support_Atomic_Primitives (Typ : Entity_Id) return Boolean is
22815 Size : Int;
22817 begin
22818 -- Verify the alignment of Typ is known
22820 if not Known_Alignment (Typ) then
22821 return False;
22822 end if;
22824 if Known_Static_Esize (Typ) then
22825 Size := UI_To_Int (Esize (Typ));
22827 -- If the Esize (Object_Size) is unknown at compile time, look at the
22828 -- RM_Size (Value_Size) which may have been set by an explicit rep item.
22830 elsif Known_Static_RM_Size (Typ) then
22831 Size := UI_To_Int (RM_Size (Typ));
22833 -- Otherwise, the size is considered to be unknown.
22835 else
22836 return False;
22837 end if;
22839 -- Check that the size of the component is 8, 16, 32, or 64 bits and
22840 -- that Typ is properly aligned.
22842 case Size is
22843 when 8 | 16 | 32 | 64 =>
22844 return Size = UI_To_Int (Alignment (Typ)) * 8;
22846 when others =>
22847 return False;
22848 end case;
22849 end Support_Atomic_Primitives;
22851 -----------------
22852 -- Trace_Scope --
22853 -----------------
22855 procedure Trace_Scope (N : Node_Id; E : Entity_Id; Msg : String) is
22856 begin
22857 if Debug_Flag_W then
22858 for J in 0 .. Scope_Stack.Last loop
22859 Write_Str (" ");
22860 end loop;
22862 Write_Str (Msg);
22863 Write_Name (Chars (E));
22864 Write_Str (" from ");
22865 Write_Location (Sloc (N));
22866 Write_Eol;
22867 end if;
22868 end Trace_Scope;
22870 -----------------------
22871 -- Transfer_Entities --
22872 -----------------------
22874 procedure Transfer_Entities (From : Entity_Id; To : Entity_Id) is
22875 procedure Set_Public_Status_Of (Id : Entity_Id);
22876 -- Set the Is_Public attribute of arbitrary entity Id by calling routine
22877 -- Set_Public_Status. If successful and Id denotes a record type, set
22878 -- the Is_Public attribute of its fields.
22880 --------------------------
22881 -- Set_Public_Status_Of --
22882 --------------------------
22884 procedure Set_Public_Status_Of (Id : Entity_Id) is
22885 Field : Entity_Id;
22887 begin
22888 if not Is_Public (Id) then
22889 Set_Public_Status (Id);
22891 -- When the input entity is a public record type, ensure that all
22892 -- its internal fields are also exposed to the linker. The fields
22893 -- of a class-wide type are never made public.
22895 if Is_Public (Id)
22896 and then Is_Record_Type (Id)
22897 and then not Is_Class_Wide_Type (Id)
22898 then
22899 Field := First_Entity (Id);
22900 while Present (Field) loop
22901 Set_Is_Public (Field);
22902 Next_Entity (Field);
22903 end loop;
22904 end if;
22905 end if;
22906 end Set_Public_Status_Of;
22908 -- Local variables
22910 Full_Id : Entity_Id;
22911 Id : Entity_Id;
22913 -- Start of processing for Transfer_Entities
22915 begin
22916 Id := First_Entity (From);
22918 if Present (Id) then
22920 -- Merge the entity chain of the source scope with that of the
22921 -- destination scope.
22923 if Present (Last_Entity (To)) then
22924 Set_Next_Entity (Last_Entity (To), Id);
22925 else
22926 Set_First_Entity (To, Id);
22927 end if;
22929 Set_Last_Entity (To, Last_Entity (From));
22931 -- Inspect the entities of the source scope and update their Scope
22932 -- attribute.
22934 while Present (Id) loop
22935 Set_Scope (Id, To);
22936 Set_Public_Status_Of (Id);
22938 -- Handle an internally generated full view for a private type
22940 if Is_Private_Type (Id)
22941 and then Present (Full_View (Id))
22942 and then Is_Itype (Full_View (Id))
22943 then
22944 Full_Id := Full_View (Id);
22946 Set_Scope (Full_Id, To);
22947 Set_Public_Status_Of (Full_Id);
22948 end if;
22950 Next_Entity (Id);
22951 end loop;
22953 Set_First_Entity (From, Empty);
22954 Set_Last_Entity (From, Empty);
22955 end if;
22956 end Transfer_Entities;
22958 -----------------------
22959 -- Type_Access_Level --
22960 -----------------------
22962 function Type_Access_Level (Typ : Entity_Id) return Uint is
22963 Btyp : Entity_Id;
22965 begin
22966 Btyp := Base_Type (Typ);
22968 -- Ada 2005 (AI-230): For most cases of anonymous access types, we
22969 -- simply use the level where the type is declared. This is true for
22970 -- stand-alone object declarations, and for anonymous access types
22971 -- associated with components the level is the same as that of the
22972 -- enclosing composite type. However, special treatment is needed for
22973 -- the cases of access parameters, return objects of an anonymous access
22974 -- type, and, in Ada 95, access discriminants of limited types.
22976 if Is_Access_Type (Btyp) then
22977 if Ekind (Btyp) = E_Anonymous_Access_Type then
22979 -- If the type is a nonlocal anonymous access type (such as for
22980 -- an access parameter) we treat it as being declared at the
22981 -- library level to ensure that names such as X.all'access don't
22982 -- fail static accessibility checks.
22984 if not Is_Local_Anonymous_Access (Typ) then
22985 return Scope_Depth (Standard_Standard);
22987 -- If this is a return object, the accessibility level is that of
22988 -- the result subtype of the enclosing function. The test here is
22989 -- little complicated, because we have to account for extended
22990 -- return statements that have been rewritten as blocks, in which
22991 -- case we have to find and the Is_Return_Object attribute of the
22992 -- itype's associated object. It would be nice to find a way to
22993 -- simplify this test, but it doesn't seem worthwhile to add a new
22994 -- flag just for purposes of this test. ???
22996 elsif Ekind (Scope (Btyp)) = E_Return_Statement
22997 or else
22998 (Is_Itype (Btyp)
22999 and then Nkind (Associated_Node_For_Itype (Btyp)) =
23000 N_Object_Declaration
23001 and then Is_Return_Object
23002 (Defining_Identifier
23003 (Associated_Node_For_Itype (Btyp))))
23004 then
23005 declare
23006 Scop : Entity_Id;
23008 begin
23009 Scop := Scope (Scope (Btyp));
23010 while Present (Scop) loop
23011 exit when Ekind (Scop) = E_Function;
23012 Scop := Scope (Scop);
23013 end loop;
23015 -- Treat the return object's type as having the level of the
23016 -- function's result subtype (as per RM05-6.5(5.3/2)).
23018 return Type_Access_Level (Etype (Scop));
23019 end;
23020 end if;
23021 end if;
23023 Btyp := Root_Type (Btyp);
23025 -- The accessibility level of anonymous access types associated with
23026 -- discriminants is that of the current instance of the type, and
23027 -- that's deeper than the type itself (AARM 3.10.2 (12.3.21)).
23029 -- AI-402: access discriminants have accessibility based on the
23030 -- object rather than the type in Ada 2005, so the above paragraph
23031 -- doesn't apply.
23033 -- ??? Needs completion with rules from AI-416
23035 if Ada_Version <= Ada_95
23036 and then Ekind (Typ) = E_Anonymous_Access_Type
23037 and then Present (Associated_Node_For_Itype (Typ))
23038 and then Nkind (Associated_Node_For_Itype (Typ)) =
23039 N_Discriminant_Specification
23040 then
23041 return Scope_Depth (Enclosing_Dynamic_Scope (Btyp)) + 1;
23042 end if;
23043 end if;
23045 -- Return library level for a generic formal type. This is done because
23046 -- RM(10.3.2) says that "The statically deeper relationship does not
23047 -- apply to ... a descendant of a generic formal type". Rather than
23048 -- checking at each point where a static accessibility check is
23049 -- performed to see if we are dealing with a formal type, this rule is
23050 -- implemented by having Type_Access_Level and Deepest_Type_Access_Level
23051 -- return extreme values for a formal type; Deepest_Type_Access_Level
23052 -- returns Int'Last. By calling the appropriate function from among the
23053 -- two, we ensure that the static accessibility check will pass if we
23054 -- happen to run into a formal type. More specifically, we should call
23055 -- Deepest_Type_Access_Level instead of Type_Access_Level whenever the
23056 -- call occurs as part of a static accessibility check and the error
23057 -- case is the case where the type's level is too shallow (as opposed
23058 -- to too deep).
23060 if Is_Generic_Type (Root_Type (Btyp)) then
23061 return Scope_Depth (Standard_Standard);
23062 end if;
23064 return Scope_Depth (Enclosing_Dynamic_Scope (Btyp));
23065 end Type_Access_Level;
23067 ------------------------------------
23068 -- Type_Without_Stream_Operation --
23069 ------------------------------------
23071 function Type_Without_Stream_Operation
23072 (T : Entity_Id;
23073 Op : TSS_Name_Type := TSS_Null) return Entity_Id
23075 BT : constant Entity_Id := Base_Type (T);
23076 Op_Missing : Boolean;
23078 begin
23079 if not Restriction_Active (No_Default_Stream_Attributes) then
23080 return Empty;
23081 end if;
23083 if Is_Elementary_Type (T) then
23084 if Op = TSS_Null then
23085 Op_Missing :=
23086 No (TSS (BT, TSS_Stream_Read))
23087 or else No (TSS (BT, TSS_Stream_Write));
23089 else
23090 Op_Missing := No (TSS (BT, Op));
23091 end if;
23093 if Op_Missing then
23094 return T;
23095 else
23096 return Empty;
23097 end if;
23099 elsif Is_Array_Type (T) then
23100 return Type_Without_Stream_Operation (Component_Type (T), Op);
23102 elsif Is_Record_Type (T) then
23103 declare
23104 Comp : Entity_Id;
23105 C_Typ : Entity_Id;
23107 begin
23108 Comp := First_Component (T);
23109 while Present (Comp) loop
23110 C_Typ := Type_Without_Stream_Operation (Etype (Comp), Op);
23112 if Present (C_Typ) then
23113 return C_Typ;
23114 end if;
23116 Next_Component (Comp);
23117 end loop;
23119 return Empty;
23120 end;
23122 elsif Is_Private_Type (T) and then Present (Full_View (T)) then
23123 return Type_Without_Stream_Operation (Full_View (T), Op);
23124 else
23125 return Empty;
23126 end if;
23127 end Type_Without_Stream_Operation;
23129 ----------------------------
23130 -- Unique_Defining_Entity --
23131 ----------------------------
23133 function Unique_Defining_Entity (N : Node_Id) return Entity_Id is
23134 begin
23135 return Unique_Entity (Defining_Entity (N));
23136 end Unique_Defining_Entity;
23138 -------------------
23139 -- Unique_Entity --
23140 -------------------
23142 function Unique_Entity (E : Entity_Id) return Entity_Id is
23143 U : Entity_Id := E;
23144 P : Node_Id;
23146 begin
23147 case Ekind (E) is
23148 when E_Constant =>
23149 if Present (Full_View (E)) then
23150 U := Full_View (E);
23151 end if;
23153 when Entry_Kind =>
23154 if Nkind (Parent (E)) = N_Entry_Body then
23155 declare
23156 Prot_Item : Entity_Id;
23157 Prot_Type : Entity_Id;
23159 begin
23160 if Ekind (E) = E_Entry then
23161 Prot_Type := Scope (E);
23163 -- Bodies of entry families are nested within an extra scope
23164 -- that contains an entry index declaration.
23166 else
23167 Prot_Type := Scope (Scope (E));
23168 end if;
23170 -- A protected type may be declared as a private type, in
23171 -- which case we need to get its full view.
23173 if Is_Private_Type (Prot_Type) then
23174 Prot_Type := Full_View (Prot_Type);
23175 end if;
23177 -- Full view may not be present on error, in which case
23178 -- return E by default.
23180 if Present (Prot_Type) then
23181 pragma Assert (Ekind (Prot_Type) = E_Protected_Type);
23183 -- Traverse the entity list of the protected type and
23184 -- locate an entry declaration which matches the entry
23185 -- body.
23187 Prot_Item := First_Entity (Prot_Type);
23188 while Present (Prot_Item) loop
23189 if Ekind (Prot_Item) in Entry_Kind
23190 and then Corresponding_Body (Parent (Prot_Item)) = E
23191 then
23192 U := Prot_Item;
23193 exit;
23194 end if;
23196 Next_Entity (Prot_Item);
23197 end loop;
23198 end if;
23199 end;
23200 end if;
23202 when Formal_Kind =>
23203 if Present (Spec_Entity (E)) then
23204 U := Spec_Entity (E);
23205 end if;
23207 when E_Package_Body =>
23208 P := Parent (E);
23210 if Nkind (P) = N_Defining_Program_Unit_Name then
23211 P := Parent (P);
23212 end if;
23214 if Nkind (P) = N_Package_Body
23215 and then Present (Corresponding_Spec (P))
23216 then
23217 U := Corresponding_Spec (P);
23219 elsif Nkind (P) = N_Package_Body_Stub
23220 and then Present (Corresponding_Spec_Of_Stub (P))
23221 then
23222 U := Corresponding_Spec_Of_Stub (P);
23223 end if;
23225 when E_Protected_Body =>
23226 P := Parent (E);
23228 if Nkind (P) = N_Protected_Body
23229 and then Present (Corresponding_Spec (P))
23230 then
23231 U := Corresponding_Spec (P);
23233 elsif Nkind (P) = N_Protected_Body_Stub
23234 and then Present (Corresponding_Spec_Of_Stub (P))
23235 then
23236 U := Corresponding_Spec_Of_Stub (P);
23238 if Is_Single_Protected_Object (U) then
23239 U := Etype (U);
23240 end if;
23241 end if;
23243 if Is_Private_Type (U) then
23244 U := Full_View (U);
23245 end if;
23247 when E_Subprogram_Body =>
23248 P := Parent (E);
23250 if Nkind (P) = N_Defining_Program_Unit_Name then
23251 P := Parent (P);
23252 end if;
23254 P := Parent (P);
23256 if Nkind (P) = N_Subprogram_Body
23257 and then Present (Corresponding_Spec (P))
23258 then
23259 U := Corresponding_Spec (P);
23261 elsif Nkind (P) = N_Subprogram_Body_Stub
23262 and then Present (Corresponding_Spec_Of_Stub (P))
23263 then
23264 U := Corresponding_Spec_Of_Stub (P);
23266 elsif Nkind (P) = N_Subprogram_Renaming_Declaration then
23267 U := Corresponding_Spec (P);
23268 end if;
23270 when E_Task_Body =>
23271 P := Parent (E);
23273 if Nkind (P) = N_Task_Body
23274 and then Present (Corresponding_Spec (P))
23275 then
23276 U := Corresponding_Spec (P);
23278 elsif Nkind (P) = N_Task_Body_Stub
23279 and then Present (Corresponding_Spec_Of_Stub (P))
23280 then
23281 U := Corresponding_Spec_Of_Stub (P);
23283 if Is_Single_Task_Object (U) then
23284 U := Etype (U);
23285 end if;
23286 end if;
23288 if Is_Private_Type (U) then
23289 U := Full_View (U);
23290 end if;
23292 when Type_Kind =>
23293 if Present (Full_View (E)) then
23294 U := Full_View (E);
23295 end if;
23297 when others =>
23298 null;
23299 end case;
23301 return U;
23302 end Unique_Entity;
23304 -----------------
23305 -- Unique_Name --
23306 -----------------
23308 function Unique_Name (E : Entity_Id) return String is
23310 -- Names in E_Subprogram_Body or E_Package_Body entities are not
23311 -- reliable, as they may not include the overloading suffix. Instead,
23312 -- when looking for the name of E or one of its enclosing scope, we get
23313 -- the name of the corresponding Unique_Entity.
23315 U : constant Entity_Id := Unique_Entity (E);
23317 function This_Name return String;
23319 ---------------
23320 -- This_Name --
23321 ---------------
23323 function This_Name return String is
23324 begin
23325 return Get_Name_String (Chars (U));
23326 end This_Name;
23328 -- Start of processing for Unique_Name
23330 begin
23331 if E = Standard_Standard
23332 or else Has_Fully_Qualified_Name (E)
23333 then
23334 return This_Name;
23336 elsif Ekind (E) = E_Enumeration_Literal then
23337 return Unique_Name (Etype (E)) & "__" & This_Name;
23339 else
23340 declare
23341 S : constant Entity_Id := Scope (U);
23342 pragma Assert (Present (S));
23344 begin
23345 -- Prefix names of predefined types with standard__, but leave
23346 -- names of user-defined packages and subprograms without prefix
23347 -- (even if technically they are nested in the Standard package).
23349 if S = Standard_Standard then
23350 if Ekind (U) = E_Package or else Is_Subprogram (U) then
23351 return This_Name;
23352 else
23353 return Unique_Name (S) & "__" & This_Name;
23354 end if;
23356 -- For intances of generic subprograms use the name of the related
23357 -- instace and skip the scope of its wrapper package.
23359 elsif Is_Wrapper_Package (S) then
23360 pragma Assert (Scope (S) = Scope (Related_Instance (S)));
23361 -- Wrapper package and the instantiation are in the same scope
23363 declare
23364 Enclosing_Name : constant String :=
23365 Unique_Name (Scope (S)) & "__" &
23366 Get_Name_String (Chars (Related_Instance (S)));
23368 begin
23369 if Is_Subprogram (U)
23370 and then not Is_Generic_Actual_Subprogram (U)
23371 then
23372 return Enclosing_Name;
23373 else
23374 return Enclosing_Name & "__" & This_Name;
23375 end if;
23376 end;
23378 else
23379 return Unique_Name (S) & "__" & This_Name;
23380 end if;
23381 end;
23382 end if;
23383 end Unique_Name;
23385 ---------------------
23386 -- Unit_Is_Visible --
23387 ---------------------
23389 function Unit_Is_Visible (U : Entity_Id) return Boolean is
23390 Curr : constant Node_Id := Cunit (Current_Sem_Unit);
23391 Curr_Entity : constant Entity_Id := Cunit_Entity (Current_Sem_Unit);
23393 function Unit_In_Parent_Context (Par_Unit : Node_Id) return Boolean;
23394 -- For a child unit, check whether unit appears in a with_clause
23395 -- of a parent.
23397 function Unit_In_Context (Comp_Unit : Node_Id) return Boolean;
23398 -- Scan the context clause of one compilation unit looking for a
23399 -- with_clause for the unit in question.
23401 ----------------------------
23402 -- Unit_In_Parent_Context --
23403 ----------------------------
23405 function Unit_In_Parent_Context (Par_Unit : Node_Id) return Boolean is
23406 begin
23407 if Unit_In_Context (Par_Unit) then
23408 return True;
23410 elsif Is_Child_Unit (Defining_Entity (Unit (Par_Unit))) then
23411 return Unit_In_Parent_Context (Parent_Spec (Unit (Par_Unit)));
23413 else
23414 return False;
23415 end if;
23416 end Unit_In_Parent_Context;
23418 ---------------------
23419 -- Unit_In_Context --
23420 ---------------------
23422 function Unit_In_Context (Comp_Unit : Node_Id) return Boolean is
23423 Clause : Node_Id;
23425 begin
23426 Clause := First (Context_Items (Comp_Unit));
23427 while Present (Clause) loop
23428 if Nkind (Clause) = N_With_Clause then
23429 if Library_Unit (Clause) = U then
23430 return True;
23432 -- The with_clause may denote a renaming of the unit we are
23433 -- looking for, eg. Text_IO which renames Ada.Text_IO.
23435 elsif
23436 Renamed_Entity (Entity (Name (Clause))) =
23437 Defining_Entity (Unit (U))
23438 then
23439 return True;
23440 end if;
23441 end if;
23443 Next (Clause);
23444 end loop;
23446 return False;
23447 end Unit_In_Context;
23449 -- Start of processing for Unit_Is_Visible
23451 begin
23452 -- The currrent unit is directly visible
23454 if Curr = U then
23455 return True;
23457 elsif Unit_In_Context (Curr) then
23458 return True;
23460 -- If the current unit is a body, check the context of the spec
23462 elsif Nkind (Unit (Curr)) = N_Package_Body
23463 or else
23464 (Nkind (Unit (Curr)) = N_Subprogram_Body
23465 and then not Acts_As_Spec (Unit (Curr)))
23466 then
23467 if Unit_In_Context (Library_Unit (Curr)) then
23468 return True;
23469 end if;
23470 end if;
23472 -- If the spec is a child unit, examine the parents
23474 if Is_Child_Unit (Curr_Entity) then
23475 if Nkind (Unit (Curr)) in N_Unit_Body then
23476 return
23477 Unit_In_Parent_Context
23478 (Parent_Spec (Unit (Library_Unit (Curr))));
23479 else
23480 return Unit_In_Parent_Context (Parent_Spec (Unit (Curr)));
23481 end if;
23483 else
23484 return False;
23485 end if;
23486 end Unit_Is_Visible;
23488 ------------------------------
23489 -- Universal_Interpretation --
23490 ------------------------------
23492 function Universal_Interpretation (Opnd : Node_Id) return Entity_Id is
23493 Index : Interp_Index;
23494 It : Interp;
23496 begin
23497 -- The argument may be a formal parameter of an operator or subprogram
23498 -- with multiple interpretations, or else an expression for an actual.
23500 if Nkind (Opnd) = N_Defining_Identifier
23501 or else not Is_Overloaded (Opnd)
23502 then
23503 if Etype (Opnd) = Universal_Integer
23504 or else Etype (Opnd) = Universal_Real
23505 then
23506 return Etype (Opnd);
23507 else
23508 return Empty;
23509 end if;
23511 else
23512 Get_First_Interp (Opnd, Index, It);
23513 while Present (It.Typ) loop
23514 if It.Typ = Universal_Integer
23515 or else It.Typ = Universal_Real
23516 then
23517 return It.Typ;
23518 end if;
23520 Get_Next_Interp (Index, It);
23521 end loop;
23523 return Empty;
23524 end if;
23525 end Universal_Interpretation;
23527 ---------------
23528 -- Unqualify --
23529 ---------------
23531 function Unqualify (Expr : Node_Id) return Node_Id is
23532 begin
23533 -- Recurse to handle unlikely case of multiple levels of qualification
23535 if Nkind (Expr) = N_Qualified_Expression then
23536 return Unqualify (Expression (Expr));
23538 -- Normal case, not a qualified expression
23540 else
23541 return Expr;
23542 end if;
23543 end Unqualify;
23545 -----------------
23546 -- Unqual_Conv --
23547 -----------------
23549 function Unqual_Conv (Expr : Node_Id) return Node_Id is
23550 begin
23551 -- Recurse to handle unlikely case of multiple levels of qualification
23552 -- and/or conversion.
23554 if Nkind_In (Expr, N_Qualified_Expression,
23555 N_Type_Conversion,
23556 N_Unchecked_Type_Conversion)
23557 then
23558 return Unqual_Conv (Expression (Expr));
23560 -- Normal case, not a qualified expression
23562 else
23563 return Expr;
23564 end if;
23565 end Unqual_Conv;
23567 -----------------------
23568 -- Visible_Ancestors --
23569 -----------------------
23571 function Visible_Ancestors (Typ : Entity_Id) return Elist_Id is
23572 List_1 : Elist_Id;
23573 List_2 : Elist_Id;
23574 Elmt : Elmt_Id;
23576 begin
23577 pragma Assert (Is_Record_Type (Typ) and then Is_Tagged_Type (Typ));
23579 -- Collect all the parents and progenitors of Typ. If the full-view of
23580 -- private parents and progenitors is available then it is used to
23581 -- generate the list of visible ancestors; otherwise their partial
23582 -- view is added to the resulting list.
23584 Collect_Parents
23585 (T => Typ,
23586 List => List_1,
23587 Use_Full_View => True);
23589 Collect_Interfaces
23590 (T => Typ,
23591 Ifaces_List => List_2,
23592 Exclude_Parents => True,
23593 Use_Full_View => True);
23595 -- Join the two lists. Avoid duplications because an interface may
23596 -- simultaneously be parent and progenitor of a type.
23598 Elmt := First_Elmt (List_2);
23599 while Present (Elmt) loop
23600 Append_Unique_Elmt (Node (Elmt), List_1);
23601 Next_Elmt (Elmt);
23602 end loop;
23604 return List_1;
23605 end Visible_Ancestors;
23607 ----------------------
23608 -- Within_Init_Proc --
23609 ----------------------
23611 function Within_Init_Proc return Boolean is
23612 S : Entity_Id;
23614 begin
23615 S := Current_Scope;
23616 while not Is_Overloadable (S) loop
23617 if S = Standard_Standard then
23618 return False;
23619 else
23620 S := Scope (S);
23621 end if;
23622 end loop;
23624 return Is_Init_Proc (S);
23625 end Within_Init_Proc;
23627 ---------------------------
23628 -- Within_Protected_Type --
23629 ---------------------------
23631 function Within_Protected_Type (E : Entity_Id) return Boolean is
23632 Scop : Entity_Id := Scope (E);
23634 begin
23635 while Present (Scop) loop
23636 if Ekind (Scop) = E_Protected_Type then
23637 return True;
23638 end if;
23640 Scop := Scope (Scop);
23641 end loop;
23643 return False;
23644 end Within_Protected_Type;
23646 ------------------
23647 -- Within_Scope --
23648 ------------------
23650 function Within_Scope (E : Entity_Id; S : Entity_Id) return Boolean is
23651 begin
23652 return Scope_Within_Or_Same (Scope (E), S);
23653 end Within_Scope;
23655 ----------------
23656 -- Wrong_Type --
23657 ----------------
23659 procedure Wrong_Type (Expr : Node_Id; Expected_Type : Entity_Id) is
23660 Found_Type : constant Entity_Id := First_Subtype (Etype (Expr));
23661 Expec_Type : constant Entity_Id := First_Subtype (Expected_Type);
23663 Matching_Field : Entity_Id;
23664 -- Entity to give a more precise suggestion on how to write a one-
23665 -- element positional aggregate.
23667 function Has_One_Matching_Field return Boolean;
23668 -- Determines if Expec_Type is a record type with a single component or
23669 -- discriminant whose type matches the found type or is one dimensional
23670 -- array whose component type matches the found type. In the case of
23671 -- one discriminant, we ignore the variant parts. That's not accurate,
23672 -- but good enough for the warning.
23674 ----------------------------
23675 -- Has_One_Matching_Field --
23676 ----------------------------
23678 function Has_One_Matching_Field return Boolean is
23679 E : Entity_Id;
23681 begin
23682 Matching_Field := Empty;
23684 if Is_Array_Type (Expec_Type)
23685 and then Number_Dimensions (Expec_Type) = 1
23686 and then Covers (Etype (Component_Type (Expec_Type)), Found_Type)
23687 then
23688 -- Use type name if available. This excludes multidimensional
23689 -- arrays and anonymous arrays.
23691 if Comes_From_Source (Expec_Type) then
23692 Matching_Field := Expec_Type;
23694 -- For an assignment, use name of target
23696 elsif Nkind (Parent (Expr)) = N_Assignment_Statement
23697 and then Is_Entity_Name (Name (Parent (Expr)))
23698 then
23699 Matching_Field := Entity (Name (Parent (Expr)));
23700 end if;
23702 return True;
23704 elsif not Is_Record_Type (Expec_Type) then
23705 return False;
23707 else
23708 E := First_Entity (Expec_Type);
23709 loop
23710 if No (E) then
23711 return False;
23713 elsif not Ekind_In (E, E_Discriminant, E_Component)
23714 or else Nam_In (Chars (E), Name_uTag, Name_uParent)
23715 then
23716 Next_Entity (E);
23718 else
23719 exit;
23720 end if;
23721 end loop;
23723 if not Covers (Etype (E), Found_Type) then
23724 return False;
23726 elsif Present (Next_Entity (E))
23727 and then (Ekind (E) = E_Component
23728 or else Ekind (Next_Entity (E)) = E_Discriminant)
23729 then
23730 return False;
23732 else
23733 Matching_Field := E;
23734 return True;
23735 end if;
23736 end if;
23737 end Has_One_Matching_Field;
23739 -- Start of processing for Wrong_Type
23741 begin
23742 -- Don't output message if either type is Any_Type, or if a message
23743 -- has already been posted for this node. We need to do the latter
23744 -- check explicitly (it is ordinarily done in Errout), because we
23745 -- are using ! to force the output of the error messages.
23747 if Expec_Type = Any_Type
23748 or else Found_Type = Any_Type
23749 or else Error_Posted (Expr)
23750 then
23751 return;
23753 -- If one of the types is a Taft-Amendment type and the other it its
23754 -- completion, it must be an illegal use of a TAT in the spec, for
23755 -- which an error was already emitted. Avoid cascaded errors.
23757 elsif Is_Incomplete_Type (Expec_Type)
23758 and then Has_Completion_In_Body (Expec_Type)
23759 and then Full_View (Expec_Type) = Etype (Expr)
23760 then
23761 return;
23763 elsif Is_Incomplete_Type (Etype (Expr))
23764 and then Has_Completion_In_Body (Etype (Expr))
23765 and then Full_View (Etype (Expr)) = Expec_Type
23766 then
23767 return;
23769 -- In an instance, there is an ongoing problem with completion of
23770 -- type derived from private types. Their structure is what Gigi
23771 -- expects, but the Etype is the parent type rather than the
23772 -- derived private type itself. Do not flag error in this case. The
23773 -- private completion is an entity without a parent, like an Itype.
23774 -- Similarly, full and partial views may be incorrect in the instance.
23775 -- There is no simple way to insure that it is consistent ???
23777 -- A similar view discrepancy can happen in an inlined body, for the
23778 -- same reason: inserted body may be outside of the original package
23779 -- and only partial views are visible at the point of insertion.
23781 elsif In_Instance or else In_Inlined_Body then
23782 if Etype (Etype (Expr)) = Etype (Expected_Type)
23783 and then
23784 (Has_Private_Declaration (Expected_Type)
23785 or else Has_Private_Declaration (Etype (Expr)))
23786 and then No (Parent (Expected_Type))
23787 then
23788 return;
23790 elsif Nkind (Parent (Expr)) = N_Qualified_Expression
23791 and then Entity (Subtype_Mark (Parent (Expr))) = Expected_Type
23792 then
23793 return;
23795 elsif Is_Private_Type (Expected_Type)
23796 and then Present (Full_View (Expected_Type))
23797 and then Covers (Full_View (Expected_Type), Etype (Expr))
23798 then
23799 return;
23801 -- Conversely, type of expression may be the private one
23803 elsif Is_Private_Type (Base_Type (Etype (Expr)))
23804 and then Full_View (Base_Type (Etype (Expr))) = Expected_Type
23805 then
23806 return;
23807 end if;
23808 end if;
23810 -- An interesting special check. If the expression is parenthesized
23811 -- and its type corresponds to the type of the sole component of the
23812 -- expected record type, or to the component type of the expected one
23813 -- dimensional array type, then assume we have a bad aggregate attempt.
23815 if Nkind (Expr) in N_Subexpr
23816 and then Paren_Count (Expr) /= 0
23817 and then Has_One_Matching_Field
23818 then
23819 Error_Msg_N ("positional aggregate cannot have one component", Expr);
23821 if Present (Matching_Field) then
23822 if Is_Array_Type (Expec_Type) then
23823 Error_Msg_NE
23824 ("\write instead `&''First ='> ...`", Expr, Matching_Field);
23825 else
23826 Error_Msg_NE
23827 ("\write instead `& ='> ...`", Expr, Matching_Field);
23828 end if;
23829 end if;
23831 -- Another special check, if we are looking for a pool-specific access
23832 -- type and we found an E_Access_Attribute_Type, then we have the case
23833 -- of an Access attribute being used in a context which needs a pool-
23834 -- specific type, which is never allowed. The one extra check we make
23835 -- is that the expected designated type covers the Found_Type.
23837 elsif Is_Access_Type (Expec_Type)
23838 and then Ekind (Found_Type) = E_Access_Attribute_Type
23839 and then Ekind (Base_Type (Expec_Type)) /= E_General_Access_Type
23840 and then Ekind (Base_Type (Expec_Type)) /= E_Anonymous_Access_Type
23841 and then Covers
23842 (Designated_Type (Expec_Type), Designated_Type (Found_Type))
23843 then
23844 Error_Msg_N -- CODEFIX
23845 ("result must be general access type!", Expr);
23846 Error_Msg_NE -- CODEFIX
23847 ("add ALL to }!", Expr, Expec_Type);
23849 -- Another special check, if the expected type is an integer type,
23850 -- but the expression is of type System.Address, and the parent is
23851 -- an addition or subtraction operation whose left operand is the
23852 -- expression in question and whose right operand is of an integral
23853 -- type, then this is an attempt at address arithmetic, so give
23854 -- appropriate message.
23856 elsif Is_Integer_Type (Expec_Type)
23857 and then Is_RTE (Found_Type, RE_Address)
23858 and then Nkind_In (Parent (Expr), N_Op_Add, N_Op_Subtract)
23859 and then Expr = Left_Opnd (Parent (Expr))
23860 and then Is_Integer_Type (Etype (Right_Opnd (Parent (Expr))))
23861 then
23862 Error_Msg_N
23863 ("address arithmetic not predefined in package System",
23864 Parent (Expr));
23865 Error_Msg_N
23866 ("\possible missing with/use of System.Storage_Elements",
23867 Parent (Expr));
23868 return;
23870 -- If the expected type is an anonymous access type, as for access
23871 -- parameters and discriminants, the error is on the designated types.
23873 elsif Ekind (Expec_Type) = E_Anonymous_Access_Type then
23874 if Comes_From_Source (Expec_Type) then
23875 Error_Msg_NE ("expected}!", Expr, Expec_Type);
23876 else
23877 Error_Msg_NE
23878 ("expected an access type with designated}",
23879 Expr, Designated_Type (Expec_Type));
23880 end if;
23882 if Is_Access_Type (Found_Type)
23883 and then not Comes_From_Source (Found_Type)
23884 then
23885 Error_Msg_NE
23886 ("\\found an access type with designated}!",
23887 Expr, Designated_Type (Found_Type));
23888 else
23889 if From_Limited_With (Found_Type) then
23890 Error_Msg_NE ("\\found incomplete}!", Expr, Found_Type);
23891 Error_Msg_Qual_Level := 99;
23892 Error_Msg_NE -- CODEFIX
23893 ("\\missing `WITH &;", Expr, Scope (Found_Type));
23894 Error_Msg_Qual_Level := 0;
23895 else
23896 Error_Msg_NE ("found}!", Expr, Found_Type);
23897 end if;
23898 end if;
23900 -- Normal case of one type found, some other type expected
23902 else
23903 -- If the names of the two types are the same, see if some number
23904 -- of levels of qualification will help. Don't try more than three
23905 -- levels, and if we get to standard, it's no use (and probably
23906 -- represents an error in the compiler) Also do not bother with
23907 -- internal scope names.
23909 declare
23910 Expec_Scope : Entity_Id;
23911 Found_Scope : Entity_Id;
23913 begin
23914 Expec_Scope := Expec_Type;
23915 Found_Scope := Found_Type;
23917 for Levels in Nat range 0 .. 3 loop
23918 if Chars (Expec_Scope) /= Chars (Found_Scope) then
23919 Error_Msg_Qual_Level := Levels;
23920 exit;
23921 end if;
23923 Expec_Scope := Scope (Expec_Scope);
23924 Found_Scope := Scope (Found_Scope);
23926 exit when Expec_Scope = Standard_Standard
23927 or else Found_Scope = Standard_Standard
23928 or else not Comes_From_Source (Expec_Scope)
23929 or else not Comes_From_Source (Found_Scope);
23930 end loop;
23931 end;
23933 if Is_Record_Type (Expec_Type)
23934 and then Present (Corresponding_Remote_Type (Expec_Type))
23935 then
23936 Error_Msg_NE ("expected}!", Expr,
23937 Corresponding_Remote_Type (Expec_Type));
23938 else
23939 Error_Msg_NE ("expected}!", Expr, Expec_Type);
23940 end if;
23942 if Is_Entity_Name (Expr)
23943 and then Is_Package_Or_Generic_Package (Entity (Expr))
23944 then
23945 Error_Msg_N ("\\found package name!", Expr);
23947 elsif Is_Entity_Name (Expr)
23948 and then Ekind_In (Entity (Expr), E_Procedure, E_Generic_Procedure)
23949 then
23950 if Ekind (Expec_Type) = E_Access_Subprogram_Type then
23951 Error_Msg_N
23952 ("found procedure name, possibly missing Access attribute!",
23953 Expr);
23954 else
23955 Error_Msg_N
23956 ("\\found procedure name instead of function!", Expr);
23957 end if;
23959 elsif Nkind (Expr) = N_Function_Call
23960 and then Ekind (Expec_Type) = E_Access_Subprogram_Type
23961 and then Etype (Designated_Type (Expec_Type)) = Etype (Expr)
23962 and then No (Parameter_Associations (Expr))
23963 then
23964 Error_Msg_N
23965 ("found function name, possibly missing Access attribute!",
23966 Expr);
23968 -- Catch common error: a prefix or infix operator which is not
23969 -- directly visible because the type isn't.
23971 elsif Nkind (Expr) in N_Op
23972 and then Is_Overloaded (Expr)
23973 and then not Is_Immediately_Visible (Expec_Type)
23974 and then not Is_Potentially_Use_Visible (Expec_Type)
23975 and then not In_Use (Expec_Type)
23976 and then Has_Compatible_Type (Right_Opnd (Expr), Expec_Type)
23977 then
23978 Error_Msg_N
23979 ("operator of the type is not directly visible!", Expr);
23981 elsif Ekind (Found_Type) = E_Void
23982 and then Present (Parent (Found_Type))
23983 and then Nkind (Parent (Found_Type)) = N_Full_Type_Declaration
23984 then
23985 Error_Msg_NE ("\\found premature usage of}!", Expr, Found_Type);
23987 else
23988 Error_Msg_NE ("\\found}!", Expr, Found_Type);
23989 end if;
23991 -- A special check for cases like M1 and M2 = 0 where M1 and M2 are
23992 -- of the same modular type, and (M1 and M2) = 0 was intended.
23994 if Expec_Type = Standard_Boolean
23995 and then Is_Modular_Integer_Type (Found_Type)
23996 and then Nkind_In (Parent (Expr), N_Op_And, N_Op_Or, N_Op_Xor)
23997 and then Nkind (Right_Opnd (Parent (Expr))) in N_Op_Compare
23998 then
23999 declare
24000 Op : constant Node_Id := Right_Opnd (Parent (Expr));
24001 L : constant Node_Id := Left_Opnd (Op);
24002 R : constant Node_Id := Right_Opnd (Op);
24004 begin
24005 -- The case for the message is when the left operand of the
24006 -- comparison is the same modular type, or when it is an
24007 -- integer literal (or other universal integer expression),
24008 -- which would have been typed as the modular type if the
24009 -- parens had been there.
24011 if (Etype (L) = Found_Type
24012 or else
24013 Etype (L) = Universal_Integer)
24014 and then Is_Integer_Type (Etype (R))
24015 then
24016 Error_Msg_N
24017 ("\\possible missing parens for modular operation", Expr);
24018 end if;
24019 end;
24020 end if;
24022 -- Reset error message qualification indication
24024 Error_Msg_Qual_Level := 0;
24025 end if;
24026 end Wrong_Type;
24028 --------------------------------
24029 -- Yields_Synchronized_Object --
24030 --------------------------------
24032 function Yields_Synchronized_Object (Typ : Entity_Id) return Boolean is
24033 Has_Sync_Comp : Boolean := False;
24034 Id : Entity_Id;
24036 begin
24037 -- An array type yields a synchronized object if its component type
24038 -- yields a synchronized object.
24040 if Is_Array_Type (Typ) then
24041 return Yields_Synchronized_Object (Component_Type (Typ));
24043 -- A descendant of type Ada.Synchronous_Task_Control.Suspension_Object
24044 -- yields a synchronized object by default.
24046 elsif Is_Descendant_Of_Suspension_Object (Typ) then
24047 return True;
24049 -- A protected type yields a synchronized object by default
24051 elsif Is_Protected_Type (Typ) then
24052 return True;
24054 -- A record type or type extension yields a synchronized object when its
24055 -- discriminants (if any) lack default values and all components are of
24056 -- a type that yelds a synchronized object.
24058 elsif Is_Record_Type (Typ) then
24060 -- Inspect all entities defined in the scope of the type, looking for
24061 -- components of a type that does not yeld a synchronized object or
24062 -- for discriminants with default values.
24064 Id := First_Entity (Typ);
24065 while Present (Id) loop
24066 if Comes_From_Source (Id) then
24067 if Ekind (Id) = E_Component then
24068 if Yields_Synchronized_Object (Etype (Id)) then
24069 Has_Sync_Comp := True;
24071 -- The component does not yield a synchronized object
24073 else
24074 return False;
24075 end if;
24077 elsif Ekind (Id) = E_Discriminant
24078 and then Present (Expression (Parent (Id)))
24079 then
24080 return False;
24081 end if;
24082 end if;
24084 Next_Entity (Id);
24085 end loop;
24087 -- Ensure that the parent type of a type extension yields a
24088 -- synchronized object.
24090 if Etype (Typ) /= Typ
24091 and then not Yields_Synchronized_Object (Etype (Typ))
24092 then
24093 return False;
24094 end if;
24096 -- If we get here, then all discriminants lack default values and all
24097 -- components are of a type that yields a synchronized object.
24099 return Has_Sync_Comp;
24101 -- A synchronized interface type yields a synchronized object by default
24103 elsif Is_Synchronized_Interface (Typ) then
24104 return True;
24106 -- A task type yelds a synchronized object by default
24108 elsif Is_Task_Type (Typ) then
24109 return True;
24111 -- Otherwise the type does not yield a synchronized object
24113 else
24114 return False;
24115 end if;
24116 end Yields_Synchronized_Object;
24118 ---------------------------
24119 -- Yields_Universal_Type --
24120 ---------------------------
24122 function Yields_Universal_Type (N : Node_Id) return Boolean is
24123 begin
24124 -- Integer and real literals are of a universal type
24126 if Nkind_In (N, N_Integer_Literal, N_Real_Literal) then
24127 return True;
24129 -- The values of certain attributes are of a universal type
24131 elsif Nkind (N) = N_Attribute_Reference then
24132 return
24133 Universal_Type_Attribute (Get_Attribute_Id (Attribute_Name (N)));
24135 -- ??? There are possibly other cases to consider
24137 else
24138 return False;
24139 end if;
24140 end Yields_Universal_Type;
24142 begin
24143 Erroutc.Subprogram_Name_Ptr := Subprogram_Name'Access;
24144 end Sem_Util;